GCC Code Coverage Report


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