GCC Code Coverage Report


Directory: src/athena/
File: athena_activation.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__activation
2 !! Module containing the activation function setup
3 use coreutils, only: stop_program, to_lower
4 use athena__misc_types, only: base_actv_type, onnx_attribute_type
5 use athena__activation_gaussian, only: gaussian_actv_type, &
6 create_from_onnx_gaussian_activation
7 use athena__activation_linear, only: linear_actv_type, &
8 create_from_onnx_linear_activation
9 use athena__activation_piecewise, only: piecewise_actv_type, &
10 create_from_onnx_piecewise_activation
11 use athena__activation_relu, only: relu_actv_type, &
12 create_from_onnx_relu_activation
13 use athena__activation_leaky_relu, only: leaky_relu_actv_type, &
14 create_from_onnx_leaky_relu_activation
15 use athena__activation_sigmoid, only: sigmoid_actv_type, &
16 create_from_onnx_sigmoid_activation
17 use athena__activation_softmax, only: softmax_actv_type, &
18 create_from_onnx_softmax_activation
19 use athena__activation_swish, only: swish_actv_type, &
20 create_from_onnx_swish_activation
21 use athena__activation_tanh, only: tanh_actv_type, &
22 create_from_onnx_tanh_activation
23 use athena__activation_none, only: none_actv_type, &
24 create_from_onnx_none_activation
25 use athena__activation_selu, only: selu_actv_type, &
26 create_from_onnx_selu_activation
27 implicit none
28
29
30 private
31
32 public :: activation_setup
33 public :: list_of_onnx_activation_creators
34 public :: allocate_list_of_onnx_activation_creators
35 public :: read_activation
36
37
38 type :: onnx_create_actv_container
39 !! Type containing information needed to create an activation from ONNX
40 character(20) :: name
41 !! Name of the layer
42 procedure(create_from_onnx_activation), nopass, pointer :: create_ptr => null()
43 !! Pointer to the specific activation creation function
44 end type onnx_create_actv_container
45 type(onnx_create_actv_container), dimension(:), allocatable :: &
46 list_of_onnx_activation_creators
47 !! List of activation names and their associated ONNX creation functions
48
49 interface
50 module function create_from_onnx_activation(attributes) result(activation)
51 !! Function to create an activation function from ONNX attributes
52 type(onnx_attribute_type), dimension(:), intent(in) :: attributes
53 !! Array of ONNX attributes
54 class(base_actv_type), allocatable :: activation
55 !! Resulting activation function
56 end function create_from_onnx_activation
57 end interface
58
59
60
61 contains
62
63 !###############################################################################
64 function activation_setup(input, error) result(activation)
65 !! Setup the desired activation function
66 implicit none
67
68 ! Arguments
69 class(*), intent(in) :: input
70 !! Name of the activation function or activation object
71 class(base_actv_type), allocatable :: activation
72 !! Activation function object
73 integer, optional, intent(out) :: error
74 !! Error code
75
76 ! Local variables
77 character(256) :: err_msg
78 !! Error message
79
80
81 !---------------------------------------------------------------------------
82 ! select desired activation function
83 !---------------------------------------------------------------------------
84 select type(input)
85 class is(base_actv_type)
86 activation = input
87 type is(character(*))
88 select case(trim(to_lower(input)))
89 case("gaussian")
90 activation = gaussian_actv_type()
91 case ("linear")
92 activation = linear_actv_type()
93 case ("piecewise")
94 activation = piecewise_actv_type()
95 case ("relu")
96 activation = relu_actv_type()
97 case ("leaky_relu")
98 activation = leaky_relu_actv_type()
99 case ("sigmoid")
100 activation = sigmoid_actv_type()
101 case ("softmax")
102 activation = softmax_actv_type()
103 case("swish")
104 activation = swish_actv_type()
105 case ("tanh")
106 activation = tanh_actv_type()
107 case ("none")
108 activation = none_actv_type()
109 case ("selu")
110 activation = selu_actv_type()
111 case default
112 if(present(error))then
113 error = -1
114 return
115 else
116 write(err_msg,'("Incorrect activation name given ''",A,"''")') &
117 trim(to_lower(input))
118 call stop_program(trim(err_msg))
119 write(*,*) "BB"
120 return
121 end if
122 end select
123 class default
124 if(present(error))then
125 error = -1
126 return
127 else
128 write(err_msg,'("Unknown input type given for activation setup")')
129 call stop_program(trim(err_msg))
130 return
131 end if
132 end select
133
134 end function activation_setup
135 !###############################################################################
136
137
138 !###############################################################################
139 subroutine allocate_list_of_onnx_activation_creators(addit_list)
140 !! Allocate and populate the list of ONNX activation creation functions
141 implicit none
142
143 ! Arguments
144 type(onnx_create_actv_container), dimension(:), intent(in), optional :: &
145 addit_list
146
147 if(.not.allocated(list_of_onnx_activation_creators)) &
148 allocate(list_of_onnx_activation_creators(0))
149 list_of_onnx_activation_creators = [ &
150 onnx_create_actv_container('gaussian', create_from_onnx_gaussian_activation), &
151 onnx_create_actv_container('leaky_relu', &
152 create_from_onnx_leaky_relu_activation), &
153 onnx_create_actv_container('linear', create_from_onnx_linear_activation), &
154 onnx_create_actv_container('none', create_from_onnx_none_activation), &
155 onnx_create_actv_container('piecewise', &
156 create_from_onnx_piecewise_activation), &
157 onnx_create_actv_container('relu', create_from_onnx_relu_activation), &
158 onnx_create_actv_container('selu', create_from_onnx_selu_activation), &
159 onnx_create_actv_container('sigmoid', create_from_onnx_sigmoid_activation), &
160 onnx_create_actv_container('softmax', create_from_onnx_softmax_activation), &
161 onnx_create_actv_container('swish', create_from_onnx_swish_activation), &
162 onnx_create_actv_container('tanh', create_from_onnx_tanh_activation) &
163 ]
164 if(present(addit_list))then
165 list_of_onnx_activation_creators = [ &
166 list_of_onnx_activation_creators, addit_list &
167 ]
168 end if
169
170 end subroutine allocate_list_of_onnx_activation_creators
171 !###############################################################################
172
173
174 !###############################################################################
175 function read_activation_attributes(unit, iline) result(attributes)
176 use coreutils, only: stop_program, to_lower
177 implicit none
178
179 ! Arguments
180 integer, intent(in) :: unit
181 !! Unit number for input file
182 integer, intent(inout), optional :: iline
183 !! Indicator for inline reading
184
185 type(onnx_attribute_type), allocatable, dimension(:) :: attributes
186 !! Array of ONNX attributes
187
188 ! Local variables
189 integer :: i
190 !! Loop variable
191 character(256) :: buffer
192 !! Buffer for reading lines
193 character(256) :: err_msg
194 !! Error message
195 character(20) :: attr_name
196 !! Attribute name
197 character(20) :: attr_value
198 !! Attribute value as string
199 integer :: stat
200 !! I/O status
201 integer :: eq_pos
202 !! Position of equals sign
203 integer :: n_attrs
204 !! Number of attributes
205 type(onnx_attribute_type), allocatable, dimension(:) :: temp_attrs
206 !! Temporary array for growing attributes
207 character(20), dimension(:), allocatable :: names
208 !! Array of attribute names
209 integer :: iline_
210 !! Line number
211
212
213 ! Initialise empty attributes array
214 allocate(attributes(0))
215 allocate(names(0))
216 iline_ = 0
217
218 ! Read lines until END or END ACTIVATION
219 read_loop: do
220 read(unit,'(A)',iostat=stat) buffer
221 if(stat.ne.0)then
222 write(err_msg,'("File encountered error (EoF?) before END ACTIVATION")')
223 call stop_program(err_msg)
224 return
225 end if
226 iline_ = iline_ + 1
227
228 ! Skip empty or comment lines
229 if(trim(adjustl(buffer)).eq."") cycle read_loop
230 if(index(trim(adjustl(buffer)),"#") .eq. 1) cycle read_loop
231 if(index(trim(adjustl(buffer)),"!") .eq. 1) cycle read_loop
232
233 ! Check for end of activation block
234 if(trim(adjustl(buffer)).eq."END" .or. &
235 trim(adjustl(buffer)).eq."END ACTIVATION")then
236 exit read_loop
237 end if
238
239 ! Look for NAME = VALUE pattern
240 eq_pos = scan(buffer, "=")
241
242
243 if(eq_pos .gt. 0)then
244 ! Extract name (everything before =)
245 attr_name = to_lower(adjustl(buffer(:eq_pos-1)))
246 ! Extract value (everything after =)
247 attr_value = adjustl(buffer(eq_pos+1:))
248
249
250 if(index(trim(adjustl(buffer)),"ACTIVATION") .eq. 1 .and. iline_ .eq. 1)then
251 attributes = [ onnx_attribute_type("name", "string", trim(attr_value)) ]
252 exit read_loop
253 end if
254
255 ! Check if attribute already exists
256 if(any(names .eq. attr_name))then
257 write(err_msg,'("Duplicate activation attribute name: ''",A,"''")') &
258 trim(attr_name)
259 call stop_program(trim(err_msg))
260 return
261 end if
262
263 ! Grow attributes array
264 attributes = [ &
265 attributes, &
266 onnx_attribute_type( &
267 trim(attr_name), &
268 "float", &
269 trim(attr_value) &
270 ) &
271 ]
272 names = [ names, attr_name ]
273
274 end if
275 end do read_loop
276
277 if(present(iline)) iline = iline + iline_
278
279 end function read_activation_attributes
280 !###############################################################################
281
282
283 !###############################################################################
284 function read_activation(unit, iline) result(activation)
285 !! Read activation function from input file
286 implicit none
287
288 ! Arguments
289 integer, intent(in) :: unit
290 !! Unit number for input file
291 integer, intent(inout), optional :: iline
292 !! Line number
293
294 class(base_actv_type), allocatable :: activation
295 !! Activation function object
296
297 ! Local variables
298 type(onnx_attribute_type), allocatable, dimension(:) :: attributes
299 !! Array of ONNX attributes
300 integer :: i
301 !! Loop variable
302 character(20) :: actv_name
303 !! Activation function name
304 logical :: found
305 !! Flag for finding activation creator
306 integer :: creator_index
307 !! Index of activation creator
308 integer :: iline_ = 0
309 !! Line number
310
311 ! initialise list if needed
312 if(.not.allocated(list_of_onnx_activation_creators)) &
313 call allocate_list_of_onnx_activation_creators()
314
315 ! Read activation attributes
316 attributes = read_activation_attributes(unit, iline=iline_)
317 if(present(iline)) iline = iline + iline_
318
319 ! Extract activation name
320 actv_name = ""
321 do i=1, size(attributes,dim=1)
322 if(trim(to_lower(attributes(i)%name)) .eq. "name")then
323 actv_name = trim(to_lower(attributes(i)%val))
324 exit
325 end if
326 end do
327 if(actv_name .eq. "")then
328 call stop_program( &
329 "Activation name '"// actv_name //"' not specified in activation block" &
330 )
331 return
332 end if
333 do i = 1, size(list_of_onnx_activation_creators,dim=1)
334 if(trim(to_lower(list_of_onnx_activation_creators(i)%name)) .eq. actv_name)then
335 found = .true.
336 creator_index = i
337 exit
338 end if
339 end do
340 if(.not.found)then
341 call stop_program( &
342 "Activation name '"// actv_name //"' not recognised" &
343 )
344 return
345 end if
346 allocate(activation, source = list_of_onnx_activation_creators(creator_index)% &
347 create_ptr(attributes))
348
349 end function read_activation
350 !###############################################################################
351
352 end module athena__activation
353