GCC Code Coverage Report


Directory: src/athena/
File: athena_lr_decay.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__learning_rate_decay
2 !! Module containing learning decay rate types and procedures
3 use coreutils, only: real32
4 implicit none
5
6
7 private
8
9 public :: base_lr_decay_type
10 public :: exp_lr_decay_type
11 public :: step_lr_decay_type
12 public :: inv_lr_decay_type
13
14
15 !-------------------------------------------------------------------------------
16
17 type base_lr_decay_type
18 !! Type for learning rate decay
19 character(len=20) :: name
20 !! Name of the learning rate decay type
21 real(real32) :: initial_learning_rate
22 !! Initial learning rate
23 real(real32) :: decay_rate
24 !! Decay rate for learning rate
25 logical :: iterate_per_epoch = .false.
26 !! Whether to iterate learning rate decay per epoch
27 contains
28 procedure :: get_lr => lr_decay_none
29 !! Procedure to get the learning rate
30 end type base_lr_decay_type
31
32 interface base_lr_decay_type
33 !! Interface for base learning rate decay type
34 module function setup_lr_decay_base() result(lr_decay)
35 !! Set up base learning rate decay type
36 type(base_lr_decay_type) :: lr_decay
37 !! Base learning rate decay type
38 end function setup_lr_decay_base
39 end interface base_lr_decay_type
40
41 !-------------------------------------------------------------------------------
42
43 type, extends(base_lr_decay_type) :: exp_lr_decay_type
44 !! Type for exponential learning rate decay
45 contains
46 procedure :: get_lr => lr_decay_exp
47 !! Procedure to get the learning rate
48 end type exp_lr_decay_type
49
50 interface exp_lr_decay_type
51 !! Interface for exponential learning rate decay type
52 module function setup_lr_decay_exp(decay_rate) result(lr_decay)
53 !! Set up exponential learning rate decay type
54 real(real32), optional, intent(in) :: decay_rate
55 !! Decay rate for learning rate
56 type(exp_lr_decay_type) :: lr_decay
57 !! Exponential learning rate decay type
58 end function setup_lr_decay_exp
59 end interface exp_lr_decay_type
60
61 !-------------------------------------------------------------------------------
62
63 type, extends(base_lr_decay_type) :: step_lr_decay_type
64 !! Type for step learning rate decay
65 integer :: decay_steps
66 !! Number of steps for learning rate decay
67 contains
68 procedure :: get_lr => lr_decay_step
69 !! Procedure to get the learning rate
70 end type step_lr_decay_type
71
72 interface step_lr_decay_type
73 !! Interface for step learning rate decay type
74 module function setup_lr_decay_step(decay_rate, decay_steps) &
75 result(lr_decay)
76 !! Set up step learning rate decay type
77 real(real32), optional, intent(in) :: decay_rate
78 !! Decay rate for learning rate
79 integer, optional, intent(in) :: decay_steps
80 !! Number of steps for learning rate decay
81 type(step_lr_decay_type) :: lr_decay
82 !! Step learning rate decay type
83 end function setup_lr_decay_step
84 end interface step_lr_decay_type
85
86 !-------------------------------------------------------------------------------
87
88 type, extends(base_lr_decay_type) :: inv_lr_decay_type
89 !! Type for inverse learning rate decay
90 real(real32) :: decay_power
91 !! Power for learning rate decay
92 contains
93 procedure :: get_lr => lr_decay_inv
94 !! Procedure to get the learning rate
95 end type inv_lr_decay_type
96
97 interface inv_lr_decay_type
98 !! Interface for inverse learning rate decay type
99 module function setup_lr_decay_inv(decay_rate, decay_power) &
100 result(lr_decay)
101 !! Set up inverse learning rate decay type
102 real(real32), optional, intent(in) :: decay_rate, decay_power
103 !! Decay rate for learning rate
104 type(inv_lr_decay_type) :: lr_decay
105 !! Inverse learning rate decay type
106 end function setup_lr_decay_inv
107 end interface inv_lr_decay_type
108
109
110
111 contains
112
113 !###############################################################################
114 module function setup_lr_decay_base() result(lr_decay)
115 !! Set up base learning rate decay type
116 implicit none
117
118 ! Output variable
119 type(base_lr_decay_type) :: lr_decay
120 !! Instance of the base learning rate decay type
121
122 lr_decay%name = "base"
123 lr_decay%decay_rate = 0._real32
124
125 end function setup_lr_decay_base
126 !-------------------------------------------------------------------------------
127 module function setup_lr_decay_exp(decay_rate) result(lr_decay)
128 !! Set up exponential learning rate decay type
129 implicit none
130
131 ! Arguments
132 real(real32), optional, intent(in) :: decay_rate
133 !! Decay rate for learning rate
134 type(exp_lr_decay_type) :: lr_decay
135 !! Exponential learning rate decay type
136
137 lr_decay%name = "exp"
138 if(present(decay_rate))then
139 lr_decay%decay_rate = decay_rate
140 else
141 lr_decay%decay_rate = 0.9_real32
142 end if
143
144 end function setup_lr_decay_exp
145 !-------------------------------------------------------------------------------
146 module function setup_lr_decay_step(decay_rate, decay_steps) result(lr_decay)
147 !! Set up step learning rate decay type
148 implicit none
149
150 ! Arguments
151 real(real32), optional, intent(in) :: decay_rate
152 !! Decay rate for learning rate
153 integer, optional, intent(in) :: decay_steps
154 !! Number of steps for learning rate decay
155 type(step_lr_decay_type) :: lr_decay
156 !! Step learning rate decay type
157
158 lr_decay%name = "step"
159 if(present(decay_rate))then
160 lr_decay%decay_rate = decay_rate
161 else
162 lr_decay%decay_rate = 0.1_real32
163 end if
164 if(present(decay_steps))then
165 lr_decay%decay_steps = decay_steps
166 else
167 lr_decay%decay_steps = 100
168 end if
169 lr_decay%iterate_per_epoch = .true.
170
171 end function setup_lr_decay_step
172 !-------------------------------------------------------------------------------
173 module function setup_lr_decay_inv(decay_rate, decay_power) result(lr_decay)
174 !! Set up inverse learning rate decay type
175 implicit none
176
177 ! Arguments
178 real(real32), optional, intent(in) :: decay_rate, decay_power
179 !! Decay rate for learning rate
180 type(inv_lr_decay_type) :: lr_decay
181 !! Inverse learning rate decay type
182
183 lr_decay%name = "inv"
184 if(present(decay_rate))then
185 lr_decay%decay_rate = decay_rate
186 else
187 lr_decay%decay_rate = 0.001_real32
188 end if
189 if(present(decay_power))then
190 lr_decay%decay_power = decay_power
191 else
192 lr_decay%decay_power = 1._real32
193 end if
194
195 end function setup_lr_decay_inv
196 !###############################################################################
197
198
199 !###############################################################################
200 pure function lr_decay_none(this, learning_rate, iteration) result(output)
201 !! Get the learning rate for the base decay type
202 implicit none
203
204 ! Arguments
205 class(base_lr_decay_type), intent(in) :: this
206 !! Instance of the base learning rate decay type
207 real(real32), intent(in) :: learning_rate
208 !! Initial learning rate
209 integer, intent(in) :: iteration
210 !! Iteration number
211 real(real32) :: output
212 !! Learning rate
213
214 output = learning_rate
215
216 end function lr_decay_none
217 !-------------------------------------------------------------------------------
218 pure function lr_decay_exp(this, learning_rate, iteration) result(output)
219 !! Get the learning rate for the exponential decay type
220 implicit none
221
222 ! Arguments
223 class(exp_lr_decay_type), intent(in) :: this
224 !! Instance of the exponential learning rate decay type
225 real(real32), intent(in) :: learning_rate
226 !! Initial learning rate
227 integer, intent(in) :: iteration
228 !! Iteration number
229 real(real32) :: output
230 !! Learning rate
231
232 output = learning_rate * exp(- iteration * this%decay_rate)
233
234 end function lr_decay_exp
235 !-------------------------------------------------------------------------------
236 pure function lr_decay_step(this, learning_rate, iteration) result(output)
237 !! Get the learning rate for the step decay type
238 implicit none
239
240 ! Arguments
241 class(step_lr_decay_type), intent(in) :: this
242 !! Instance of the step learning rate decay type
243 real(real32), intent(in) :: learning_rate
244 !! Initial learning rate
245 integer, intent(in) :: iteration
246 !! Iteration number
247 real(real32) :: output
248 !! Learning rate
249
250 output = learning_rate * this%decay_rate ** (iteration / this%decay_steps)
251
252 end function lr_decay_step
253 !-------------------------------------------------------------------------------
254 pure function lr_decay_inv(this, learning_rate, iteration) result(output)
255 !! Get the learning rate for the inverse decay type
256 implicit none
257
258 ! Arguments
259 class(inv_lr_decay_type), intent(in) :: this
260 !! Instance of the inverse learning rate decay type
261 real(real32), intent(in) :: learning_rate
262 !! Initial learning rate
263 integer, intent(in) :: iteration
264 !! Iteration number
265 real(real32) :: output
266 !! Learning rate
267
268 output = learning_rate * &
269 (1._real32 + this%decay_rate * iteration) ** (- this%decay_power)
270
271 end function lr_decay_inv
272 !###############################################################################
273
274 end module athena__learning_rate_decay
275