GCC Code Coverage Report


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