GCC Code Coverage Report


Directory: src/athena/
File: athena_activation_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__actv_layer
2 !! Module containing implementation of the activation layer
3 !!
4 !! This module wraps various activation functions into a layer type,
5 !! applying element-wise non-linear transformations to inputs.
6 !!
7 !! Mathematical operation:
8 !! y = σ(x)
9 !!
10 !! where σ is one of: relu, sigmoid, tanh, softmax, linear, etc.
11 !!
12 !! Properties:
13 !! - No learnable parameters (fixed non-linearity)
14 !! - Element-wise operation (preserves shape)
15 !! - Enables networks to learn non-linear functions
16 !! - Choice of activation affects gradient flow and convergence
17 use coreutils, only: real32, stop_program
18 use athena__base_layer, only: base_layer_type
19 use athena__misc_types, only: base_actv_type, &
20 onnx_node_type, onnx_initialiser_type, onnx_tensor_type
21 use diffstruc, only: array_type
22 implicit none
23
24
25 private
26
27 public :: actv_layer_type
28 public :: read_actv_layer, create_from_onnx_actv_layer
29
30
31 type, extends(base_layer_type) :: actv_layer_type
32 !! Layer type for activation layers
33 class(base_actv_type), allocatable :: activation
34 !! Activation function
35 contains
36 procedure, pass(this) :: set_rank => set_rank_actv
37 !! Set the input and output ranks of the layer
38 procedure, pass(this) :: set_hyperparams => set_hyperparams_actv
39 !! Set hyperparameters
40 procedure, pass(this) :: init => init_actv
41 !! Initialise layer
42 procedure, pass(this) :: print_to_unit => print_to_unit_actv
43 !! Print layer to unit
44 procedure, pass(this) :: read => read_actv
45 !! Read layer from file
46 procedure, pass(this) :: build_from_onnx => build_from_onnx_actv
47 !! Build activation layer from ONNX node and initialiser
48
49 procedure, pass(this) :: forward => forward_actv
50 !! Forward propagation derived type handler
51
52 end type actv_layer_type
53
54
55 interface actv_layer_type
56 !! Interface for the activation layer type
57 module function layer_setup( &
58 activation, &
59 input_shape, &
60 verbose &
61 ) result(layer)
62 !! Set up the activation layer
63 class(*), intent(in) :: activation
64 !! Activation function
65 integer, dimension(:), optional, intent(in) :: input_shape
66 !! Input shape
67 integer, optional, intent(in) :: verbose
68 !! Verbosity level
69 type(actv_layer_type) :: layer
70 !! Instance of the activation layer
71 end function layer_setup
72 end interface actv_layer_type
73
74
75
76 contains
77
78 !###############################################################################
79 module function layer_setup( &
80 activation, &
81 input_shape, &
82 verbose &
83 ) result(layer)
84 !! Set up the activation layer
85 use athena__activation, only: activation_setup
86 implicit none
87
88 ! Arguments
89 class(*), intent(in) :: activation
90 !! Activation function
91 integer, dimension(:), optional, intent(in) :: input_shape
92 !! Input shape
93 integer, optional, intent(in) :: verbose
94 !! Verbosity level
95 type(actv_layer_type) :: layer
96 !! Instance of the activation layer
97
98 ! Local variables
99 class(base_actv_type), allocatable :: activation_
100 !! Activation function
101 integer :: verbose_
102 !! Verbosity level
103
104
105 verbose_ = 0
106 if(present(verbose)) verbose_ = verbose
107
108 !---------------------------------------------------------------------------
109 ! Set activation function
110 !---------------------------------------------------------------------------
111 activation_ = activation_setup(activation)
112
113
114 !---------------------------------------------------------------------------
115 ! set hyperparameters
116 !---------------------------------------------------------------------------
117 call layer%set_hyperparams( &
118 activation = activation_, &
119 verbose = verbose_ &
120 )
121
122
123 !---------------------------------------------------------------------------
124 ! initialise layer shape
125 !---------------------------------------------------------------------------
126 if(present(input_shape)) call layer%init( &
127 input_shape=input_shape, &
128 verbose=verbose_ &
129 )
130
131 end function layer_setup
132 !###############################################################################
133
134
135 !###############################################################################
136 subroutine set_hyperparams_actv( &
137 this, &
138 activation, &
139 input_rank, &
140 verbose &
141 )
142 !! Set hyperparameters for activation layer
143 use athena__activation, only: activation_setup
144 use coreutils, only: to_lower
145 implicit none
146
147 ! Arguments
148 class(actv_layer_type), intent(inout) :: this
149 !! Instance of the activation layer
150 integer, optional, intent(in) :: input_rank
151 !! Input rank
152 class(base_actv_type), allocatable, intent(in) :: activation
153 !! Activation function
154 integer, optional, intent(in) :: verbose
155 !! Verbosity level
156
157
158 this%name = "actv"
159 this%type = "actv"
160 this%input_rank = 0
161 if(present(input_rank)) this%input_rank = input_rank
162 this%output_rank = this%input_rank
163 if(.not.allocated(activation))then
164 this%activation = activation_setup("none")
165 else
166 if(allocated(this%activation)) deallocate(this%activation)
167 allocate(this%activation, source=activation)
168 end if
169 this%subtype = trim(to_lower(this%activation%name))
170
171 if(present(verbose))then
172 if(abs(verbose).gt.0)then
173 write(*,'("ACTV activation function: ",A)') &
174 trim(this%activation%name)
175 end if
176 end if
177
178 end subroutine set_hyperparams_actv
179 !###############################################################################
180
181
182 !###############################################################################
183 subroutine init_actv(this, input_shape, verbose)
184 !! Initialise activation layer
185 implicit none
186
187 ! Arguments
188 class(actv_layer_type), intent(inout) :: this
189 !! Instance of the activation layer
190 integer, dimension(:), intent(in) :: input_shape
191 !! Input shape
192 integer, optional, intent(in) :: verbose
193 !! Verbosity level
194
195 ! Local variables
196 integer :: verbose_ = 0
197 !! Verbosity level
198
199
200 !---------------------------------------------------------------------------
201 ! initialise optional arguments
202 !---------------------------------------------------------------------------
203 if(present(verbose)) verbose_ = verbose
204
205
206 !---------------------------------------------------------------------------
207 ! initialise input shape
208 !---------------------------------------------------------------------------
209 this%input_rank = size(input_shape, dim=1)
210 this%output_rank = this%input_rank
211 if(.not.allocated(this%input_shape)) call this%set_shape(input_shape)
212 this%output_shape = this%input_shape
213
214
215 !---------------------------------------------------------------------------
216 ! Allocate arrays
217 !---------------------------------------------------------------------------
218 if(this%use_graph_input)then
219 call stop_program( &
220 "Graph input not supported for activation layer" &
221 )
222 return
223 end if
224 if(allocated(this%output)) deallocate(this%output)
225 allocate(this%output(1,1))
226
227 end subroutine init_actv
228 !###############################################################################
229
230
231 !###############################################################################
232 subroutine set_rank_actv(this, input_rank, output_rank)
233 !! Set the input and output ranks of the activation layer
234 implicit none
235
236 ! Arguments
237 class(actv_layer_type), intent(inout) :: this
238 !! Instance of the activation layer
239 integer, intent(in) :: input_rank
240 !! Input rank
241 integer, intent(in) :: output_rank
242 !! Output rank
243
244 this%input_rank = input_rank
245 this%output_rank = output_rank
246 if(this%input_rank.ne.this%output_rank)then
247 call stop_program("Warning: Activation layer input and output ranks differ")
248 return
249 end if
250 if(this%input_rank.lt.1) then
251 write(*,*) "Error: Activation layer input rank must be at least 1"
252 call stop_program("Invalid activation layer input rank")
253 return
254 end if
255 if(this%output_rank.lt.1) then
256 write(*,*) "Error: Activation layer output rank must be at least 1"
257 call stop_program("Invalid activation layer output rank")
258 return
259 end if
260
261 end subroutine set_rank_actv
262 !###############################################################################
263
264
265 !##############################################################################!
266 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
267 !##############################################################################!
268
269
270 !###############################################################################
271 subroutine print_to_unit_actv(this, unit)
272 !! Print activation layer to unit
273 use coreutils, only: to_upper
274 implicit none
275
276 ! Arguments
277 class(actv_layer_type), intent(in) :: this
278 !! Instance of the activation layer
279 integer, intent(in) :: unit
280 !! File unit
281
282
283 ! Write initial parameters
284 !---------------------------------------------------------------------------
285 write(unit,'(3X,"INPUT_SHAPE = ",3(1X,I0))') this%input_shape
286 if(this%activation%name .ne. 'none')then
287 call this%activation%print_to_unit(unit)
288 end if
289
290 end subroutine print_to_unit_actv
291 !###############################################################################
292
293
294 !###############################################################################
295 subroutine read_actv(this, unit, verbose)
296 !! Read activation layer from file
297 use athena__tools_infile, only: assign_val, assign_vec
298 use coreutils, only: to_lower, to_upper
299 use athena__activation, only: read_activation
300 implicit none
301
302 ! Arguments
303 class(actv_layer_type), intent(inout) :: this
304 !! Instance of the activation layer
305 integer, intent(in) :: unit
306 !! File unit
307 integer, optional, intent(in) :: verbose
308 !! Verbosity level
309
310 ! Local variables
311 integer :: verbose_ = 0
312 !! Verbosity level
313 integer :: stat
314 !! File status
315 integer :: itmp1, iline
316 !! Temporary integer and line counter
317 character(20) :: activation_name
318 !! Activation function name
319 class(base_actv_type), allocatable :: activation
320 !! Activation function
321 integer, dimension(3) :: input_shape
322 !! Input shape
323 character(256) :: buffer, tag, err_msg
324 !! Buffer for reading lines, tag for identifying lines, error message
325
326
327 ! Initialise optional arguments
328 !---------------------------------------------------------------------------
329 if(present(verbose)) verbose_ = verbose
330
331
332 ! Loop over tags in layer card
333 !---------------------------------------------------------------------------
334 iline = 0
335 tag_loop: do
336
337 ! Check for end of file
338 !------------------------------------------------------------------------
339 read(unit,'(A)',iostat=stat) buffer
340 if(stat.ne.0)then
341 write(err_msg,'("file encountered error (EoF?) before END ",A)') &
342 to_upper(this%name)
343 call stop_program(err_msg)
344 return
345 end if
346 if(trim(adjustl(buffer)).eq."") cycle tag_loop
347
348 ! Check for end of layer card
349 !------------------------------------------------------------------------
350 if(trim(adjustl(buffer)).eq."END "//to_upper(trim(this%name)))then
351 backspace(unit)
352 exit tag_loop
353 end if
354 iline = iline + 1
355
356 tag=trim(adjustl(buffer))
357 if(scan(buffer,"=").ne.0) tag=trim(tag(:scan(tag,"=")-1))
358
359 ! Read parameters from save file
360 !------------------------------------------------------------------------
361 select case(trim(tag))
362 case("INPUT_SHAPE")
363 call assign_vec(buffer, input_shape, itmp1)
364 case("ACTIVATION")
365 iline = iline - 1
366 backspace(unit)
367 activation = read_activation(unit, iline)
368 case default
369 !! don't look for "e" due to scientific notation of numbers
370 !! ... i.e. exponent (E+00)
371 if(scan(to_lower(trim(adjustl(buffer))),&
372 'abcdfghijklmnopqrstuvwxyz').eq.0)then
373 cycle tag_loop
374 elseif(tag(:3).eq.'END')then
375 cycle tag_loop
376 end if
377 write(err_msg,'("Unrecognised line in input file: ",A)') &
378 trim(adjustl(buffer))
379 call stop_program(err_msg)
380 return
381 end select
382 end do tag_loop
383
384
385 ! Set hyperparameters and initialise layer
386 !---------------------------------------------------------------------------
387 call this%set_hyperparams( &
388 activation = activation &
389 )
390 call this%init(input_shape = input_shape)
391
392
393 ! Check for end of layer card
394 !---------------------------------------------------------------------------
395 read(unit,'(A)') buffer
396 if(trim(adjustl(buffer)).ne."END "//to_upper(trim(this%name)))then
397 write(0,*) trim(adjustl(buffer))
398 write(err_msg,'("END ",A," not where expected")') to_upper(this%name)
399 call stop_program(err_msg)
400 return
401 end if
402
403 end subroutine read_actv
404 !###############################################################################
405
406
407 !###############################################################################
408 function read_actv_layer(unit, verbose) result(layer)
409 !! Read activation layer from file
410 implicit none
411
412 ! Arguments
413 integer, intent(in) :: unit
414 !! File unit
415 integer, optional, intent(in) :: verbose
416 !! Verbosity level
417 class(base_layer_type), allocatable :: layer
418 !! Instance of the activation layer
419
420 ! Local variables
421 integer :: verbose_ = 0
422 !! Verbosity level
423
424
425 if(present(verbose)) verbose_ = verbose
426 allocate(layer, source=actv_layer_type("none"))
427 call layer%read(unit, verbose=verbose_)
428
429 end function read_actv_layer
430 !###############################################################################
431
432
433 !###############################################################################
434 subroutine build_from_onnx_actv(this, node, initialisers, value_info, verbose )
435 !! Read ONNX attributes for activation layer
436 implicit none
437
438 ! Arguments
439 class(actv_layer_type), intent(inout) :: this
440 !! Instance of the activation layer
441 type(onnx_node_type), intent(in) :: node
442 !! ONNX node information
443 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
444 !! ONNX initialiser information
445 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
446 !! ONNX value info
447 integer, intent(in) :: verbose
448 !! Verbosity level
449
450 ! Local variables
451 integer :: verbose_ = 0
452 !! Verbosity level
453
454 end subroutine build_from_onnx_actv
455 !###############################################################################
456
457
458 !###############################################################################
459 function create_from_onnx_actv_layer(node, initialisers, value_info, verbose) &
460 result(layer)
461 !! Build activation layer from attributes and return layer
462 use coreutils, only: to_lower
463 implicit none
464
465 ! Arguments
466 type(onnx_node_type), intent(in) :: node
467 !! ONNX node information
468 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
469 !! ONNX initialiser information
470 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
471 !! ONNX value info
472 integer, optional, intent(in) :: verbose
473 !! Verbosity level
474 class(base_layer_type), allocatable :: layer
475 !! Instance of the activation layer
476
477 ! Local variables
478 integer :: verbose_ = 0
479 !! Verbosity level
480
481 if(present(verbose)) verbose_ = verbose
482 allocate(layer, source=actv_layer_type(to_lower(trim(node%op_type))))
483 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
484
485 end function create_from_onnx_actv_layer
486 !###############################################################################
487
488
489 !##############################################################################!
490 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
491 !##############################################################################!
492
493
494 !###############################################################################
495 subroutine forward_actv(this, input)
496 !! Forward propagation
497 implicit none
498
499 ! Arguments
500 class(actv_layer_type), intent(inout) :: this
501 !! Instance of the fully connected layer
502 class(array_type), dimension(:,:), intent(in) :: input
503 !! Input values
504
505 ! Local variables
506 integer :: i, s
507 !! Loop indices
508 type(array_type), pointer :: ptr
509 !! Pointer array
510
511 do s = 1, size(input, 2)
512 do i = 1, size(input, 1)
513 ptr => this%activation%apply(input(i,s))
514 call this%output(i,s)%assign_and_deallocate_source(ptr)
515 end do
516 end do
517
518 end subroutine forward_actv
519 !###############################################################################
520
521 end module athena__actv_layer
522