GCC Code Coverage Report


Directory: src/athena/
File: athena_base_layer.f90
Date: 2025-12-10 07:37:07
Exec Total Coverage
Lines: 0 0 100.0%
Functions: 0 0 -%
Branches: 0 0 -%

Line Branch Exec Source
1 module athena__base_layer
2 !! Module containing the abstract base layer type
3 !!
4 !! This module contains the abstract base layer type, from which all other
5 !! layers are derived. The module also contains the abstract derived types
6 !! for the following layer types:
7 !! - padding
8 !! - pooling
9 !! - dropout
10 !! - learnable
11 !! - convolutional
12 !! - batch normalisation
13 !!
14 !! The following procedures are based on code from the neural-fortran library
15 !! https://github.com/modern-fortran/neural-fortran/blob/main/src/nf/nf_layer.f90
16 use coreutils, only: real32
17 use athena__clipper, only: clip_type
18 use athena__misc_types, only: base_actv_type, base_init_type, facets_type, &
19 onnx_attribute_type, onnx_node_type, onnx_initialiser_type, onnx_tensor_type
20 use diffstruc, only: array_type
21 use athena__diffstruc_extd, only: array_ptr_type
22 use graphstruc, only: graph_type
23 implicit none
24
25 private
26
27 public :: base_layer_type
28 public :: pad_layer_type
29 public :: pool_layer_type
30 public :: drop_layer_type
31 public :: learnable_layer_type
32 public :: conv_layer_type
33 public :: batch_layer_type
34 public :: merge_layer_type
35
36 !-------------------------------------------------------------------------------
37 ! layer abstract type
38 !-------------------------------------------------------------------------------
39 type, abstract :: base_layer_type
40 !! Type for base layer, from which all other layers are derived
41 integer :: id
42 !! Unique identifier
43 integer :: input_rank = 0
44 !! Rank of input data
45 integer :: output_rank = 0
46 !! Rank of output data
47 logical :: inference = .false.
48 !! Inference mode
49 logical :: use_graph_input = .false.
50 !! Use graph input
51 logical :: use_graph_output = .false.
52 !! Use graph output
53 character(:), allocatable :: name
54 !! Layer name
55 character(4) :: type = 'base'
56 !! Layer type
57 character(20) :: subtype = repeat(" ",20)
58 type(graph_type), allocatable, dimension(:) :: graph
59 !! Graph structure of input data
60 class(array_type), allocatable, dimension(:,:) :: output
61 !! Output
62 integer, allocatable, dimension(:) :: input_shape
63 !! Input shape
64 integer, allocatable, dimension(:) :: output_shape
65 !! Output shape
66 contains
67 procedure, pass(this) :: set_rank => set_rank_base
68 !! Set the input and output ranks of the layer
69 procedure, pass(this) :: set_shape => set_shape_base
70 !! Set the input shape of the layer
71 procedure, pass(this) :: get_num_params => get_num_params_base
72 !! Get the number of parameters in the layer
73 procedure, pass(this) :: print => print_base
74 !! Print the layer to a file with additional information
75 procedure, pass(this) :: print_to_unit => print_to_unit_base
76 !! Print the layer to a unit
77 procedure, pass(this) :: get_attributes => get_attributes_base
78 !! Get the attributes of the layer (for ONNX export)
79 procedure, pass(this) :: extract_output => extract_output_base
80 !! Extract the output of the layer as a standard real array
81 procedure(initialise), deferred, pass(this) :: init
82 !! Initialise the layer
83
84 procedure, pass(this) :: forward => forward_base
85 !! Forward pass of layer
86 procedure, pass(this) :: forward_eval => forward_eval_base
87 !! Forward pass of layer and return output for evaluation
88
89 procedure, pass(this) :: nullify_graph => nullify_graph_base
90 !! Nullify the forward pass data of the layer to free memory
91
92
93 !! Forward pass of layer using derived array_type
94 procedure(read_layer), deferred, pass(this) :: read
95 !! Read layer from file
96 procedure, pass(this) :: build_from_onnx => build_from_onnx_base
97 !! Build layer from ONNX node and initialiser
98 procedure, pass(this) :: set_graph => set_graph_base
99 !! Set the graph structure of the input data !! this is adjacency and edge weighting
100 end type base_layer_type
101
102 interface
103 module subroutine print_base(this, file, unit, print_header_footer)
104 !! Print the layer to a file with additional information
105 class(base_layer_type), intent(in) :: this
106 !! Instance of the layer
107 character(*), optional, intent(in) :: file
108 !! File name
109 integer, optional, intent(in) :: unit
110 !! Unit number
111 logical, optional, intent(in) :: print_header_footer
112 !! Boolean whether to print header and footer
113 end subroutine print_base
114
115 module subroutine print_to_unit_base(this, unit)
116 !! Print the layer to a file
117 class(base_layer_type), intent(in) :: this
118 !! Instance of the layer
119 integer, intent(in) :: unit
120 !! File unit
121 end subroutine print_to_unit_base
122
123 module function get_attributes_base(this) result(attributes)
124 !! Get the attributes of the layer (for ONNX export)
125 class(base_layer_type), intent(in) :: this
126 !! Instance of the layer
127 type(onnx_attribute_type), allocatable, dimension(:) :: attributes
128 !! Attributes of the layer
129 end function get_attributes_base
130
131 module subroutine set_rank_base(this, input_rank, output_rank)
132 !! Set the input and output ranks of the layer
133 class(base_layer_type), intent(inout) :: this
134 !! Instance of the layer
135 integer, intent(in) :: input_rank
136 !! Input rank
137 integer, intent(in) :: output_rank
138 !! Output rank
139 end subroutine set_rank_base
140
141 module subroutine set_shape_base(this, input_shape)
142 !! Set the input shape of the layer
143 class(base_layer_type), intent(inout) :: this
144 !! Instance of the layer
145 integer, dimension(:), intent(in) :: input_shape
146 !! Input shape
147 end subroutine set_shape_base
148
149 module subroutine extract_output_base(this, output)
150 !! Extract the output of the layer as a standard real array
151 class(base_layer_type), intent(in) :: this
152 !! Instance of the layer
153 real(real32), dimension(..), allocatable, intent(out) :: output
154 !! Output values
155 end subroutine extract_output_base
156
157 pure module function get_num_params_base(this) result(num_params)
158 class(base_layer_type), intent(in) :: this
159 integer :: num_params
160 end function get_num_params_base
161 end interface
162
163
164 interface
165 module subroutine initialise(this, input_shape, verbose)
166 !! Initialise the layer
167 class(base_layer_type), intent(inout) :: this
168 !! Instance of the layer
169 integer, dimension(:), intent(in) :: input_shape
170 !! Input shape
171 integer, optional, intent(in) :: verbose
172 !! Verbosity level
173 end subroutine initialise
174 end interface
175
176 interface
177 pure module function get_num_params(this) result(num_params)
178 !! Get number of parameters in layer
179 class(base_layer_type), intent(in) :: this
180 !! Instance of the layer
181 integer :: num_params
182 !! Number of parameters
183 end function get_num_params
184 end interface
185
186 interface
187 module subroutine forward_base(this, input)
188 !! Forward pass of layer
189 class(base_layer_type), intent(inout) :: this
190 !! Instance of the layer
191 class(array_type), dimension(:,:), intent(in) :: input
192 !! Input data
193 end subroutine forward_base
194
195 module function forward_eval_base(this, input) result(output)
196 !! Forward pass of layer and return output for evaluation
197 class(base_layer_type), intent(inout), target :: this
198 !! Instance of the layer
199 class(array_type), dimension(:,:), intent(in) :: input
200 !! Input data
201 type(array_type), pointer :: output(:,:)
202 !! Output data
203 end function forward_eval_base
204
205 module subroutine set_graph_base(this, graph)
206 !! Set the graph structure of the input data
207 class(base_layer_type), intent(inout) :: this
208 !! Instance of the layer
209 type(graph_type), dimension(:), intent(in) :: graph
210 !! Graph structure of input data
211 end subroutine set_graph_base
212
213 module subroutine nullify_graph_base(this)
214 !! Nullify the forward pass data of the layer to free memory
215 class(base_layer_type), intent(inout) :: this
216 !! Instance of the layer
217 end subroutine nullify_graph_base
218 end interface
219
220 interface
221 module subroutine read_layer(this, unit, verbose)
222 !! Read layer from file
223 class(base_layer_type), intent(inout) :: this
224 !! Instance of the layer
225 integer, intent(in) :: unit
226 !! File unit
227 integer, optional, intent(in) :: verbose
228 !! Verbosity level
229 end subroutine read_layer
230
231 module subroutine build_from_onnx_base( &
232 this, node, initialisers, value_info, verbose &
233 )
234 !! Build layer from ONNX node
235 class(base_layer_type), intent(inout) :: this
236 !! Instance of the layer
237 type(onnx_node_type), intent(in) :: node
238 !! ONNX node
239 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
240 !! ONNX initialisers
241 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
242 !! ONNX value info
243 integer, intent(in) :: verbose
244 !! Verbosity level
245 end subroutine build_from_onnx_base
246 end interface
247
248
249 type, abstract, extends(base_layer_type) :: pad_layer_type
250 !! Type for padding layers
251 integer :: num_channels
252 !! Number of channels
253 integer :: imethod = 0
254 !! Method for padding
255 integer, allocatable, dimension(:) :: pad
256 !! Padding size
257 character(len=20) :: method = 'valid'
258 !! Padding method
259 integer, allocatable, dimension(:,:) :: orig_bound, dest_bound
260 !! Original and destination bounds
261 type(facets_type), dimension(:), allocatable :: facets
262 !! Facets of the layer
263 contains
264 procedure, pass(this) :: init => init_pad
265 !! Initialise the layer
266 procedure, pass(this) :: print_to_unit => print_to_unit_pad
267 !! Print layer to unit
268 end type pad_layer_type
269
270 interface
271 module subroutine print_to_unit_pad(this, unit)
272 !! Print layer to unit
273 class(pad_layer_type), intent(in) :: this
274 !! Instance of the layer
275 integer, intent(in) :: unit
276 !! File unit
277 end subroutine print_to_unit_pad
278
279 module subroutine init_pad(this, input_shape, verbose)
280 class(pad_layer_type), intent(inout) :: this
281 integer, dimension(:), intent(in) :: input_shape
282 integer, optional, intent(in) :: verbose
283 end subroutine init_pad
284 end interface
285
286
287 type, abstract, extends(base_layer_type) :: pool_layer_type
288 !! Type for pooling layers
289 integer, allocatable, dimension(:) :: pool, strd
290 !! Pooling and stride sizes
291 integer :: num_channels
292 !! Number of channels
293 class(pad_layer_type), allocatable :: pad_layer
294 !! Padding layer
295 contains
296 procedure, pass(this) :: init => init_pool
297 !! Initialise the layer
298 procedure, pass(this) :: print_to_unit => print_to_unit_pool
299 !! Print layer to unit
300 procedure, pass(this) :: get_attributes => get_attributes_pool
301 !! Get the attributes of the layer (for ONNX export)
302 end type pool_layer_type
303
304 interface
305 module subroutine print_to_unit_pool(this, unit)
306 !! Print layer to unit
307 class(pool_layer_type), intent(in) :: this
308 !! Instance of the layer
309 integer, intent(in) :: unit
310 !! File unit
311 end subroutine print_to_unit_pool
312
313 module subroutine init_pool(this, input_shape, verbose)
314 class(pool_layer_type), intent(inout) :: this
315 integer, dimension(:), intent(in) :: input_shape
316 integer, optional, intent(in) :: verbose
317 end subroutine init_pool
318
319 module function get_attributes_pool(this) result(attributes)
320 !! Get the attributes of the layer (for ONNX export)
321 class(pool_layer_type), intent(in) :: this
322 !! Instance of the layer
323 type(onnx_attribute_type), allocatable, dimension(:) :: attributes
324 !! Attributes of the layer
325 end function get_attributes_pool
326 end interface
327
328
329 type, abstract, extends(base_layer_type) :: drop_layer_type
330 !! Type for dropout layers
331 real(real32) :: rate = 0.1_real32
332 !! Dropout rate, rate = 1 - keep_prob -- typical = 0.05-0.25
333 contains
334 procedure(generate_mask), deferred, pass(this) :: generate_mask
335 !! Generate dropout mask
336 end type drop_layer_type
337
338 abstract interface
339 subroutine generate_mask(this)
340 !! Generate dropout mask
341 import :: drop_layer_type
342 class(drop_layer_type), intent(inout) :: this
343 !! Instance of the layer
344 end subroutine generate_mask
345 end interface
346
347
348 type, abstract, extends(base_layer_type) :: merge_layer_type
349 !! Type for merge layers (i.e. add, multiply, concatenate)
350 integer :: merge_mode = 1
351 !! Integer code for fundamental merge method
352 !! 1 = pointwise
353 !! 2 = concatenate
354 !! 3 = reduction
355 !! 4 = parametric (NOT IMPLEMENTED)
356 character(len=20) :: method
357 !! Merge method
358 integer :: num_input_layers = 0
359 !! Number of input layers
360 integer, allocatable, dimension(:) :: input_layer_ids
361 !! IDs of input layers
362 contains
363 procedure(combine_merge), deferred, pass(this) :: combine
364 !! Merge two layers (forward)
365 procedure(calc_input_shape), deferred, pass(this) :: calc_input_shape
366 !! Calculate input shape based on shapes of input layers
367 end type merge_layer_type
368
369 interface
370 module subroutine combine_merge(this, input_list)
371 !! Combine two layers (forward)
372 class(merge_layer_type), intent(inout) :: this
373 !! Instance of the layer
374 type(array_ptr_type), dimension(:), intent(in) :: input_list
375 !! Input values
376 end subroutine combine_merge
377
378 module function calc_input_shape(this, input_shapes) result(input_shape)
379 !! Calculate input shape based on shapes of input layers
380 class(merge_layer_type), intent(in) :: this
381 !! Instance of the layer
382 integer, dimension(:,:), intent(in) :: input_shapes
383 !! Input shapes
384 integer, allocatable, dimension(:) :: input_shape
385 !! Calculated input shape
386 end function calc_input_shape
387 end interface
388
389 type, abstract, extends(base_layer_type) :: learnable_layer_type
390 !! Type for layers with learnable parameters
391 integer :: num_params = 0
392 !! Number of learnable parameters
393 logical :: use_bias = .false.
394 !! Layer has bias
395 integer, allocatable, dimension(:,:) :: weight_shape
396 !! Shape of weights
397 integer, allocatable, dimension(:) :: bias_shape
398 !! Shape of biases
399 type(array_type), allocatable, dimension(:) :: params
400 !! Learnable parameters
401 character(len=14) :: kernel_initialiser='', bias_initialiser=''
402 !! Initialisers for kernel and bias
403 class(base_init_type), allocatable :: kernel_init, bias_init
404 !! Initialisers for kernel and bias
405 class(base_actv_type), allocatable :: activation
406 !! Activation function
407 contains
408 procedure, pass(this) :: get_params => get_params
409 !! Get learnable parameters of layer
410 procedure, pass(this) :: set_params => set_params
411 !! Set learnable parameters of layer
412 procedure, pass(this) :: get_gradients => get_gradients
413 !! Get parameter gradients of layer
414 procedure, pass(this) :: set_gradients => set_gradients
415 !! Set learnable parameters of layer
416
417 procedure, pass(this) :: reduce => reduce_learnable
418 !! Merge another learnable layer into this one
419 procedure :: add_t_t => add_learnable
420 !! Add two layers
421 generic :: operator(+) => add_t_t
422 !! Operator overloading for addition
423 end type learnable_layer_type
424
425 interface
426 module subroutine reduce_learnable(this, input)
427 !! Merge another learnable layer into this one
428 class(learnable_layer_type), intent(inout) :: this
429 !! Instance of the layer
430 class(learnable_layer_type), intent(in) :: input
431 !! Other layer to merge
432 end subroutine reduce_learnable
433
434 module function add_learnable(a, b) result(output)
435 !! Add two layers
436 class(learnable_layer_type), intent(in) :: a, b
437 !! Instances of the layers
438 class(learnable_layer_type), allocatable :: output
439 !! Output layer
440 end function add_learnable
441 end interface
442
443 interface
444 pure module function get_params(this) result(params)
445 !! Get learnable parameters of layer
446 class(learnable_layer_type), intent(in) :: this
447 !! Instance of the layer
448 real(real32), dimension(this%num_params) :: params
449 !! Learnable parameters
450 end function get_params
451
452 module subroutine set_params(this, params)
453 !! Set learnable parameters of layer
454 class(learnable_layer_type), intent(inout) :: this
455 !! Instance of the layer
456 real(real32), dimension(this%num_params), intent(in) :: params
457 !! Learnable parameters
458 end subroutine set_params
459
460 pure module function get_gradients(this, clip_method) result(gradients)
461 !! Get parameter gradients of layer
462 class(learnable_layer_type), intent(in) :: this
463 !! Instance of the layer
464 type(clip_type), optional, intent(in) :: clip_method
465 !! Clip method
466 real(real32), dimension(this%num_params) :: gradients
467 !! Parameter gradients
468 end function get_gradients
469
470 module subroutine set_gradients(this, gradients)
471 !! Set learnable parameters of layer
472 class(learnable_layer_type), intent(inout) :: this
473 !! Instance of the layer
474 real(real32), dimension(..), intent(in) :: gradients
475 !! Learnable parameters
476 end subroutine set_gradients
477 end interface
478
479 type, abstract, extends(learnable_layer_type) :: conv_layer_type
480 integer :: num_channels
481 !! Number of channels
482 integer :: num_filters
483 !! Number of filters
484 integer, allocatable, dimension(:) :: knl, stp, dil
485 !! Kernel, stride, and dilation sizes
486 real(real32), pointer :: bias(:) => null()
487 !! Bias pointer
488 class(pad_layer_type), allocatable :: pad_layer
489 !! Optional preprocess padding layer
490 class(array_type), allocatable :: di_padded
491 !! Padded input gradients
492 contains
493 procedure, pass(this) :: get_num_params => get_num_params_conv
494 !! Get the number of parameters in the layer
495 procedure, pass(this) :: init => init_conv
496 !! Initialise the layer
497 procedure, pass(this) :: get_attributes => get_attributes_conv
498 !! Get the attributes of the layer (for ONNX export)
499 procedure, pass(this) :: print_to_unit => print_to_unit_conv
500 !! Print layer to unit
501 end type conv_layer_type
502
503 interface
504 pure module function get_num_params_conv(this) result(num_params)
505 class(conv_layer_type), intent(in) :: this
506 integer :: num_params
507 end function get_num_params_conv
508
509 module subroutine init_conv(this, input_shape, verbose)
510 class(conv_layer_type), intent(inout) :: this
511 integer, dimension(:), intent(in) :: input_shape
512 integer, optional, intent(in) :: verbose
513 end subroutine init_conv
514
515 module function get_attributes_conv(this) result(attributes)
516 class(conv_layer_type), intent(in) :: this
517 type(onnx_attribute_type), allocatable, dimension(:) :: attributes
518 end function get_attributes_conv
519
520 module subroutine print_to_unit_conv(this, unit)
521 !! Print layer to unit
522 class(conv_layer_type), intent(in) :: this
523 !! Instance of the layer
524 integer, intent(in) :: unit
525 !! File unit
526 end subroutine print_to_unit_conv
527 end interface
528
529 type, abstract, extends(learnable_layer_type) :: batch_layer_type
530 !! Type for batch normalisation layers
531 integer :: num_channels
532 !! Number of channels
533 real(real32) :: momentum = 0.99_real32
534 !! Momentum factor
535 !! NOTE: if momentum = 0, mean and variance batch-dependent values
536 !! NOTE: if momentum > 0, mean and variance are running averages
537 real(real32) :: epsilon = 0.001_real32
538 !! Epsilon factor
539 real(real32) :: gamma_init_mean = 1._real32, gamma_init_std = 0.01_real32
540 !! Initialisation parameters for gamma
541 real(real32) :: beta_init_mean = 0._real32, beta_init_std = 0.01_real32
542 !! Initialisation parameters for beta
543 class(base_init_type), allocatable :: moving_mean_init, moving_variance_init
544 !! Initialisers for moving mean and variance
545 real(real32), allocatable, dimension(:) :: mean, variance
546 !! Mean and variance (not learnable)
547 contains
548 procedure, pass(this) :: get_num_params => get_num_params_batch
549 !! Get the number of parameters in the layer
550 procedure, pass(this) :: init => init_batch
551 !! Initialise the layer
552 procedure, pass(this) :: print_to_unit => print_to_unit_batch
553 !! Print layer to unit
554 procedure, pass(this) :: get_attributes => get_attributes_batch
555 !! Get the attributes of the layer (for ONNX export)
556 end type batch_layer_type
557
558 interface
559
560 pure module function get_num_params_batch(this) result(num_params)
561 class(batch_layer_type), intent(in) :: this
562 integer :: num_params
563 end function get_num_params_batch
564
565 module subroutine init_batch(this, input_shape, verbose)
566 class(batch_layer_type), intent(inout) :: this
567 integer, dimension(:), intent(in) :: input_shape
568 integer, optional, intent(in) :: verbose
569 end subroutine init_batch
570
571 module subroutine print_to_unit_batch(this, unit)
572 !! Print layer to unit
573 class(batch_layer_type), intent(in) :: this
574 !! Instance of the layer
575 integer, intent(in) :: unit
576 !! File unit
577 end subroutine print_to_unit_batch
578
579 module function get_attributes_batch(this) result(attributes)
580 class(batch_layer_type), intent(in) :: this
581 !! Instance of the layer
582 type(onnx_attribute_type), allocatable, dimension(:) :: attributes
583 !! Attributes of the layer
584 end function get_attributes_batch
585 end interface
586
587
588 end module athena__base_layer
589