GCC Code Coverage Report


Directory: src/athena/
File: athena_activation_sigmoid.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_sigmoid
2 !! Module containing implementation of the sigmoid activation function
3 !!
4 !! This module implements the logistic sigmoid function that squashes
5 !! inputs to the range (0, 1), commonly used for binary classification.
6 !!
7 !! Mathematical operation:
8 !! \[ \sigma(x) = \frac{1}{1 + e^{-x}} = \frac{e^x}{e^x + 1} \]
9 !!
10 !! Derivative:
11 !! \[ \sigma'(x) = \sigma(x)(1 - \sigma(x)) \]
12 !!
13 !! Properties: Smooth, bounded \([0,1]\), saturates for large \(|x|\)
14 !! Output interpretation: Can be viewed as probability for binary events
15 use coreutils, only: real32, print_warning
16 use diffstruc, only: array_type, operator(+), operator(-), &
17 operator(*), operator(/), exp, merge, operator(.gt.), sigmoid
18 use athena__misc_types, only: base_actv_type
19 use athena__misc_types, only: onnx_attribute_type
20 implicit none
21
22
23 private
24
25 public :: sigmoid_actv_type, create_from_onnx_sigmoid_activation
26
27
28 type, extends(base_actv_type) :: sigmoid_actv_type
29 !! Type for sigmoid activation function with overloaded procedures
30 contains
31 procedure, pass(this) :: apply => apply_sigmoid
32 procedure, pass(this) :: reset => reset_sigmoid
33 procedure, pass(this) :: apply_attributes => apply_attributes_sigmoid
34 procedure, pass(this) :: export_attributes => export_attributes_sigmoid
35 end type sigmoid_actv_type
36
37 interface sigmoid_actv_type
38 procedure initialise
39 end interface sigmoid_actv_type
40
41
42
43 contains
44
45 !###############################################################################
46 function initialise(scale, attributes) result(activation)
47 !! Initialise a sigmoid activation function
48 implicit none
49
50 ! Arguments
51 real(real32), intent(in), optional :: scale
52 !! Optional scale factor for activation output
53 type(onnx_attribute_type), dimension(:), intent(in), optional :: attributes
54 !! Optional array of ONNX attributes
55 type(sigmoid_actv_type) :: activation
56 !! Sigmoid activation type
57
58
59 call activation%reset()
60
61 if(present(scale)) activation%scale = scale
62 if(abs(activation%scale-1._real32) .gt. 1.e-6_real32)then
63 activation%apply_scaling = .true.
64 end if
65
66 if(present(attributes)) then
67 call activation%apply_attributes(attributes)
68 end if
69
70 end function initialise
71 !-------------------------------------------------------------------------------
72 pure subroutine reset_sigmoid(this)
73 !! Reset sigmoid activation function attributes and variables
74 implicit none
75
76 ! Arguments
77 class(sigmoid_actv_type), intent(inout) :: this
78 !! Sigmoid activation type
79
80 this%name = "sigmoid"
81 this%scale = 1._real32
82 this%threshold = 0._real32
83 this%apply_scaling = .false.
84
85 end subroutine reset_sigmoid
86 !-------------------------------------------------------------------------------
87 function create_from_onnx_sigmoid_activation(attributes) result(activation)
88 !! Create sigmoid activation function from ONNX attributes
89 implicit none
90
91 ! Arguments
92 type(onnx_attribute_type), dimension(:), intent(in) :: attributes
93 !! Array of ONNX attributes
94
95 class(base_actv_type), allocatable :: activation
96 !! Instance of activation type
97
98 allocate(activation, source = sigmoid_actv_type(attributes = attributes))
99
100 end function create_from_onnx_sigmoid_activation
101 !###############################################################################
102
103
104 !###############################################################################
105 subroutine apply_attributes_sigmoid(this, attributes)
106 !! Load ONNX attributes into sigmoid activation function
107 implicit none
108
109 ! Arguments
110 class(sigmoid_actv_type), intent(inout) :: this
111 !! Sigmoid activation type
112 type(onnx_attribute_type), dimension(:), intent(in) :: attributes
113 !! Array of ONNX attributes
114
115 ! Local variables
116 integer :: i
117 !! Loop variable
118
119 ! Load provided attributes
120 do i=1, size(attributes,dim=1)
121 select case(trim(attributes(i)%name))
122 case("scale")
123 read(attributes(i)%val,*) this%scale
124 if(abs(this%scale-1._real32) .gt. 1.e-6_real32)then
125 this%apply_scaling = .true.
126 else
127 this%apply_scaling = .false.
128 end if
129 case("name")
130 if(trim(attributes(i)%val) .ne. trim(this%name)) then
131 call print_warning( &
132 'Sigmoid activation: name attribute "' // &
133 trim(attributes(i)%val) // &
134 '"" does not match expected "' // trim(this%name)//'"' &
135 )
136
137 end if
138 case default
139 call print_warning( &
140 'Sigmoid activation: unknown attribute "' // &
141 trim(attributes(i)%name) // '"' &
142 )
143 end select
144 end do
145
146 end subroutine apply_attributes_sigmoid
147 !###############################################################################
148
149
150 !###############################################################################
151 pure function export_attributes_sigmoid(this) result(attributes)
152 !! Export sigmoid activation function attributes as ONNX attributes
153 implicit none
154
155 ! Arguments
156 class(sigmoid_actv_type), intent(in) :: this
157 !! Sigmoid activation type
158 type(onnx_attribute_type), allocatable, dimension(:) :: attributes
159 !! Array of ONNX attributes
160
161 ! Local variables
162 character(50) :: buffer
163 !! Temporary string buffer
164
165 allocate(attributes(2))
166 write(buffer, '(A)') this%name
167 attributes(1) = onnx_attribute_type( &
168 "name", "string", trim(adjustl(buffer)) )
169
170 write(buffer, '(F10.6)') this%scale
171 attributes(2) = onnx_attribute_type( &
172 "scale", "float", trim(adjustl(buffer)) )
173
174 end function export_attributes_sigmoid
175 !###############################################################################
176
177
178 !###############################################################################
179 function apply_sigmoid(this, val) result(output)
180 !! Apply sigmoid activation to 1D array
181 !!
182 !! Computes: f = 1/(1+exp(-x))
183 implicit none
184
185 ! Arguments
186 class(sigmoid_actv_type), intent(in) :: this
187 !! Sigmoid activation type
188 type(array_type), intent(in) :: val
189 !! Input values
190 type(array_type), pointer :: output
191 !! Activated output values in range [0,1]
192
193 if(this%apply_scaling)then
194 output => sigmoid(val) * this%scale
195 else
196 output => sigmoid(val)
197 end if
198 end function apply_sigmoid
199 !###############################################################################
200
201 end module athena__activation_sigmoid
202