GCC Code Coverage Report


Directory: src/athena/
File: athena_add_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__add_layer
2 !! Module containing implementation of an element-wise addition layer
3 !!
4 !! This module implements a merge layer that performs element-wise addition
5 !! of multiple input tensors. Commonly used for residual/skip connections.
6 !!
7 !! Mathematical operation:
8 !! output = sum(input_i) for i=1..N
9 !!
10 !! where N is the number of input layers. All inputs must have identical shapes.
11 !! Gradients are copied (not split) to all inputs during backpropagation.
12 use coreutils, only: real32, stop_program
13 use athena__base_layer, only: merge_layer_type, base_layer_type
14 use athena__diffstruc_extd, only: array_ptr_type, add_layers
15 use diffstruc, only: array_type, operator(+)
16 implicit none
17
18
19 private
20
21 public :: add_layer_type
22 public :: read_add_layer
23
24
25 type, extends(merge_layer_type) :: add_layer_type
26 !! Type for add layer with overloaded procedures
27 contains
28 procedure, pass(this) :: set_hyperparams => set_hyperparams_add
29 !! Set the hyperparameters for add layer
30 procedure, pass(this) :: init => init_add
31 !! Initialise add layer
32 procedure, pass(this) :: print_to_unit => print_to_unit_add
33 !! Print the layer to a file
34 procedure, pass(this) :: read => read_add
35 !! Read the layer from a file
36
37 procedure, pass(this) :: calc_input_shape => calc_input_shape_add
38 !! Calculate input shape based on shapes of input layers
39
40 procedure, pass(this) :: combine => combine_add
41 end type add_layer_type
42
43 interface add_layer_type
44 !! Interface for setting up the add layer
45 module function layer_setup( &
46 input_layer_ids, input_rank, verbose &
47 ) result(layer)
48 !! Setup a add layer
49 integer, dimension(:), intent(in) :: input_layer_ids
50 !! Input layer IDs
51 integer, optional, intent(in) :: input_rank
52 !! Input rank
53 integer, optional, intent(in) :: verbose
54 !! Verbosity level
55 type(add_layer_type) :: layer
56 end function layer_setup
57 end interface add_layer_type
58
59
60
61 contains
62
63 !###############################################################################
64 module function layer_setup( &
65 input_layer_ids, input_rank, verbose &
66 ) result(layer)
67 !! Setup a add layer
68 implicit none
69
70 ! Arguments
71 integer, dimension(:), intent(in) :: input_layer_ids
72 !! Input layer IDs
73 integer, optional, intent(in) :: input_rank
74 !! Input rank
75 integer, optional, intent(in) :: verbose
76 !! Verbosity level
77
78 type(add_layer_type) :: layer
79 !! Instance of the add layer
80
81 ! Local variables
82 integer :: input_rank_ = 0
83 !! Input rank
84 integer :: verbose_ = 0
85 !! Verbosity level
86
87 if(present(verbose)) verbose_ = verbose
88
89
90 !---------------------------------------------------------------------------
91 ! Set hyperparameters
92 !---------------------------------------------------------------------------
93 if(present(input_rank))then
94 input_rank_ = input_rank
95 else
96 call stop_program( &
97 "input_rank or input_shape must be provided to concat layer" &
98 )
99 return
100 end if
101 call layer%set_hyperparams( &
102 input_layer_ids = input_layer_ids, &
103 input_rank = input_rank_, &
104 verbose = verbose_ &
105 )
106
107 end function layer_setup
108 !###############################################################################
109
110
111 !###############################################################################
112 subroutine set_hyperparams_add( &
113 this, &
114 input_layer_ids, &
115 input_rank, &
116 verbose &
117 )
118 !! Set the hyperparameters for add layer
119 implicit none
120
121 ! Arguments
122 class(add_layer_type), intent(inout) :: this
123 !! Instance of the add layer
124 integer, dimension(:), intent(in) :: input_layer_ids
125 !! Input layer IDs
126 integer, intent(in) :: input_rank
127 !! Input rank
128 integer, optional, intent(in) :: verbose
129 !! Verbosity level
130
131
132 this%name = "add"
133 this%type = "merg"
134 this%merge_mode = 1 ! pointwise mode
135 this%input_layer_ids = input_layer_ids
136 this%input_rank = input_rank
137 this%output_rank = input_rank
138
139 end subroutine set_hyperparams_add
140 !###############################################################################
141
142
143 !###############################################################################
144 subroutine init_add(this, input_shape, verbose)
145 !! Initialise add layer
146 implicit none
147
148 ! Arguments
149 class(add_layer_type), intent(inout) :: this
150 !! Instance of the add layer
151 integer, dimension(:), intent(in) :: input_shape
152 !! Input shape
153 integer, optional, intent(in) :: verbose
154 !! Verbosity level
155
156 ! Local variables
157 integer :: i
158 !! Loop index
159 integer :: verbose_ = 0
160 !! Verbosity level
161
162
163 !---------------------------------------------------------------------------
164 ! Initialise optional arguments
165 !---------------------------------------------------------------------------
166 if(present(verbose)) verbose_ = verbose
167
168
169 !---------------------------------------------------------------------------
170 ! Initialise input shape
171 !---------------------------------------------------------------------------
172 this%input_rank = size(input_shape)
173 if(.not.allocated(this%input_shape)) call this%set_shape(input_shape)
174
175
176 !---------------------------------------------------------------------------
177 ! Initialise output shape
178 !---------------------------------------------------------------------------
179 this%output_shape = this%input_shape
180 this%output_rank = size(this%output_shape)
181
182
183 !---------------------------------------------------------------------------
184 ! Allocate arrays
185 !---------------------------------------------------------------------------
186 if(allocated(this%output)) deallocate(this%output)
187 allocate(this%output(1,1))
188
189 end subroutine init_add
190 !###############################################################################
191
192
193 !##############################################################################!
194 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
195 !##############################################################################!
196
197
198 !###############################################################################
199 subroutine print_to_unit_add(this, unit)
200 !! Print add layer to unit
201 implicit none
202
203 ! Arguments
204 class(add_layer_type), intent(in) :: this
205 !! Instance of the add layer
206 integer, intent(in) :: unit
207 !! File unit
208
209 ! Local variables
210 integer :: i
211 !! Loop index
212 character(100) :: fmt
213
214
215 ! Write initial parameters
216 !---------------------------------------------------------------------------
217 write(unit,'(3X,"INPUT_RANK = ",I0)') this%input_rank
218 write(fmt,'("(3X,""INPUT_SHAPE ="",",I0,"(1X,I0))")') size(this%input_shape)
219 write(unit,fmt) this%input_shape
220 write(fmt,'("(3X,""INPUT_LAYER_IDS ="",",I0,"(1X,I0))")') size(this%input_layer_ids)
221 write(unit,fmt) this%input_layer_ids
222
223 end subroutine print_to_unit_add
224 !###############################################################################
225
226
227 !###############################################################################
228 subroutine read_add(this, unit, verbose)
229 !! Read add layer from file
230 use athena__tools_infile, only: assign_val, assign_vec, get_val
231 use coreutils, only: to_lower, to_upper, icount
232 implicit none
233
234 ! Arguments
235 class(add_layer_type), intent(inout) :: this
236 !! Instance of the add layer
237 integer, intent(in) :: unit
238 !! Unit number
239 integer, optional, intent(in) :: verbose
240 !! Verbosity level
241
242 ! Local variables
243 integer :: stat, verbose_ = 0
244 !! File status and verbosity level
245 integer :: itmp1 = 0
246 !! Temporary integer
247 integer :: input_rank = 0
248 !! Input rank
249 integer, dimension(:), allocatable :: input_shape, input_layer_ids
250 !! Input shape
251 character(256) :: buffer, tag, err_msg
252 !! Buffer, tag, and error message
253
254
255 ! Initialise optional arguments
256 !---------------------------------------------------------------------------
257 if(present(verbose)) verbose_ = verbose
258
259
260 ! Loop over tags in layer card
261 !---------------------------------------------------------------------------
262 tag_loop: do
263
264 ! Check for end of file
265 !------------------------------------------------------------------------
266 read(unit,'(A)',iostat=stat) buffer
267 if(stat.ne.0)then
268 write(err_msg,'("file encountered error (EoF?) before END ",A)') &
269 to_upper(this%name)
270 call stop_program(err_msg)
271 return
272 end if
273 if(trim(adjustl(buffer)).eq."") cycle tag_loop
274
275 ! Check for end of layer card
276 !------------------------------------------------------------------------
277 if(trim(adjustl(buffer)).eq."END "//to_upper(trim(this%name)))then
278 backspace(unit)
279 exit tag_loop
280 end if
281
282 tag=trim(adjustl(buffer))
283 if(scan(buffer,"=").ne.0) tag=trim(tag(:scan(tag,"=")-1))
284
285 ! Read parameters from file
286 !------------------------------------------------------------------------
287 select case(trim(tag))
288 case("INPUT_SHAPE")
289 itmp1 = icount(get_val(buffer))
290 allocate(input_shape(itmp1), source=0)
291 call assign_vec(buffer, input_shape, itmp1)
292 case("INPUT_RANK")
293 call assign_val(buffer, input_rank, itmp1)
294 case("INPUT_LAYER_IDS")
295 itmp1 = icount(get_val(buffer))
296 allocate(input_layer_ids(itmp1), source=0)
297 call assign_vec(buffer, input_layer_ids, itmp1)
298 case default
299 ! Don't look for "e" due to scientific notation of numbers
300 ! ... i.e. exponent (E+00)
301 if(scan(to_lower(trim(adjustl(buffer))),&
302 'abcdfghijklmnopqrstuvwxyz').eq.0)then
303 cycle tag_loop
304 elseif(tag(:3).eq.'END')then
305 cycle tag_loop
306 end if
307 write(err_msg,'("Unrecognised line in input file: ",A)') &
308 trim(adjustl(buffer))
309 call stop_program(err_msg)
310 return
311 end select
312 end do tag_loop
313
314 if(allocated(input_shape))then
315 if(input_rank.eq.0)then
316 input_rank = size(input_shape)
317 elseif(input_rank.ne.size(input_shape))then
318 write(err_msg,'("input_rank (",I0,") does not match input_shape (",I0,")")') &
319 input_rank, size(input_shape)
320 call stop_program(err_msg)
321 return
322 end if
323 elseif(input_rank.eq.0)then
324 write(err_msg,'("input_rank must be provided if input_shape is not")')
325 call stop_program(err_msg)
326 return
327 end if
328
329
330 ! Set hyperparameters and initialise layer
331 !---------------------------------------------------------------------------
332 call this%set_hyperparams( &
333 input_layer_ids = input_layer_ids, &
334 input_rank = input_rank, &
335 verbose = verbose_ &
336 )
337 call this%init(input_shape = input_shape)
338
339
340 ! Check for end of layer card
341 !---------------------------------------------------------------------------
342 read(unit,'(A)') buffer
343 if(trim(adjustl(buffer)).ne."END "//to_upper(trim(this%name)))then
344 write(0,*) trim(adjustl(buffer))
345 write(err_msg,'("END ",A," not where expected")') to_upper(this%name)
346 call stop_program(err_msg)
347 return
348 end if
349
350 end subroutine read_add
351 !###############################################################################
352
353
354 !###############################################################################
355 function read_add_layer(unit, verbose) result(layer)
356 !! Read add layer from file and return layer
357 implicit none
358
359 ! Arguments
360 integer, intent(in) :: unit
361 !! Unit number
362 integer, optional, intent(in) :: verbose
363 !! Verbosity level
364 class(base_layer_type), allocatable :: layer
365 !! Instance of the add layer
366
367 ! Local variables
368 integer :: verbose_ = 0
369 !! Verbosity level
370
371 if(present(verbose)) verbose_ = verbose
372 allocate(layer, source=add_layer_type(input_layer_ids=[0,0]))
373 call layer%read(unit, verbose=verbose_)
374
375 end function read_add_layer
376 !###############################################################################
377
378
379 !##############################################################################!
380 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
381 !##############################################################################!
382
383
384 !###############################################################################
385 function calc_input_shape_add(this, input_shapes) result(input_shape)
386 !! Calculate input shape based on shapes of input layers
387 implicit none
388
389 ! Arguments
390 class(add_layer_type), intent(in) :: this
391 !! Instance of the layer
392 integer, dimension(:,:), intent(in) :: input_shapes
393 !! Input shapes
394 integer, allocatable, dimension(:) :: input_shape
395 !! Calculated input shape
396
397 ! Local variables
398 integer :: i
399
400 ! Check that all input shapes are the same
401 do i = 2, size(input_shapes, 2), 1
402 if(any(input_shapes(:,1).ne.input_shapes(:,i)))then
403 call stop_program("All input shapes to add layer must be the same")
404 return
405 end if
406 end do
407
408 ! Set input shape
409 input_shape = input_shapes(:,1)
410
411 end function calc_input_shape_add
412 !###############################################################################
413
414
415
416 !##############################################################################!
417 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
418 !##############################################################################!
419
420
421 !###############################################################################
422 subroutine combine_add(this, input_list)
423 !! Forward propagation for 2D input
424 implicit none
425
426 ! Arguments
427 class(add_layer_type), intent(inout) :: this
428 !! Instance of the add layer
429 type(array_ptr_type), dimension(:), intent(in) :: input_list
430 !! Input values
431
432 ! Local variables
433 integer :: i, j, s
434 !! Loop index
435 type(array_type), pointer :: ptr
436 !! Pointer array
437
438
439 if(allocated(this%output))then
440 if(any(shape(this%output).ne.shape(input_list(1)%array)))then
441 deallocate(this%output)
442 allocate(this%output( &
443 size(input_list(1)%array,1), &
444 size(input_list(1)%array,2) &
445 ))
446 end if
447 else
448 allocate(this%output( &
449 size(input_list(1)%array,1), &
450 size(input_list(1)%array,2) &
451 ))
452 end if
453
454 do s = 1, size(input_list(1)%array, 2)
455 index_loop: do i = 1, size(input_list(1)%array, 1)
456 do j = 1, size(input_list,1)
457 if(.not.input_list(j)%array(i,s)%allocated) cycle index_loop
458 end do
459 ptr => add_layers(input_list, i, s)
460 call this%output(i,s)%zero_grad()
461 call this%output(i,s)%assign_and_deallocate_source(ptr)
462 this%output(i,s)%is_temporary = .false.
463 end do index_loop
464 end do
465
466 end subroutine combine_add
467 !###############################################################################
468
469 end module athena__add_layer
470