GCC Code Coverage Report


Directory: src/athena/
File: athena_pad2d_layer.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__pad2d_layer
2 !! Module containing implementation of a 2D padding layer
3 !!
4 !! This module implements padding for 2D spatial data (images), adding values
5 !! around borders to control output dimensions or prepare for convolution.
6 !!
7 !! Operation: Extends spatial dimensions at boundaries
8 !! Adds p_top, p_bottom rows and p_left, p_right columns
9 !!
10 !! Padding modes:
11 !! - 'constant': pad with fixed value (typically 0)
12 !! - 'replicate': repeat edge values
13 !! - 'reflect': mirror values at boundaries
14 !!
15 !! Common use: Preserve spatial dimensions through convolution,
16 !! handle boundary effects in CNNs
17 !! Shape: (W,H,C) -> (W+p_l+p_r, H+p_t+p_b, C)
18 use coreutils, only: real32, stop_program
19 use athena__base_layer, only: pad_layer_type, base_layer_type
20 use diffstruc, only: array_type
21 use athena__diffstruc_extd, only: pad2d
22 use athena__misc_types, only: &
23 onnx_node_type, onnx_initialiser_type, onnx_tensor_type
24 implicit none
25
26
27 private
28
29 public :: pad2d_layer_type
30 public :: read_pad2d_layer
31
32
33 type, extends(pad_layer_type) :: pad2d_layer_type
34 !! Type for 2D padding layer with overloaded procedures
35 contains
36 procedure, pass(this) :: set_hyperparams => set_hyperparams_pad2d
37 !! Set hyperparameters for 2D padding layer
38 procedure, pass(this) :: read => read_pad2d
39 !! Read 2D padding layer from file
40
41 procedure, pass(this) :: forward => forward_pad2d
42 !! Forward propagation derived type handler
43
44 end type pad2d_layer_type
45
46 interface pad2d_layer_type
47 !! Interface for setting up the 2D padding layer
48 module function layer_setup( &
49 padding, method, &
50 input_shape, &
51 verbose &
52 ) result(layer)
53 !! Set up the 2D padding layer
54 integer, dimension(:), intent(in) :: padding
55 !! Padding sizes
56 character(*), intent(in) :: method
57 !! Padding method
58 integer, dimension(:), optional, intent(in) :: input_shape
59 !! Input shape
60 integer, optional, intent(in) :: verbose
61 !! Verbosity level
62 type(pad2d_layer_type) :: layer
63 !! Instance of the 2D padding layer
64 end function layer_setup
65 end interface pad2d_layer_type
66
67
68
69 contains
70
71 !###############################################################################
72 module function layer_setup( &
73 padding, method, &
74 input_shape, &
75 verbose) result(layer)
76 !! Set up the 2D padding layer
77 implicit none
78
79 ! Arguments
80 integer, dimension(:), intent(in) :: padding
81 !! Padding sizes
82 character(*), intent(in) :: method
83 !! Padding method
84 integer, dimension(:), optional, intent(in) :: input_shape
85 !! Input shape
86 integer, optional, intent(in) :: verbose
87 !! Verbosity level
88
89 type(pad2d_layer_type) :: layer
90 !! Instance of the 2D padding layer
91
92 ! Local variables
93 integer :: verbose_ = 0
94 !! Verbosity level
95 integer, dimension(2) :: padding_2d
96 !! 2D padding sizes
97
98 if(present(verbose)) verbose_ = verbose
99
100 !---------------------------------------------------------------------------
101 ! Initialise padding sizes
102 !---------------------------------------------------------------------------
103 select case(size(padding))
104 case(1)
105 padding_2d = [padding(1), padding(1)]
106 case(2)
107 padding_2d = padding
108 case default
109 call stop_program("Invalid padding size")
110 end select
111
112
113 !---------------------------------------------------------------------------
114 ! Set hyperparameters
115 !---------------------------------------------------------------------------
116 call layer%set_hyperparams(padding=padding_2d, method=method, verbose=verbose_)
117
118
119 !---------------------------------------------------------------------------
120 ! Initialise layer shape
121 !---------------------------------------------------------------------------
122 if(present(input_shape)) call layer%init(input_shape=input_shape)
123
124 end function layer_setup
125 !###############################################################################
126
127
128 !###############################################################################
129 subroutine set_hyperparams_pad2d(this, padding, method, verbose)
130 !! Set hyperparameters for 2D padding layer
131 use coreutils, only: to_lower
132 implicit none
133
134 ! Arguments
135 class(pad2d_layer_type), intent(inout) :: this
136 !! Instance of the 2D padding layer
137 integer, dimension(2), intent(in) :: padding
138 !! Padding sizes
139 character(*), intent(in) :: method
140 !! Padding method
141 integer, optional, intent(in) :: verbose
142 !! Verbosity level
143
144 this%name = "pad2d"
145 this%type = "pad"
146 this%input_rank = 3
147 this%output_rank = 3
148 this%pad = padding
149 if(allocated(this%facets)) deallocate(this%facets)
150 allocate(this%facets(this%input_rank - 1))
151 this%facets(1)%rank = 2
152 this%facets(1)%nfixed_dims = 1
153 this%facets(2)%rank = 2
154 this%facets(2)%nfixed_dims = 2
155 select case(trim(adjustl(to_lower(method))))
156 case("valid", "none")
157 this%imethod = 0
158 case("same", "zero", "constant", "const")
159 this%imethod = 1
160 case("full")
161 this%imethod = 2
162 case("circular", "circ")
163 this%imethod = 3
164 case("reflection", "reflect", "refl")
165 this%imethod = 4
166 case("replication", "replicate", "copy", "repl")
167 this%imethod = 5
168 case default
169 call stop_program("Unrecognised padding method :"//method)
170 return
171 end select
172 this%method = trim(adjustl(to_lower(method)))
173
174 end subroutine set_hyperparams_pad2d
175 !###############################################################################
176
177
178 !##############################################################################!
179 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
180 !##############################################################################!
181
182
183 !###############################################################################
184 subroutine read_pad2d(this, unit, verbose)
185 !! Read 2D padding layer from file
186 use athena__tools_infile, only: assign_val, assign_vec
187 use coreutils, only: to_lower, to_upper, icount
188 implicit none
189
190 ! Arguments
191 class(pad2d_layer_type), intent(inout) :: this
192 !! Instance of the 2D padding layer
193 integer, intent(in) :: unit
194 !! File unit
195 integer, optional, intent(in) :: verbose
196 !! Verbosity level
197
198 ! Local variables
199 integer :: verbose_ = 0
200 !! Verbosity level
201 integer :: stat
202 !! File status
203 integer :: itmp1
204 !! Temporary integer
205 integer, dimension(2) :: padding
206 !! Padding sizes
207 integer, dimension(3) :: input_shape
208 !! Input shape
209 character(20) :: method
210 !! Padding method
211 character(256) :: buffer, tag, err_msg
212 !! Buffer for reading lines, tag for identifying lines, error message
213
214
215 ! Initialise optional arguments
216 !---------------------------------------------------------------------------
217 if(present(verbose)) verbose_ = verbose
218
219
220 ! Loop over tags in layer card
221 !---------------------------------------------------------------------------
222 tag_loop: do
223
224 ! Check for end of file
225 !------------------------------------------------------------------------
226 read(unit,'(A)',iostat=stat) buffer
227 if(stat.ne.0)then
228 write(err_msg,'("file encountered error (EoF?) before END ",A)') &
229 to_upper(this%name)
230 call stop_program(err_msg)
231 return
232 end if
233 if(trim(adjustl(buffer)).eq."") cycle tag_loop
234
235 ! Check for end of layer card
236 !------------------------------------------------------------------------
237 if(trim(adjustl(buffer)).eq."END "//to_upper(trim(this%name)))then
238 backspace(unit)
239 exit tag_loop
240 end if
241
242 tag=trim(adjustl(buffer))
243 if(scan(buffer,"=").ne.0) tag=trim(tag(:scan(tag,"=")-1))
244
245 ! Read parameters from save file
246 !------------------------------------------------------------------------
247 select case(trim(tag))
248 case("INPUT_SHAPE")
249 call assign_vec(buffer, input_shape, itmp1)
250 case("PADDING")
251 call assign_vec(buffer, padding, itmp1)
252 case("METHOD")
253 call assign_val(buffer, method, itmp1)
254 case default
255 ! Don't look for "e" due to scientific notation of numbers
256 ! ... i.e. exponent (E+00)
257 if(scan(to_lower(trim(adjustl(buffer))),&
258 'abcdfghijklmnopqrstuvwxyz').eq.0)then
259 cycle tag_loop
260 elseif(tag(:3).eq.'END')then
261 cycle tag_loop
262 end if
263 write(err_msg,'("Unrecognised line in input file: ",A)') &
264 trim(adjustl(buffer))
265 call stop_program(err_msg)
266 return
267 end select
268 end do tag_loop
269
270
271 ! Set hyperparameters and initialise layer
272 !---------------------------------------------------------------------------
273 call this%set_hyperparams(padding=padding, method=method, verbose=verbose_)
274 call this%init(input_shape = input_shape)
275
276
277 ! Check for end of layer card
278 !---------------------------------------------------------------------------
279 read(unit,'(A)') buffer
280 if(trim(adjustl(buffer)).ne."END "//to_upper(trim(this%name)))then
281 write(0,*) trim(adjustl(buffer))
282 write(err_msg,'("END ",A," not where expected")') to_upper(this%name)
283 call stop_program(err_msg)
284 return
285 end if
286
287 end subroutine read_pad2d
288 !###############################################################################
289
290
291 !###############################################################################
292 function read_pad2d_layer(unit, verbose) result(layer)
293 !! Read 2D padding layer from file and return layer
294 implicit none
295
296 ! Arguments
297 integer, intent(in) :: unit
298 !! File unit
299 integer, optional, intent(in) :: verbose
300 !! Verbosity level
301 class(base_layer_type), allocatable :: layer
302 !! Instance of the 2D padding layer
303
304 ! Local variables
305 integer :: verbose_ = 0
306 !! Verbosity level
307
308 if(present(verbose)) verbose_ = verbose
309 allocate(layer, source=pad2d_layer_type(padding=[0,0], method="none"))
310 call layer%read(unit, verbose=verbose_)
311
312 end function read_pad2d_layer
313 !###############################################################################
314
315
316 !###############################################################################
317 subroutine build_from_onnx_pad2d( &
318 this, node, initialisers, value_info, verbose &
319 )
320 !! Read ONNX attributes for 2D padding layer
321 implicit none
322
323 ! Arguments
324 class(pad2d_layer_type), intent(inout) :: this
325 !! Instance of the 2D padding layer
326 type(onnx_node_type), intent(in) :: node
327 !! ONNX node information
328 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
329 !! ONNX initialiser information
330 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
331 !! ONNX value info
332 integer, intent(in) :: verbose
333 !! Verbosity level
334
335 ! Local variables
336 integer :: i
337 !! Loop index
338 integer, dimension(2) :: padding
339 !! Padding sizes
340 character(256) :: val, mode
341 !! Attribute value and mode
342
343 ! Set default values
344 padding = 0
345 mode = "constant"
346
347 ! Parse ONNX attributes
348 do i = 1, size(node%attributes)
349 val = node%attributes(i)%val
350 select case(trim(adjustl(node%attributes(i)%name)))
351 case("pads")
352 read(val,*) padding
353 case("mode")
354 mode = trim(adjustl(val))
355 case default
356 ! Do nothing
357 write(0,*) "WARNING: Unrecognised attribute in ONNX PAD2D &
358 &layer: ", trim(adjustl(node%attributes(i)%name))
359 end select
360 end do
361
362 ! Check size of initialisers
363 if(size(initialisers).gt.0)then
364 write(0,*) "WARNING: initialisers found for ONNX PAD2D layer"
365 end if
366
367 call this%set_hyperparams( &
368 padding = padding, &
369 method = mode, &
370 verbose = verbose &
371 )
372
373 end subroutine build_from_onnx_pad2d
374 !###############################################################################
375
376
377 !##############################################################################!
378 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
379 !##############################################################################!
380
381
382 !###############################################################################
383 subroutine forward_pad2d(this, input)
384 !! Forward propagation
385 implicit none
386
387 ! Arguments
388 class(pad2d_layer_type), intent(inout) :: this
389 !! Instance of the 2D padding layer
390 class(array_type), dimension(:,:), intent(in) :: input
391 !! Input values
392
393 ! Local variables
394 type(array_type), pointer :: ptr
395 !! Pointer array
396
397
398 call this%output(1,1)%zero_grad()
399 ptr => pad2d(input(1,1), this%facets, this%pad, this%imethod)
400 call this%output(1,1)%assign_and_deallocate_source(ptr)
401 this%output(1,1)%is_temporary = .false.
402
403 end subroutine forward_pad2d
404 !###############################################################################
405
406 end module athena__pad2d_layer
407