GCC Code Coverage Report


Directory: src/athena/
File: athena_activation_piecewise.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 !###############################################################################
2 module athena__activation_piecewise
3 !! Module containing implementation of the piecewise activation function
4 !! https://doi.org/10.48550/arXiv.1809.09534
5 use coreutils, only: real32, print_warning
6 use diffstruc, only: array_type, operator(*)
7 use athena__diffstruc_extd, only: piecewise
8 use athena__misc_types, only: base_actv_type
9 use athena__misc_types, only: onnx_attribute_type
10 implicit none
11
12
13 private
14
15 public :: piecewise_actv_type, create_from_onnx_piecewise_activation
16
17
18 type, extends(base_actv_type) :: piecewise_actv_type
19 !! Type for piecewise activation function with overloaded procedures
20 real(real32) :: gradient, limit
21 contains
22 procedure, pass(this) :: apply => apply_piecewise
23 procedure, pass(this) :: reset => reset_piecewise
24 procedure, pass(this) :: apply_attributes => apply_attributes_piecewise
25 procedure, pass(this) :: export_attributes => export_attributes_piecewise
26 end type piecewise_actv_type
27
28 interface piecewise_actv_type
29 procedure initialise
30 end interface piecewise_actv_type
31
32
33
34 contains
35
36 !###############################################################################
37 function initialise(scale, gradient, limit, attributes) result(activation)
38 !! Initialise a piecewise activation function
39 implicit none
40
41 ! Arguments
42 real(real32), intent(in), optional :: scale
43 !! Optional scale factor for activation output
44 real(real32), intent(in), optional :: gradient
45 !! Optional gradient parameter for piecewise function
46 real(real32), intent(in), optional :: limit
47 !! Optional limit parameter for piecewise function
48 !! -limit < x < limit
49 type(onnx_attribute_type), dimension(:), intent(in), optional :: attributes
50 !! Optional array of ONNX attributes
51 type(piecewise_actv_type) :: activation
52 !! Piecewise activation type
53
54
55 call activation%reset()
56
57 if(present(scale)) activation%scale = scale
58 if(abs(activation%scale-1._real32) .gt. 1.e-6_real32)then
59 activation%apply_scaling = .true.
60 end if
61
62 if(present(gradient)) activation%gradient = gradient
63 if(present(limit)) activation%limit = limit
64
65 if(present(attributes)) then
66 call activation%apply_attributes(attributes)
67 end if
68
69 end function initialise
70 !-------------------------------------------------------------------------------
71 pure subroutine reset_piecewise(this)
72 !! Reset piecewise activation function attributes and variables
73 implicit none
74
75 ! Arguments
76 class(piecewise_actv_type), intent(inout) :: this
77 !! Piecewise activation type
78
79 this%name = "piecewise"
80 this%scale = 1._real32
81 this%threshold = 0._real32
82 this%apply_scaling = .false.
83 this%gradient = 0.1_real32
84 this%limit = 1._real32
85
86 end subroutine reset_piecewise
87 !-------------------------------------------------------------------------------
88 function create_from_onnx_piecewise_activation(attributes) result(activation)
89 !! Create piecewise activation function from ONNX attributes
90 implicit none
91
92 ! Arguments
93 type(onnx_attribute_type), dimension(:), intent(in) :: attributes
94 !! Array of ONNX attributes
95
96 class(base_actv_type), allocatable :: activation
97 !! Instance of activation type
98
99 allocate(activation, source = piecewise_actv_type(attributes = attributes))
100
101 end function create_from_onnx_piecewise_activation
102 !###############################################################################
103
104
105 !###############################################################################
106 subroutine apply_attributes_piecewise(this, attributes)
107 !! Load ONNX attributes into piecewise activation function
108 implicit none
109
110 ! Arguments
111 class(piecewise_actv_type), intent(inout) :: this
112 !! Piecewise activation type
113 type(onnx_attribute_type), dimension(:), intent(in) :: attributes
114 !! Array of ONNX attributes
115
116 ! Local variables
117 integer :: i
118 !! Loop variable
119
120 ! Load provided attributes
121 do i=1, size(attributes,dim=1)
122 select case(trim(attributes(i)%name))
123 case("scale")
124 read(attributes(i)%val,*) this%scale
125 if(abs(this%scale-1._real32) .gt. 1.e-6_real32)then
126 this%apply_scaling = .true.
127 else
128 this%apply_scaling = .false.
129 end if
130 case("gradient")
131 read(attributes(i)%val,*) this%gradient
132 case("limit")
133 read(attributes(i)%val,*) this%limit
134 case("name")
135 if(trim(attributes(i)%val) .ne. trim(this%name)) then
136 call print_warning( &
137 'Piecewise activation: name attribute "' // &
138 trim(attributes(i)%val) // &
139 '"" does not match expected "' // trim(this%name)//'"' &
140 )
141
142 end if
143 case default
144 call print_warning( &
145 'Piecewise activation: unknown attribute '// &
146 trim(attributes(i)%name) &
147 )
148 end select
149 end do
150
151 end subroutine apply_attributes_piecewise
152 !###############################################################################
153
154
155 !###############################################################################
156 pure function export_attributes_piecewise(this) result(attributes)
157 !! Export piecewise activation function attributes as ONNX attributes
158 implicit none
159
160 ! Arguments
161 class(piecewise_actv_type), intent(in) :: this
162 !! Piecewise activation type
163 type(onnx_attribute_type), allocatable, dimension(:) :: attributes
164 !! Array of ONNX attributes
165
166 ! Local variables
167 character(50) :: buffer
168 !! Temporary string buffer
169
170 allocate(attributes(4))
171
172 write(buffer, '(A)') this%name
173 attributes(1) = onnx_attribute_type( &
174 "name", "string", trim(adjustl(buffer)) )
175
176 write(buffer, '(F10.6)') this%scale
177 attributes(2) = onnx_attribute_type( &
178 "scale", "float", trim(adjustl(buffer)) )
179
180 write(buffer, '(F10.6)') this%gradient
181 attributes(3) = onnx_attribute_type( &
182 "gradient", "float", trim(adjustl(buffer)) )
183
184 write(buffer, '(F10.6)') this%limit
185 attributes(4) = onnx_attribute_type( &
186 "limit", "float", trim(adjustl(buffer)) )
187
188 end function export_attributes_piecewise
189 !###############################################################################
190
191
192 !###############################################################################
193 function apply_piecewise(this, val) result(output)
194 !! Apply piecewise activation to 1D array
195 !!
196 !! Computes piecewise function:
197 !! f = 0 if x ≤ min
198 !! f = scale if x ≥ max
199 !! f = scale * x + intercept otherwise
200 implicit none
201
202 ! Arguments
203 class(piecewise_actv_type), intent(in) :: this
204 !! Piecewise activation type
205 type(array_type), intent(in) :: val
206 !! Input values
207 type(array_type), pointer :: output
208 !! Activated output values
209
210 if(this%apply_scaling)then
211 output => piecewise(val, this%gradient, this%limit) * this%scale
212 else
213 output => piecewise(val, this%gradient, this%limit)
214 end if
215 end function apply_piecewise
216 !###############################################################################
217
218 end module athena__activation_piecewise
219