GCC Code Coverage Report


Directory: src/athena/
File: athena_base_layer_sub_io.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 submodule(athena__base_layer) athena__base_layer_submodule_io
2 !! Submodule containing the implementation of the base layer types
3 !!
4 !! This submodule contains the implementation of the base layer types
5 !! used in the ATHENA library. The base layer types are the abstract
6 !! types from which all other layer types are derived. The submodule
7 !! contains the implementation of the I/O procedures for the base layer
8 !!
9 use coreutils, only: stop_program, to_upper
10
11 contains
12
13 !###############################################################################
14 module subroutine print_base(this, file, unit, print_header_footer)
15 !! Print the layer and wrapping info to a file
16 implicit none
17
18 ! Arguments
19 class(base_layer_type), intent(in) :: this
20 !! Instance of the layer
21 character(*), optional, intent(in) :: file
22 !! File name
23 integer, optional, intent(in) :: unit
24 !! Unit number
25 logical, optional, intent(in) :: print_header_footer
26 !! Boolean whether to print header and footer
27
28 ! Local variables
29 integer :: unit_
30 !! Unit number
31 logical :: filename_provided
32 !! Boolean whether file is
33 logical :: print_header_footer_
34 !! Boolean whether to print header and footer
35
36
37 ! Open file with new unit
38 !---------------------------------------------------------------------------
39 filename_provided = .false.
40 if(present(file).and.present(unit))then
41 call stop_program("print_base: both file and unit specified")
42 elseif(present(file))then
43 filename_provided = .true.
44 open(newunit=unit_, file=trim(file), access='append')
45 elseif(present(unit))then
46 unit_ = unit
47 else
48 call stop_program("print_base: neither file nor unit specified")
49 end if
50 print_header_footer_ = .true.
51 if(present(print_header_footer)) print_header_footer_ = print_header_footer
52
53
54 ! Write card
55 !---------------------------------------------------------------------------
56 if(print_header_footer_) write(unit_,'(A)') to_upper(trim(this%name))
57 call this%print_to_unit(unit_)
58 if(print_header_footer_) write(unit_,'("END ",A)') to_upper(trim(this%name))
59
60
61 ! Close unit
62 !---------------------------------------------------------------------------
63 if(filename_provided) close(unit_)
64
65 end subroutine print_base
66 !-------------------------------------------------------------------------------
67 module subroutine print_to_unit_base(this, unit)
68 !! Print the layer to a file
69 implicit none
70
71 ! Arguments
72 class(base_layer_type), intent(in) :: this
73 !! Instance of the layer
74 integer, intent(in) :: unit
75 !! File unit
76
77 return
78 end subroutine print_to_unit_base
79 !###############################################################################
80
81
82 !###############################################################################
83 module subroutine print_to_unit_pool(this, unit)
84 !! Print pooling layer to a file
85 implicit none
86
87 ! Arguments
88 class(pool_layer_type), intent(in) :: this
89 !! Instance of the layer
90 integer, intent(in) :: unit
91 !! File unit
92
93 ! Local variables
94 character(100) :: fmt
95 !! Format string
96
97 ! Write initial parameters
98 !---------------------------------------------------------------------------
99 write(fmt,'("(3X,""INPUT_SHAPE ="",",I0,"(1X,I0))")') size(this%input_shape)
100 write(unit,fmt) this%input_shape
101 if(all(this%pool.eq.this%pool(1)))then
102 write(unit,'(3X,"POOL_SIZE =",1X,I0)') this%pool(1)
103 else
104 write(fmt,'("(3X,""STRIDE ="",",I0,"(1X,I0))")') size(this%pool)
105 write(unit,fmt) this%pool
106 end if
107 if(all(this%strd.eq.this%strd(1)))then
108 write(unit,'(3X,"STRIDE =",1X,I0)') this%strd(1)
109 else
110 write(fmt,'("(3X,""STRIDE ="",",I0,"(1X,I0))")') size(this%strd)
111 write(unit,fmt) this%strd
112 end if
113
114 end subroutine print_to_unit_pool
115 !###############################################################################
116
117
118 !###############################################################################
119 module subroutine print_to_unit_pad(this, unit)
120 !! Print padding layer to a file
121 implicit none
122
123 ! Arguments
124 class(pad_layer_type), intent(in) :: this
125 !! Instance of the layer
126 integer, intent(in) :: unit
127 !! File unit
128
129 ! Local variables
130 character(100) :: fmt
131 !! Format string
132
133 ! Write initial parameters
134 !---------------------------------------------------------------------------
135 write(fmt,'("(3X,""INPUT_SHAPE ="",",I0,"(1X,I0))")') size(this%input_shape)
136 write(unit,fmt) this%input_shape
137 write(fmt,'("(3X,""PADDING ="",",I0,"(1X,I0))")') size(this%pad)
138 write(unit,fmt) this%pad
139 write(unit,'(3X,"METHOD = ",A)') trim(this%method)
140
141 end subroutine print_to_unit_pad
142 !###############################################################################
143
144
145 !###############################################################################
146 module subroutine print_to_unit_batch(this, unit)
147 !! Print 3D batch normalisation layer to unit
148 implicit none
149
150 ! Arguments
151 class(batch_layer_type), intent(in) :: this
152 !! Instance of batch normalisation layer
153 integer, intent(in) :: unit
154 !! File unit
155
156 ! Local variables
157 integer :: m
158 !! Loop index
159 character(100) :: fmt
160 !! Format string
161
162
163 ! Write initial parameters
164 !---------------------------------------------------------------------------
165 write(fmt,'("(3X,""INPUT_SHAPE = "",",I0,"(1X,I0))")') size(this%input_shape)
166 write(unit,fmt) this%input_shape
167 write(unit,'(3X,"MOMENTUM = ",F0.9)') this%momentum
168 write(unit,'(3X,"EPSILON = ",F0.9)') this%epsilon
169 write(unit,'(3X,"NUM_CHANNELS = ",I0)') this%num_channels
170 write(unit,'(3X,"GAMMA_INITIALISER = ",A)') trim(this%kernel_init%name)
171 write(unit,'(3X,"BETA_INITIALISER = ",A)') trim(this%bias_init%name)
172 write(unit,'(3X,"MOVING_MEAN_INITIALISER = ",A)') &
173 trim(this%moving_mean_init%name)
174 write(unit,'(3X,"MOVING_VARIANCE_INITIALISER = ",A)') &
175 trim(this%moving_variance_init%name)
176 write(unit,'("GAMMA")')
177 do m = 1, this%num_channels
178 write(unit,'(5(E16.8E2))') this%params(1)%val(m,1)
179 end do
180 write(unit,'("END GAMMA")')
181 write(unit,'("BETA")')
182 do m = 1, this%num_channels
183 write(unit,'(5(E16.8E2))') this%params(1)%val(this%num_channels+m,1)
184 end do
185 write(unit,'("END BETA")')
186
187 end subroutine print_to_unit_batch
188 !###############################################################################
189
190
191 !###############################################################################
192 module subroutine print_to_unit_conv(this, unit)
193 !! Print 2D convolutional layer to unit
194 implicit none
195
196 ! Arguments
197 class(conv_layer_type), intent(in) :: this
198 !! Instance of the 2D convolutional layer
199 integer, intent(in) :: unit
200 !! File unit
201
202 ! Local variables
203 integer :: l, i, itmp1, idx
204 !! Loop indices
205 character(:), allocatable :: padding_type
206 !! Padding type
207 character(100) :: fmt
208
209
210 ! Write pad layer if applicable
211 !---------------------------------------------------------------------------
212 if(allocated(this%pad_layer))then
213 call this%pad_layer%print_to_unit(unit)
214 end if
215
216
217 ! Write initial parameters
218 !---------------------------------------------------------------------------
219 ! write the format string for input shape
220 write(fmt,'("(3X,""INPUT_SHAPE ="",",I0,"(1X,I0))")') size(this%input_shape)
221 write(unit,fmt) this%input_shape
222 write(unit,'(3X,"NUM_FILTERS = ",I0)') this%num_filters
223 write(fmt,'("(3X,A,"" ="",",I0,"(1X,I0))")') this%input_rank-1
224 if(all(this%knl.eq.this%knl(1)))then
225 write(unit,'(3X,"KERNEL_SIZE =",1X,I0)') this%knl(1)
226 else
227 write(unit,fmt) "KERNEL_SIZE", this%knl
228 end if
229 if(all(this%stp.eq.this%stp(1)))then
230 write(unit,'(3X,"STRIDE =",1X,I0)') this%stp(1)
231 else
232 write(unit,fmt) "STRIDE", this%stp
233 end if
234 if(all(this%dil.eq.this%dil(1)))then
235 write(unit,'(3X,"DILATION =",1X,I0)') this%dil(1)
236 else
237 write(unit,fmt) "DILATION", this%dil
238 end if
239
240 write(unit,'(3X,"USE_BIAS = ",L1)') this%use_bias
241 if(this%activation%name .ne. 'none')then
242 call this%activation%print_to_unit(unit)
243 end if
244
245
246 ! Write weights and biases
247 !---------------------------------------------------------------------------
248 write(unit,'("WEIGHTS")')
249 write(unit,'(5(E16.8E2))') this%params(1)%val(:,1)
250 write(unit,'(5(E16.8E2))') this%params(2)%val(:,1)
251 write(unit,'("END WEIGHTS")')
252
253 end subroutine print_to_unit_conv
254 !###############################################################################
255
256 end submodule athena__base_layer_submodule_io
257