GCC Code Coverage Report


Directory: src/athena/
File: athena_initialiser_gaussian.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_gaussian
2 !! Module containing the Gaussian initialisation
3 !!
4 !! This module contains the implementation of the Gaussian initialisation
5 !! for the weights and biases of a layer
6 use coreutils, only: real32, pi
7 use athena__misc_types, only: base_init_type
8 implicit none
9
10
11 private
12
13 public :: gaussian_init_type
14
15
16 type, extends(base_init_type) :: gaussian_init_type
17 !! Type for the Gaussian initialiser
18 contains
19 procedure, pass(this) :: initialise => gaussian_initialise
20 !! Initialise the weights and biases using the Gaussian distribution
21 end type gaussian_init_type
22
23
24 interface gaussian_init_type
25 module function initialiser_gaussian_type(name) result(initialiser)
26 !! Interface for the Gaussian initialiser
27 type(gaussian_init_type) :: initialiser
28 !! Gaussian initialiser object
29 character(*), optional, intent(in) :: name
30 !! Name of the initialiser
31 end function initialiser_gaussian_type
32 end interface gaussian_init_type
33
34
35
36 contains
37
38 !###############################################################################
39 module function initialiser_gaussian_type(name) result(initialiser)
40 !! Interface for the Gaussian initialiser
41 implicit none
42 ! Arguments
43 character(*), optional, intent(in) :: name
44 !! Name of the initialiser
45
46
47 type(gaussian_init_type) :: initialiser
48 !! Gaussian initialiser object
49
50 if(present(name)) then
51 initialiser%name = trim(adjustl(name))
52 else
53 initialiser%name = "gaussian"
54 end if
55
56 end function initialiser_gaussian_type
57 !###############################################################################
58
59
60 !###############################################################################
61 subroutine gaussian_initialise(this, input, fan_in, fan_out, spacing)
62 !! Initialise the weights and biases using the Gaussian distribution
63 implicit none
64
65 ! Arguments
66 class(gaussian_init_type), intent(inout) :: this
67 !! Instance of the Gaussian initialiser
68 real(real32), dimension(..), intent(out) :: input
69 !! Weights and biases to initialise
70 integer, optional, intent(in) :: fan_in, fan_out
71 !! Number of input and output parameters
72 integer, dimension(:), optional, intent(in) :: spacing
73 !! Spacing of the input and output units
74
75 ! Local variables
76 integer :: n
77 !! Number of elements in the input array
78 real(real32), dimension(:), allocatable :: u1, u2, z
79 !! Temporary arrays for the random numbers
80
81 n = size(input)
82 allocate(u1(n), u2(n), z(n))
83
84 call random_number(u1)
85 call random_number(u2)
86 where (u1 .lt. 1.E-7_real32)
87 u1 = 1.E-7_real32
88 end where
89
90 ! Box-Muller transform for normal distribution
91 z = sqrt(-2._real32 * log(u1)) * cos(2._real32 * pi * u2)
92 z = this%mean + this%std * z
93
94 ! Assign according to rank
95 select rank(input)
96 rank(0)
97 input = z(1)
98 rank(1)
99 input = z
100 rank(2)
101 input = reshape(z, shape(input))
102 rank(3)
103 input = reshape(z, shape(input))
104 rank(4)
105 input = reshape(z, shape(input))
106 rank(5)
107 input = reshape(z, shape(input))
108 rank(6)
109 input = reshape(z, shape(input))
110 end select
111
112 deallocate(u1, u2, z)
113
114 end subroutine gaussian_initialise
115 !###############################################################################
116
117 end module athena__initialiser_gaussian
118