GCC Code Coverage Report


Directory: src/athena/
File: athena_flatten_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__flatten_layer
2 !! Module containing implementation of a flattening layer
3 !!
4 !! This module implements a reshape layer that flattens multi-dimensional
5 !! inputs into 1D vectors. Commonly used between convolutional and dense layers.
6 !!
7 !! Mathematical operation:
8 !! Reshape: (d1, d2, ..., dn) -> (d1 * d2 * ... * dn)
9 !!
10 !! Example: (28, 28, 32) -> (25088)
11 !!
12 !! No parameters, pure reshape operation
13 !! Preserves all information, just changes tensor structure
14 use coreutils, only: real32, stop_program
15 use athena__base_layer, only: base_layer_type
16 use diffstruc, only: array_type, pack
17 use athena__misc_types, only: &
18 onnx_node_type, onnx_initialiser_type, onnx_tensor_type
19 implicit none
20
21
22 private
23
24 public :: flatten_layer_type
25 public :: read_flatten_layer, create_from_onnx_flatten_layer
26
27
28 type, extends(base_layer_type) :: flatten_layer_type
29 !! Type for 1D flattening layer with overloaded procedures
30 integer :: num_outputs
31 !! Number of outputs
32 contains
33 procedure, pass(this) :: set_rank => set_rank_flatten
34 !! Set input and output rank for flattening layer
35 procedure, pass(this) :: set_hyperparams => set_hyperparams_flatten
36 !! Set hyperparameters for flattening layer
37 procedure, pass(this) :: init => init_flatten
38 !! Initialise flattening layer
39 procedure, pass(this) :: print_to_unit => print_to_unit_flatten
40 !! Print flatten layer to unit
41 procedure, pass(this) :: read => read_flatten
42 !! Read flattening layer from file
43 procedure, pass(this) :: build_from_onnx => build_from_onnx_flatten
44 !! Build flattening layer from ONNX node and initialisers
45
46 procedure, pass(this) :: forward => forward_flatten
47 !! Forward propagation derived type handler
48
49 end type flatten_layer_type
50
51 interface flatten_layer_type
52 !! Interface for setting up the flattening layer
53 module function layer_setup( &
54 input_shape, input_rank, verbose &
55 ) result(layer)
56 !! Set up the flattening layer
57 integer, dimension(:), optional, intent(in) :: input_shape
58 !! Input shape
59 integer, optional, intent(in) :: input_rank
60 !! Input rank
61 integer, optional, intent(in) :: verbose
62 !! Verbosity level
63 type(flatten_layer_type) :: layer
64 !! Instance of the flattening layer
65 end function layer_setup
66 end interface flatten_layer_type
67
68
69
70 contains
71
72 !###############################################################################
73 subroutine set_rank_flatten(this, input_rank, output_rank)
74 !! Set the input and output ranks of the layer
75 implicit none
76
77 ! Arguments
78 class(flatten_layer_type), intent(inout) :: this
79 !! Instance of the layer
80 integer, intent(in) :: input_rank
81 !! Input rank
82 integer, intent(in) :: output_rank
83 !! Output rank
84
85 !---------------------------------------------------------------------------
86 ! Set input and output ranks
87 !---------------------------------------------------------------------------
88 this%input_rank = input_rank
89 this%output_rank = output_rank
90
91 end subroutine set_rank_flatten
92 !###############################################################################
93
94
95 !###############################################################################
96 module function layer_setup( &
97 input_shape, input_rank, verbose &
98 ) result(layer)
99 !! Set up the flattening layer
100 implicit none
101
102 ! Arguments
103 integer, dimension(:), optional, intent(in) :: input_shape
104 !! Input shape
105 integer, optional, intent(in) :: input_rank
106 !! Input rank
107 integer, optional, intent(in) :: verbose
108 !! Verbosity level
109
110 type(flatten_layer_type) :: layer
111 !! Instance of the flattening layer
112
113 ! Local variables
114 integer :: input_rank_ = 0
115 !! Input rank
116 integer :: verbose_ = 0
117 !! Verbosity level
118
119 if(present(verbose)) verbose_ = verbose
120
121
122 !---------------------------------------------------------------------------
123 ! Set hyperparameters
124 !---------------------------------------------------------------------------
125 if(present(input_rank))then
126 input_rank_ = input_rank
127 elseif(present(input_shape))then
128 input_rank_ = size(input_shape)
129 else
130 call stop_program( &
131 "input_rank or input_shape must be provided to flatten layer" &
132 )
133 return
134 end if
135 call layer%set_hyperparams(input_rank_, verbose_)
136
137
138 !---------------------------------------------------------------------------
139 ! Initialise layer shape
140 !---------------------------------------------------------------------------
141 if(present(input_shape)) call layer%init(input_shape=input_shape)
142
143 end function layer_setup
144 !###############################################################################
145
146
147 !###############################################################################
148 subroutine set_hyperparams_flatten(this, input_rank, verbose)
149 !! Set hyperparameters for flattening layer
150 implicit none
151
152 ! Arguments
153 class(flatten_layer_type), intent(inout) :: this
154 !! Instance of the flattening layer
155 integer, intent(in) :: input_rank
156 !! Input rank
157 integer, optional, intent(in) :: verbose
158 !! Verbosity level
159
160 this%name = "flatten"
161 this%type = "flat"
162 this%input_rank = input_rank
163 this%output_rank = 1
164 end subroutine set_hyperparams_flatten
165 !###############################################################################
166
167
168 !###############################################################################
169 subroutine init_flatten(this, input_shape, verbose)
170 !! Initialise flattening layer
171 implicit none
172
173 ! Arguments
174 class(flatten_layer_type), intent(inout) :: this
175 !! Instance of the flattening layer
176 integer, dimension(:), intent(in) :: input_shape
177 !! Input shape
178 integer, optional, intent(in) :: verbose
179 !! Verbosity level
180
181 ! Local variables
182 integer :: verbose_ = 0
183 !! Verbosity level
184
185
186 !---------------------------------------------------------------------------
187 ! Initialise optional arguments
188 !---------------------------------------------------------------------------
189 if(present(verbose)) verbose_ = verbose
190
191
192 !---------------------------------------------------------------------------
193 ! Initialise input shape
194 !---------------------------------------------------------------------------
195 this%input_rank = size(input_shape)
196 if(.not.allocated(this%input_shape)) call this%set_shape(input_shape)
197
198
199 !---------------------------------------------------------------------------
200 ! Initialise output shape
201 !---------------------------------------------------------------------------
202 this%num_outputs = product(this%input_shape)
203 if(allocated(this%output))then
204 if(this%output(1,1)%allocated) call this%output(1,1)%deallocate()
205 end if
206 allocate(this%output(1,1))
207 this%output_shape = [this%num_outputs]
208
209
210 !---------------------------------------------------------------------------
211 ! Allocate arrays
212 !---------------------------------------------------------------------------
213 if(this%use_graph_input)then
214 call stop_program( &
215 "Graph input not supported for flatten layer" &
216 )
217 return
218 else
219 if(allocated(this%output)) deallocate(this%output)
220 allocate( this%output(1,1) )
221 end if
222
223 end subroutine init_flatten
224 !###############################################################################
225
226
227 !##############################################################################!
228 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
229 !##############################################################################!
230
231
232 !###############################################################################
233 subroutine print_to_unit_flatten(this, unit)
234 !! Print flatten layer to unit
235 implicit none
236
237 ! Arguments
238 class(flatten_layer_type), intent(in) :: this
239 !! Instance of the flatten layer
240 integer, intent(in) :: unit
241 !! File unit
242
243 ! Local variables
244 character(100) :: fmt
245 !! Format string
246
247
248 ! Write initial parameters
249 !---------------------------------------------------------------------------
250 write(unit,'(3X,"INPUT_RANK = ",I0)') this%input_rank
251 write(fmt,'("(3X,""INPUT_SHAPE ="",",I0,"(1X,I0))")') size(this%input_shape)
252 write(unit,fmt) this%input_shape
253
254 end subroutine print_to_unit_flatten
255 !###############################################################################
256
257
258 !###############################################################################
259 subroutine read_flatten(this, unit, verbose)
260 !! Read flattening layer from file
261 use athena__tools_infile, only: assign_val, assign_vec, get_val
262 use coreutils, only: to_lower, to_upper, icount
263 implicit none
264
265 ! Arguments
266 class(flatten_layer_type), intent(inout) :: this
267 !! Instance of the flattening layer
268 integer, intent(in) :: unit
269 !! File unit
270 integer, optional, intent(in) :: verbose
271 !! Verbosity level
272
273 ! Local variables
274 integer :: stat, verbose_ = 0
275 !! File status and verbosity level
276 integer :: itmp1 = 0
277 !! Temporary integer
278 integer :: input_rank = 0
279 !! Input rank
280 integer, dimension(:), allocatable :: input_shape
281 !! Input shape
282 character(256) :: buffer, tag, err_msg
283 !! Buffer, tag, and error message
284
285
286 ! Initialise optional arguments
287 !---------------------------------------------------------------------------
288 if(present(verbose)) verbose_ = verbose
289
290
291 ! Loop over tags in layer card
292 !---------------------------------------------------------------------------
293 tag_loop: do
294
295 ! Check for end of file
296 !------------------------------------------------------------------------
297 read(unit,'(A)',iostat=stat) buffer
298 if(stat.ne.0)then
299 write(err_msg,'("file encountered error (EoF?) before END ",A)') &
300 to_upper(this%name)
301 call stop_program(err_msg)
302 return
303 end if
304 if(trim(adjustl(buffer)).eq."") cycle tag_loop
305
306 ! Check for end of layer card
307 !------------------------------------------------------------------------
308 if(trim(adjustl(buffer)).eq."END "//to_upper(trim(this%name)))then
309 backspace(unit)
310 exit tag_loop
311 end if
312
313 tag=trim(adjustl(buffer))
314 if(scan(buffer,"=").ne.0) tag=trim(tag(:scan(tag,"=")-1))
315
316 ! Read parameters from save file
317 !------------------------------------------------------------------------
318 select case(trim(tag))
319 case("INPUT_SHAPE")
320 itmp1 = icount(get_val(buffer))
321 allocate(input_shape(itmp1), source=0)
322 call assign_vec(buffer, input_shape, itmp1)
323 case("INPUT_RANK")
324 call assign_val(buffer, input_rank, itmp1)
325 case default
326 ! Don't look for "e" due to scientific notation of numbers
327 ! ... i.e. exponent (E+00)
328 if( &
329 scan( &
330 to_lower(trim(adjustl(buffer))), &
331 'abcdfghijklmnopqrstuvwxyz' &
332 ) .eq. 0 &
333 )then
334 cycle tag_loop
335 elseif(tag(:3).eq.'END')then
336 cycle tag_loop
337 end if
338 write(err_msg,'("Unrecognised line in input file: ",A)') &
339 trim(adjustl(buffer))
340 call stop_program(err_msg)
341 return
342 end select
343 end do tag_loop
344
345 if(allocated(input_shape))then
346 if(input_rank.eq.0)then
347 input_rank = size(input_shape)
348 elseif(input_rank.ne.size(input_shape))then
349 write(err_msg,'("input_rank (",I0,") does not match input_shape (",I0,")")') &
350 input_rank, size(input_shape)
351 call stop_program(err_msg)
352 return
353 end if
354 elseif(input_rank.eq.0)then
355 write(err_msg,'("input_rank must be provided if input_shape is not")')
356 call stop_program(err_msg)
357 return
358 end if
359
360
361 ! Set hyperparameters and initialise layer
362 !---------------------------------------------------------------------------
363 call this%set_hyperparams(input_rank = input_rank, verbose = verbose_)
364 call this%init(input_shape = input_shape)
365
366
367 ! Check for end of layer card
368 !---------------------------------------------------------------------------
369 read(unit,'(A)') buffer
370 if(trim(adjustl(buffer)).ne."END "//to_upper(trim(this%name)))then
371 write(0,*) trim(adjustl(buffer))
372 write(err_msg,'("END ",A," not where expected")') to_upper(this%name)
373 call stop_program(err_msg)
374 return
375 end if
376
377 end subroutine read_flatten
378 !###############################################################################
379
380
381 !###############################################################################
382 function read_flatten_layer(unit, verbose) result(layer)
383 !! Read flattening layer from file and return layer
384 implicit none
385
386 ! Arguments
387 integer, intent(in) :: unit
388 !! File unit
389 integer, optional, intent(in) :: verbose
390 !! Verbosity level
391 class(base_layer_type), allocatable :: layer
392 !! Instance of the flattening layer
393
394 ! Local variables
395 integer :: verbose_ = 0
396 !! Verbosity level
397
398 if(present(verbose)) verbose_ = verbose
399 allocate(layer, source=flatten_layer_type(input_rank=1))
400 call layer%read(unit, verbose=verbose_)
401
402 end function read_flatten_layer
403 !###############################################################################
404
405
406 !###############################################################################
407 subroutine build_from_onnx_flatten(this, node, initialisers, value_info, verbose )
408 !! Read ONNX attributes for flattening layer
409 implicit none
410
411 ! Arguments
412 class(flatten_layer_type), intent(inout) :: this
413 !! Instance of the flattening layer
414 type(onnx_node_type), intent(in) :: node
415 !! ONNX node information
416 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
417 !! ONNX initialiser information
418 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
419 !! ONNX value info
420 integer, intent(in) :: verbose
421 !! Verbosity level
422
423 ! Local variables
424 integer :: verbose_ = 0
425 !! Verbosity level
426
427 end subroutine build_from_onnx_flatten
428 !###############################################################################
429
430
431 !###############################################################################
432 function create_from_onnx_flatten_layer( &
433 node, initialisers, value_info, verbose &
434 ) result(layer)
435 !! Build flattening layer from attributes and return layer
436 implicit none
437
438 ! Arguments
439 type(onnx_node_type), intent(in) :: node
440 !! ONNX node information
441 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
442 !! ONNX initialiser information
443 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
444 !! ONNX value info
445 integer, optional, intent(in) :: verbose
446 !! Verbosity level
447 class(base_layer_type), allocatable :: layer
448 !! Instance of the flattening layer
449
450 ! Local variables
451 integer :: verbose_ = 0
452 !! Verbosity level
453
454 if(present(verbose)) verbose_ = verbose
455 allocate(layer, source=flatten_layer_type(input_rank=0))
456 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
457
458 end function create_from_onnx_flatten_layer
459 !###############################################################################
460
461
462 !##############################################################################!
463 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
464 !##############################################################################!
465
466
467 !###############################################################################
468 subroutine forward_flatten(this, input)
469 !! Forward propagation
470 implicit none
471
472 ! Arguments
473 class(flatten_layer_type), intent(inout) :: this
474 !! Instance of the fully connected layer
475 class(array_type), dimension(:,:), intent(in) :: input
476 !! Input values
477
478 type(array_type), pointer :: ptr => null()
479
480
481 ! Flatten input
482 !---------------------------------------------------------------------------
483 call this%output(1,1)%zero_grad()
484 ptr => pack(input(1,1), dim = 1)
485 call this%output(1,1)%assign_and_deallocate_source(ptr)
486 this%output(1,1)%is_temporary = .false.
487
488 end subroutine forward_flatten
489 !###############################################################################
490
491 end module athena__flatten_layer
492