GCC Code Coverage Report


Directory: src/athena/
File: athena_input_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__input_layer
2 !! Module containing procedures for an input layer
3 !!
4 !! This module implements the input layer which serves as the entry point
5 !! for data into a neural network. It handles data conversion and batching.
6 !!
7 !! Operation: Accepts external data and converts to internal array_type format
8 !! - Validates input shape matches specified dimensions
9 !! - Handles both dense arrays and graph-structured data
10 !! - No learnable parameters (pass-through layer)
11 !!
12 !! Properties:
13 !! - First layer in any network architecture
14 !! - Defines expected input shape for subsequent layers
15 !! - Supports multiple input sources in multi-input networks
16 use coreutils, only: real32, stop_program
17 use athena__base_layer, only: base_layer_type
18 use graphstruc, only: graph_type
19 use athena__misc_types, only: &
20 onnx_node_type, onnx_initialiser_type, onnx_tensor_type
21 use diffstruc, only: array_type
22 implicit none
23
24
25 private
26
27 public :: input_layer_type
28 public :: read_input_layer, create_from_onnx_input_layer
29
30
31 type, extends(base_layer_type) :: input_layer_type
32 !! Type for an input layer
33 integer :: index = 1
34 !! Index of the layer
35 integer :: num_outputs
36 !! Number of outputs
37 contains
38 procedure, pass(this) :: set_hyperparams => set_hyperparams_input
39 !! Set hyperparameters
40 procedure, pass(this) :: init => init_input
41 !! Initialise layer
42 procedure, pass(this) :: print_to_unit => print_to_unit_input
43 !! Print layer to unit
44 procedure, pass(this) :: read => read_input
45 !! Read layer from file
46 procedure, pass(this) :: set_input_real
47 !! Set input values
48 procedure, pass(this) :: set_input_graph
49 !! Set input values
50 generic :: set => set_input_real, set_input_graph
51 !! Generic interface for setting input values
52 procedure, pass(this) :: build_from_onnx => build_from_onnx_input
53 !! Build fully connected layer from ONNX node and initialiser
54
55 procedure, pass(this) :: forward => forward_input
56 !! Forward propagation derived type handler
57
58 end type input_layer_type
59
60 interface input_layer_type
61 !! Interface for an input layer
62 module function layer_setup( &
63 input_shape, index, use_graph_input, verbose &
64 ) result(layer)
65 !! Set up layer
66 integer, dimension(:), optional, intent(in) :: input_shape
67 !! Shape of the input data
68 integer, optional, intent(in) :: index
69 !! Index of the layer
70 logical, optional, intent(in) :: use_graph_input
71 !! Use graph input
72 integer, optional, intent(in) :: verbose
73 !! Verbosity level
74 type(input_layer_type) :: layer
75 !! Instance of the input layer
76 end function layer_setup
77 end interface input_layer_type
78
79
80
81 contains
82
83 !###############################################################################
84 module function layer_setup( &
85 input_shape, index, use_graph_input, verbose &
86 ) result(layer)
87 !! Set up layer
88 implicit none
89
90 ! Arguments
91 integer, dimension(:), optional, intent(in) :: input_shape
92 !! Shape of the input data
93 integer, optional, intent(in) :: index
94 !! Index of the layer
95 logical, optional, intent(in) :: use_graph_input
96 !! Use graph input
97 integer, optional, intent(in) :: verbose
98 !! Verbosity level
99
100 type(input_layer_type) :: layer
101 !! Instance of the input layer
102
103 ! Local variables
104 integer :: index_ = 1
105 !! Index of the layer
106 integer :: verbose_ = 0
107 !! Verbosity level
108 logical :: use_graph_input_ = .false.
109 !! Use graph input
110
111
112 if(present(verbose)) verbose_ = verbose
113
114 !---------------------------------------------------------------------------
115 ! Set hyperparameters
116 !---------------------------------------------------------------------------
117 if(present(index)) index_ = index
118 if(present(use_graph_input)) use_graph_input_ = use_graph_input
119 call layer%set_hyperparams( &
120 index = index_, &
121 use_graph_input = use_graph_input_, &
122 verbose = verbose_ &
123 )
124
125
126 !---------------------------------------------------------------------------
127 ! Initialise layer shape
128 !---------------------------------------------------------------------------
129 if(present(input_shape)) call layer%init(input_shape=input_shape)
130
131 end function layer_setup
132 !###############################################################################
133
134
135 !###############################################################################
136 subroutine set_hyperparams_input( &
137 this, &
138 input_rank, &
139 index, &
140 use_graph_input, &
141 verbose &
142 )
143 !! Set hyperparameters for an input layer
144 implicit none
145
146 ! Arguments
147 class(input_layer_type), intent(inout) :: this
148 !! Instance of the input layer
149 integer, optional, intent(in) :: input_rank
150 !! Rank of the input data
151 integer, optional, intent(in) :: index
152 !! Index of the layer
153 logical, optional, intent(in) :: use_graph_input
154 !! Use graph input
155 integer, optional, intent(in) :: verbose
156 !! Verbosity level
157
158 this%name = "input"
159 this%type = "inpt"
160 this%input_rank = 0
161 if(present(input_rank)) this%input_rank = input_rank
162 this%output_rank = this%input_rank
163 if(present(index)) this%index = index
164 if(present(use_graph_input))then
165 this%use_graph_input = use_graph_input
166 this%use_graph_output = use_graph_input
167 end if
168
169 end subroutine set_hyperparams_input
170 !###############################################################################
171
172
173 !###############################################################################
174 subroutine init_input(this, input_shape, verbose)
175 !! Initialise an input layer
176 implicit none
177
178 ! Arguments
179 class(input_layer_type), intent(inout) :: this
180 !! Instance of the input layer
181 integer, dimension(:), intent(in) :: input_shape
182 !! Shape of the input data
183 integer, optional, intent(in) :: verbose
184 !! Verbosity level
185
186 ! Local variables
187 integer :: verbose_ = 0
188 !! Verbosity level
189
190
191 !---------------------------------------------------------------------------
192 ! Initialise optional arguments
193 !---------------------------------------------------------------------------
194 if(present(verbose)) verbose_ = verbose
195
196
197 !---------------------------------------------------------------------------
198 ! Initialise input shape
199 !---------------------------------------------------------------------------
200 this%input_rank = size(input_shape, dim=1)
201 this%output_rank = this%input_rank
202 if(.not.allocated(this%input_shape)) call this%set_shape(input_shape)
203 this%output_shape = this%input_shape
204 this%num_outputs = product(this%input_shape)
205
206
207 !---------------------------------------------------------------------------
208 ! Allocate arrays
209 !---------------------------------------------------------------------------
210 this%input_rank = size(this%input_shape)
211 this%output_rank = this%input_rank
212 if(allocated(this%output)) deallocate(this%output)
213 allocate(this%output(1,1))
214
215 end subroutine init_input
216 !###############################################################################
217
218
219 !##############################################################################!
220 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
221 !##############################################################################!
222
223
224 !###############################################################################
225 subroutine print_to_unit_input(this, unit)
226 !! Print input layer to unit
227 implicit none
228
229 ! Arguments
230 class(input_layer_type), intent(in) :: this
231 !! Instance of the input layer
232 integer, intent(in) :: unit
233 !! File unit
234
235 ! Local variables
236 integer :: t
237 !! Loop index
238 character(100) :: fmt
239 !! Format string
240
241
242 ! Write initial parameters
243 !---------------------------------------------------------------------------
244 write(unit,'(3X,"INPUT_RANK = ",I0)') this%input_rank
245 write(fmt,'("(3X,""INPUT_SHAPE ="",",I0,"(1X,I0))")') size(this%input_shape)
246 write(unit,fmt) this%input_shape
247 write(unit,'(3X,"USE_GRAPH_INPUT = ",L1)') this%use_graph_input
248
249 end subroutine print_to_unit_input
250 !###############################################################################
251
252
253 !###############################################################################
254 subroutine read_input(this, unit, verbose)
255 !! Read an input layer from a file
256 use athena__tools_infile, only: assign_val, assign_vec, get_val
257 use coreutils, only: to_lower, to_upper, icount
258 implicit none
259
260 ! Arguments
261 class(input_layer_type), intent(inout) :: this
262 !! Instance of the input layer
263 integer, intent(in) :: unit
264 !! Unit number
265 integer, optional, intent(in) :: verbose
266 !! Verbosity level
267
268 ! Local variables
269 integer :: verbose_ = 0
270 !! Verbosity level
271 integer :: stat
272 !! File status
273 integer :: itmp1= 0
274 !! Temporary integer
275
276 ! Local variables
277 integer :: input_rank = 0
278 !! Rank of the input data
279 integer, dimension(:), allocatable :: input_shape
280 !! Shape of the input data
281 logical :: use_graph_input = .false.
282 !! Use graph input
283 character(256) :: buffer, tag, err_msg
284 !! Buffer for reading lines, tag for identifying lines, error message
285
286
287 ! Initialise optional arguments
288 !---------------------------------------------------------------------------
289 if(present(verbose)) verbose_ = verbose
290
291
292 ! Loop over tags in layer card
293 !---------------------------------------------------------------------------
294 tag_loop: do
295
296 ! Check for end of file
297 !------------------------------------------------------------------------
298 read(unit,'(A)',iostat=stat) buffer
299 if(stat.ne.0)then
300 write(err_msg,'("file encountered error (EoF?) before END ",A)') &
301 to_upper(this%name)
302 call stop_program(err_msg)
303 return
304 end if
305 if(trim(adjustl(buffer)).eq."") cycle tag_loop
306
307 ! Check for end of layer card
308 !------------------------------------------------------------------------
309 if(trim(adjustl(buffer)).eq."END INPUT")then
310 backspace(unit)
311 exit tag_loop
312 end if
313
314 tag=trim(adjustl(buffer))
315 if(scan(buffer,"=").ne.0) tag=trim(tag(:scan(tag,"=")-1))
316
317 ! Read parameters from save file
318 !------------------------------------------------------------------------
319 select case(trim(tag))
320 case("INPUT_RANK")
321 call assign_val(buffer, input_rank, itmp1)
322 case("INPUT_SHAPE")
323 itmp1 = icount(get_val(buffer))
324 allocate(input_shape(itmp1))
325 call assign_vec(buffer, input_shape, itmp1)
326 case("USE_GRAPH_INPUT")
327 call assign_val(buffer, use_graph_input, itmp1)
328 case default
329 ! Don't look for "e" due to scientific notation of numbers
330 ! ... i.e. exponent (E+00)
331 if(scan(to_lower(trim(adjustl(buffer))),&
332 'abcdfghijklmnopqrstuvwxyz').eq.0)then
333 cycle tag_loop
334 elseif(tag(:3).eq.'END')then
335 cycle tag_loop
336 end if
337 write(err_msg,'("Unrecognised line in input file: ",A)') &
338 trim(adjustl(buffer))
339 call stop_program(err_msg)
340 return
341 end select
342 end do tag_loop
343 if(.not.allocated(input_shape))then
344 write(err_msg,'("No input shape found in ",A)') to_upper(this%name)
345 call stop_program(err_msg)
346 return
347 end if
348
349
350 ! Set hyperparameters and initialise layer
351 !---------------------------------------------------------------------------
352 call this%set_hyperparams( &
353 input_rank = input_rank, &
354 use_graph_input = use_graph_input, &
355 verbose = verbose_ &
356 )
357 call this%init(input_shape = input_shape)
358
359
360 ! Check for end of layer card
361 !---------------------------------------------------------------------------
362 read(unit,'(A)') buffer
363 if(trim(adjustl(buffer)).ne."END INPUT")then
364 write(0,*) trim(adjustl(buffer))
365 write(err_msg,'("END ",A," not where expected")') to_upper(this%name)
366 call stop_program(err_msg)
367 return
368 end if
369
370 end subroutine read_input
371 !###############################################################################
372
373
374 !###############################################################################
375 function read_input_layer(unit, verbose) result(layer)
376 !! Read an input layer from a file
377 implicit none
378
379 ! Arguments
380 integer, intent(in) :: unit
381 !! Unit number
382 integer, optional, intent(in) :: verbose
383 !! Verbosity level
384 class(base_layer_type), allocatable :: layer
385 !! Instance of the input layer
386
387 ! Local variables
388 integer :: verbose_ = 0
389 !! Verbosity level
390
391
392 if(present(verbose)) verbose_ = verbose
393 allocate(layer, source=input_layer_type())
394 call layer%read(unit, verbose=verbose_)
395
396 end function read_input_layer
397 !###############################################################################
398
399
400 !###############################################################################
401 subroutine build_from_onnx_input(this, node, initialisers, value_info, verbose )
402 !! Read ONNX attributes for fully connected layer
403 implicit none
404
405 ! Arguments
406 class(input_layer_type), intent(inout) :: this
407 !! Instance of the fully connected layer
408 type(onnx_node_type), intent(in) :: node
409 !! ONNX node information
410 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
411 !! ONNX initialiser information
412 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
413 !! ONNX value info
414 integer, intent(in) :: verbose
415 !! Verbosity level
416
417 end subroutine build_from_onnx_input
418 !###############################################################################
419
420
421 !###############################################################################
422 function create_from_onnx_input_layer(node, initialisers, value_info, verbose) &
423 result(layer)
424 !! Build fully connected layer from attributes and return layer
425 implicit none
426
427 ! Arguments
428 type(onnx_node_type), intent(in) :: node
429 !! ONNX node information
430 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
431 !! ONNX initialiser information
432 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
433 !! ONNX value info
434 integer, optional, intent(in) :: verbose
435 !! Verbosity level
436 class(base_layer_type), allocatable :: layer
437 !! Instance of the 2D convolutional layer
438
439 ! Local variables
440 integer :: verbose_ = 0
441 !! Verbosity level
442
443 if(present(verbose)) verbose_ = verbose
444 allocate(layer, source=input_layer_type())
445 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
446
447 end function create_from_onnx_input_layer
448 !###############################################################################
449
450
451 !##############################################################################!
452 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
453 !##############################################################################!
454
455
456 !###############################################################################
457 subroutine forward_input(this, input)
458 !! Forward propagation for an input layer
459 implicit none
460
461 ! Arguments
462 class(input_layer_type), intent(inout) :: this
463 !! Instance of the input layer
464 class(array_type), dimension(:,:), intent(in) :: input
465 !! Input data
466
467 ! Local variables
468 integer :: i, j
469 !! Loop indices
470
471 if(allocated(this%output))then
472 if(any(shape(this%output).ne.shape(input)))then
473 deallocate(this%output)
474 allocate(this%output(size(input,1),size(input,2)))
475 end if
476 else
477 allocate(this%output(size(input,1),size(input,2)))
478 end if
479
480 do i = 1, size(input, 1)
481 do j = 1, size(input, 2)
482 if(.not.input(i,j)%allocated)then
483 call stop_program('Input to input layer not allocated')
484 return
485 end if
486 call this%output(i,j)%assign_shallow( input(i,j) )
487 this%output(i,j)%is_temporary = .false.
488 end do
489 end do
490
491 end subroutine forward_input
492 !###############################################################################
493
494
495 !###############################################################################
496 pure subroutine set_input_real(this, input)
497 !! Set input values for an input layer
498 implicit none
499
500 ! Arguments
501 class(input_layer_type), intent(inout) :: this
502 !! Instance of the input layer
503 real(real32), dimension(..), intent(in) :: input
504 !! Input data
505
506 call this%output(1,1)%set( input )
507 this%output(1,1)%is_temporary = .false.
508
509 end subroutine set_input_real
510 !-------------------------------------------------------------------------------
511 subroutine set_input_graph(this, input)
512 !! Set input values for an input layer
513 implicit none
514
515 ! Arguments
516 class(input_layer_type), intent(inout) :: this
517 !! Instance of the input layer
518 type(graph_type), dimension(:), intent(in) :: input
519 !! Input data
520
521 integer :: s
522
523 if(allocated(this%output))then
524 if(any(shape(this%output).ne.[2,size(input)]))then
525 deallocate(this%output)
526 allocate(this%output(2,size(input)))
527 end if
528 else
529 allocate(this%output(2,size(input)))
530 end if
531
532 do s = 1, size(input)
533 if(this%output(1,s)%allocated) call this%output(1,s)%deallocate()
534 if(this%output(2,s)%allocated) call this%output(2,s)%deallocate()
535 call this%output(1,s)%allocate( &
536 array_shape = [ &
537 input(s)%num_vertex_features, input(s)%num_vertices &
538 ] &
539 )
540 call this%output(1,s)%zero_grad()
541 call this%output(1,s)%set_requires_grad(.false.)
542 call this%output(1,s)%set( input(s)%vertex_features )
543 this%output(1,s)%is_temporary = .false.
544 if(input(s)%num_edge_features.le.0) cycle
545 call this%output(2,s)%allocate( &
546 array_shape = [ &
547 input(s)%num_edge_features, input(s)%num_edges &
548 ] &
549 )
550 call this%output(2,s)%zero_grad()
551 call this%output(2,s)%set_requires_grad(.false.)
552 call this%output(2,s)%set( input(s)%edge_features )
553 this%output(2,s)%is_temporary = .false.
554 end do
555
556 end subroutine set_input_graph
557 !###############################################################################
558
559 end module athena__input_layer
560