GCC Code Coverage Report


Directory: src/athena/
File: athena_initialiser_lecun.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__initialiser_lecun
2 !! Module containing the implementation of the LeCun initialiser
3 !!
4 !! This module implements LeCun initialisation, the precursor to modern
5 !! initialisation schemes, designed for efficient backpropagation.
6 !!
7 !! Mathematical operation:
8 !! Uniform variant: W ~ U(-limit, limit)
9 !! where limit = sqrt(3 / fan_in)
10 !! Normal variant: W ~ N(0, σ²)
11 !! where σ = sqrt(1 / fan_in)
12 !!
13 !! fan_in is the number of input units to the layer.
14 !!
15 !! Rationale: Maintains variance of inputs through layers
16 !! Helps prevent saturation of activation functions
17 !!
18 !! Best for: SELU activation (with lecun_normal variant)
19 !! Also works with: Tanh, Sigmoid
20 !! Reference: LeCun et al. (1998), Neural Networks: Tricks of the Trade
21 use coreutils, only: real32, pi, stop_program
22 use athena__misc_types, only: base_init_type
23 implicit none
24
25
26 private
27
28 public :: lecun_uniform_init_type
29 public :: lecun_normal_init_type
30
31
32 type, extends(base_init_type) :: lecun_uniform_init_type
33 !! Type for the LeCun initialiser (uniform)
34 contains
35 procedure, pass(this) :: initialise => lecun_uniform_initialise
36 !! Initialise the weights and biases using the LeCun uniform distribution
37 end type lecun_uniform_init_type
38 type, extends(base_init_type) :: lecun_normal_init_type
39 !! Type for the LeCun initialiser (normal)
40 contains
41 procedure, pass(this) :: initialise => lecun_normal_initialise
42 !! Initialise the weights and biases using the LeCun normal distribution
43 end type lecun_normal_init_type
44
45
46 interface lecun_uniform_init_type
47 module function initialiser_lecun_uniform_setup() result(initialiser)
48 !! Interface for the LeCun uniform initialiser
49 type(lecun_uniform_init_type) :: initialiser
50 !! LeCun uniform initialiser object
51 end function initialiser_lecun_uniform_setup
52 end interface lecun_uniform_init_type
53
54 interface lecun_normal_init_type
55 module function initialiser_lecun_normal_setup() result(initialiser)
56 !! Interface for the LeCun normal initialiser
57 type(lecun_normal_init_type) :: initialiser
58 !! LeCun normal initialiser object
59 end function initialiser_lecun_normal_setup
60 end interface lecun_normal_init_type
61
62
63
64 contains
65
66 !###############################################################################
67 module function initialiser_lecun_uniform_setup() result(initialiser)
68 !! Interface for the LeCun uniform initialiser
69 implicit none
70
71 type(lecun_uniform_init_type) :: initialiser
72 !! LeCun uniform initialiser object
73
74 initialiser%name = "lecun_uniform"
75
76 end function initialiser_lecun_uniform_setup
77 !-------------------------------------------------------------------------------
78 module function initialiser_lecun_normal_setup() result(initialiser)
79 !! Interface for the LeCun normal initialiser
80 implicit none
81
82 type(lecun_normal_init_type) :: initialiser
83 !! LeCun normal initialiser object
84
85 initialiser%name = "lecun_normal"
86
87 end function initialiser_lecun_normal_setup
88 !###############################################################################
89
90
91 !###############################################################################
92 subroutine lecun_uniform_initialise(this, input, fan_in, fan_out, spacing)
93 !! Initialise the weights and biases using the LeCun uniform distribution
94 implicit none
95
96 ! Arguments
97 class(lecun_uniform_init_type), intent(inout) :: this
98 !! Instance of the Glorot initialiser
99 real(real32), dimension(..), intent(out) :: input
100 !! Weights and biases to initialise
101 integer, optional, intent(in) :: fan_in, fan_out
102 !! Number of input and output units
103 integer, dimension(:), optional, intent(in) :: spacing
104 !! Spacing of the input and output units (not used)
105
106 ! Local variables
107 integer :: n
108 !! Number of elements in the input array
109 real(real32) :: limit
110 !! Scaling factor
111 real(real32), dimension(:), allocatable :: r
112 !! Temporary uniform random numbers
113
114 if(.not.present(fan_in)) &
115 call stop_program("lecun_uniform_initialise: fan_in not present")
116
117 limit = sqrt(3._real32 / real(fan_in, real32))
118 n = size(input)
119 allocate(r(n))
120 call random_number(r)
121 r = (2._real32 * r - 1._real32) * limit
122
123 ! Assign according to rank
124 select rank(input)
125 rank(0)
126 input = r(1)
127 rank(1)
128 input = r
129 rank(2)
130 input = reshape(r, shape(input))
131 rank(3)
132 input = reshape(r, shape(input))
133 rank(4)
134 input = reshape(r, shape(input))
135 rank(5)
136 input = reshape(r, shape(input))
137 rank(6)
138 input = reshape(r, shape(input))
139 end select
140
141 deallocate(r)
142 end subroutine lecun_uniform_initialise
143 !###############################################################################
144
145
146 !###############################################################################
147 subroutine lecun_normal_initialise(this, input, fan_in, fan_out, spacing)
148 !! Initialise the weights and biases using the LeCun normal distribution
149 implicit none
150
151 ! Arguments
152 class(lecun_normal_init_type), intent(inout) :: this
153 !! Instance of the LeCun initialiser
154 real(real32), dimension(..), intent(out) :: input
155 !! Weights and biases to initialise
156 integer, optional, intent(in) :: fan_in, fan_out
157 !! Number of input and output parameters
158 integer, dimension(:), optional, intent(in) :: spacing
159 !! Spacing of the input and output units (not used)
160
161 ! Local variables
162 integer :: n
163 !! Number of elements in the input array
164 real(real32) :: sigma
165 !! Scaling factor
166 real(real32), dimension(:), allocatable :: u1, u2, z
167 !! Temporary arrays for the random numbers
168
169 if(.not.present(fan_in)) &
170 call stop_program("lecun_normal_initialise: fan_in not present")
171
172 sigma = sqrt(1._real32/real(fan_in,real32))
173 n = size(input)
174 allocate(u1(n), u2(n), z(n))
175
176 call random_number(u1)
177 call random_number(u2)
178 where (u1 .lt. 1.E-7_real32)
179 u1 = 1.E-7_real32
180 end where
181
182 ! Box-Muller transform
183 z = sqrt(-2._real32 * log(u1)) * cos(2._real32 * pi * u2)
184 z = sigma * z
185
186 select rank(input)
187 rank(0)
188 input = z(1)
189 rank(1)
190 input = z
191 rank(2)
192 input = reshape(z, shape(input))
193 rank(3)
194 input = reshape(z, shape(input))
195 rank(4)
196 input = reshape(z, shape(input))
197 rank(5)
198 input = reshape(z, shape(input))
199 rank(6)
200 input = reshape(z, shape(input))
201 end select
202
203 deallocate(u1, u2, z)
204
205 end subroutine lecun_normal_initialise
206 !###############################################################################
207
208 end module athena__initialiser_lecun
209