GCC Code Coverage Report


Directory: src/athena/
File: athena_initialiser_data.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_data
2 !! Module containing the implementation of the data initialiser
3 !!
4 !! This module contains the implementation of the data initialiser
5 !! for the weights and biases of a layer
6 use coreutils, only: real32, stop_program
7 use athena__misc_types, only: base_init_type
8 implicit none
9
10
11 private
12
13 public :: data_init_type
14
15
16 type, extends(base_init_type) :: data_init_type
17 !! Type for the data initialiser
18 real(real32), dimension(:), allocatable :: data
19 !! Data to initialise the weights or biases with
20 contains
21 procedure, pass(this) :: initialise => data_initialise
22 !! Initialise the weights and biases using the data distribution
23 end type data_init_type
24
25
26 interface data_init_type
27 module function initialiser_data_setup(data) result(initialiser)
28 !! Interface for the data initialiser
29 type(data_init_type) :: initialiser
30 !! data initialiser object
31 real(real32), dimension(..), intent(in) :: data
32 !! Data to initialise the weights and biases with
33 end function initialiser_data_setup
34 end interface data_init_type
35
36
37
38 contains
39
40 !###############################################################################
41 module function initialiser_data_setup(data) result(initialiser)
42 !! Interface for the data initialiser
43 implicit none
44
45 ! Arguments
46 real(real32), dimension(..), intent(in) :: data
47 !! Data to initialise the weights and biases with
48
49 type(data_init_type) :: initialiser
50 !! data initialiser object
51
52 initialiser%name = "data"
53 allocate(initialiser%data(size(data)))
54 select rank(data)
55 rank(0)
56 initialiser%data(1) = data
57 rank(1)
58 initialiser%data(:) = data(:)
59 rank(2)
60 initialiser%data(:) = reshape(data, [size(data)])
61 rank(3)
62 initialiser%data(:) = reshape(data, [size(data)])
63 rank(4)
64 initialiser%data(:) = reshape(data, [size(data)])
65 rank(5)
66 initialiser%data(:) = reshape(data, [size(data)])
67 rank(6)
68 initialiser%data(:) = reshape(data, [size(data)])
69 rank default
70 call stop_program("initialiser_data_setup: Unsupported rank of data array")
71 end select
72
73 end function initialiser_data_setup
74 !###############################################################################
75
76
77 !###############################################################################
78 pure subroutine data_initialise(this, input, fan_in, fan_out, spacing)
79 !! Initialise the weights and biases using the data distribution
80 implicit none
81
82 ! Arguments
83 class(data_init_type), intent(inout) :: this
84 !! Instance of the data initialiser
85 real(real32), dimension(..), intent(out) :: input
86 !! Weights and biases to initialise
87 integer, optional, intent(in) :: fan_in, fan_out
88 !! Number of input and output parameters
89 integer, dimension(:), optional, intent(in) :: spacing
90 !! Spacing of the input and output units
91
92 select rank(input)
93 rank(0)
94 input = this%data(1)
95 rank(1)
96 input(:) = this%data(:)
97 rank(2)
98 input(:,:) = reshape(this%data, shape(input))
99 rank(3)
100 input(:,:,:) = reshape(this%data, shape(input))
101 rank(4)
102 input(:,:,:,:) = reshape(this%data, shape(input))
103 rank(5)
104 input(:,:,:,:,:) = reshape(this%data, shape(input))
105 rank(6)
106 input(:,:,:,:,:,:) = reshape(this%data, shape(input))
107 end select
108
109 end subroutine data_initialise
110 !###############################################################################
111
112 end module athena__initialiser_data
113