GCC Code Coverage Report


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