GCC Code Coverage Report


Directory: src/athena/
File: athena_full_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__full_layer
2 !! Module containing implementation of a fully connected layer
3 !!
4 !! This module implements a fully connected (dense) layer, the fundamental
5 !! building block of neural networks that connects every input to every output.
6 !!
7 !! Mathematical operation:
8 !! \[ \mathbf{y} = \sigma(\mathbf{W}\mathbf{x} + \mathbf{b}) \]
9 !!
10 !! where:
11 !! - \(\mathbf{x} \in \mathbb{R}^{n_{in}}\) is the input vector
12 !! - \(\mathbf{W} \in \mathbb{R}^{n_{out} \times n_{in}}\) is the weight matrix
13 !! - \(\mathbf{b} \in \mathbb{R}^{n_{out}}\) is the bias vector
14 !! - \(\sigma\) is the activation function
15 !! - \(\mathbf{y} \in \mathbb{R}^{n_{out}}\) is the output vector
16 !!
17 !! Number of parameters: \(n_{out} \times n_{in} + n_{out}\) (if bias used)
18 !!
19 !! Properties: Universal function approximator (with sufficient width/depth)
20 !! Learns arbitrary non-linear mappings between input and output spaces
21 !!
22 !! Attribution statement:
23 !! The get_num_params procedure is based on code from the
24 !! neural-fortran library
25 !! https://github.com/modern-fortran/neural-fortran
26 use coreutils, only: real32, stop_program
27 use athena__base_layer, only: learnable_layer_type, base_layer_type
28 use athena__misc_types, only: base_actv_type, base_init_type, &
29 onnx_node_type, onnx_initialiser_type, onnx_tensor_type
30 use diffstruc, only: array_type, matmul, operator(+)
31 use athena__initialiser_data, only: data_init_type
32 implicit none
33
34
35 private
36
37 public :: full_layer_type
38 public :: read_full_layer, create_from_onnx_full_layer
39
40
41 type, extends(learnable_layer_type) :: full_layer_type
42 !! Type for fully connected (aka dense) layer with overloaded procedures
43 integer :: num_inputs
44 !! Number of inputs
45 integer :: num_outputs
46 !! Number of outputs
47 type(array_type), dimension(1) :: z
48 !! Temporary arrays for forward propagation
49 contains
50 procedure, pass(this) :: get_num_params => get_num_params_full
51 !! Get the number of parameters for fully connected layer
52 procedure, pass(this) :: set_hyperparams => set_hyperparams_full
53 !! Set the hyperparameters for fully connected layer
54 procedure, pass(this) :: init => init_full
55 !! Initialise fully connected layer
56 procedure, pass(this) :: print_to_unit => print_to_unit_full
57 !! Print the layer to a file
58 procedure, pass(this) :: read => read_full
59 !! Read the layer from a file
60 procedure, pass(this) :: build_from_onnx => build_from_onnx_full
61 !! Build fully connected layer from ONNX node and initialiser
62
63 procedure, pass(this) :: forward => forward_full
64 !! Forward propagation derived type handler
65
66 final :: finalise_full
67 !! Finalise fully connected layer
68 end type full_layer_type
69
70 interface full_layer_type
71 !! Interface for setting up the fully connected layer
72 module function layer_setup( &
73 num_outputs, num_inputs, use_bias, &
74 activation, &
75 kernel_initialiser, bias_initialiser, verbose &
76 ) result(layer)
77 !! Setup a fully connected layer
78 integer, intent(in) :: num_outputs
79 !! Number of outputs
80 integer, optional, intent(in) :: num_inputs
81 !! Number of inputs
82 logical, optional, intent(in) :: use_bias
83 !! Whether to use bias
84 class(*), optional, intent(in) :: activation
85 !! Activation function
86 class(*), optional, intent(in) :: kernel_initialiser, bias_initialiser
87 !! Kernel and bias initialisers
88 integer, optional, intent(in) :: verbose
89 !! Verbosity level
90 type(full_layer_type) :: layer
91 !! Instance of the fully connected layer
92 end function layer_setup
93 end interface full_layer_type
94
95
96
97 contains
98
99 !###############################################################################
100 subroutine finalise_full(this)
101 !! Finalise fully connected layer
102 implicit none
103
104 ! Arguments
105 type(full_layer_type), intent(inout) :: this
106 !! Instance of the fully connected layer
107
108 if(allocated(this%input_shape)) deallocate(this%input_shape)
109 if(allocated(this%output)) deallocate(this%output)
110 if(this%z(1)%allocated) call this%z(1)%deallocate()
111
112 end subroutine finalise_full
113 !###############################################################################
114
115
116 !##############################################################################!
117 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
118 !##############################################################################!
119
120
121 !###############################################################################
122 pure function get_num_params_full(this) result(num_params)
123 !! Get the number of parameters for fully connected layer
124 !!
125 !! This function calculates the number of parameters for a fully connected
126 !! layer.
127 !! This procedure is based on code from the neural-fortran library
128 implicit none
129
130 ! Arguments
131 class(full_layer_type), intent(in) :: this
132 !! Instance of the fully connected layer
133 integer :: num_params
134 !! Number of parameters
135
136 num_params = ( this%num_inputs + 1 )* this%num_outputs
137
138 end function get_num_params_full
139 !###############################################################################
140
141
142 !##############################################################################!
143 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
144 !##############################################################################!
145
146
147 !###############################################################################
148 module function layer_setup( &
149 num_outputs, num_inputs, &
150 use_bias, &
151 activation, &
152 kernel_initialiser, bias_initialiser, verbose &
153 ) result(layer)
154 !! Setup a fully connected layer
155 use athena__activation, only: activation_setup
156 use athena__initialiser, only: initialiser_setup
157 implicit none
158
159 ! Arguments
160 integer, intent(in) :: num_outputs
161 !! Number of outputs
162 integer, optional, intent(in) :: num_inputs
163 !! Number of inputs
164 logical, optional, intent(in) :: use_bias
165 !! Whether to use bias
166 class(*), optional, intent(in) :: activation
167 !! Activation function
168 class(*), optional, intent(in) :: kernel_initialiser, bias_initialiser
169 !! Activation function, kernel initialiser, and bias initialiser
170 integer, optional, intent(in) :: verbose
171 !! Verbosity level
172
173 type(full_layer_type) :: layer
174 !! Instance of the fully connected layer
175
176 ! Local variables
177 integer :: verbose_ = 0
178 !! Verbosity level
179 logical :: use_bias_ = .true.
180 !! Whether to use bias
181 class(base_actv_type), allocatable :: activation_
182 !! Activation function
183 class(base_init_type), allocatable :: kernel_initialiser_, bias_initialiser_
184 !! Kernel and bias initialisers
185
186 if(present(verbose)) verbose_ = verbose
187
188
189 !---------------------------------------------------------------------------
190 ! Set use_bias
191 !---------------------------------------------------------------------------
192 if(present(use_bias)) use_bias_ = use_bias
193
194
195 !---------------------------------------------------------------------------
196 ! Set activation functions based on input name
197 !---------------------------------------------------------------------------
198 if(present(activation))then
199 activation_ = activation_setup(activation)
200 else
201 activation_ = activation_setup("none")
202 end if
203
204
205 !---------------------------------------------------------------------------
206 ! Define weights (kernels) and biases initialisers
207 !---------------------------------------------------------------------------
208 if(present(kernel_initialiser))then
209 kernel_initialiser_ = initialiser_setup(kernel_initialiser)
210 end if
211 if(present(bias_initialiser))then
212 bias_initialiser_ = initialiser_setup(bias_initialiser)
213 end if
214
215
216 !---------------------------------------------------------------------------
217 ! Set hyperparameters
218 !---------------------------------------------------------------------------
219 call layer%set_hyperparams( &
220 num_outputs = num_outputs, &
221 use_bias = use_bias_, &
222 activation = activation_, &
223 kernel_initialiser = kernel_initialiser_, &
224 bias_initialiser = bias_initialiser_, &
225 verbose = verbose_ &
226 )
227
228
229 !---------------------------------------------------------------------------
230 ! Initialise layer shape
231 !---------------------------------------------------------------------------
232 if(present(num_inputs)) call layer%init(input_shape=[num_inputs])
233
234 end function layer_setup
235 !###############################################################################
236
237
238 !###############################################################################
239 subroutine set_hyperparams_full( &
240 this, num_outputs, &
241 use_bias, &
242 activation, &
243 kernel_initialiser, bias_initialiser, &
244 verbose &
245 )
246 !! Set the hyperparameters for fully connected layer
247 use athena__activation, only: activation_setup
248 use athena__initialiser, only: get_default_initialiser, initialiser_setup
249 implicit none
250
251 ! Arguments
252 class(full_layer_type), intent(inout) :: this
253 !! Instance of the fully connected layer
254 integer, intent(in) :: num_outputs
255 !! Number of outputs
256 logical, intent(in) :: use_bias
257 !! Whether to use bias
258 class(base_actv_type), allocatable, intent(in) :: activation
259 !! Activation function
260 class(base_init_type), allocatable, intent(in) :: &
261 kernel_initialiser, bias_initialiser
262 !! Kernel and bias initialisers
263 integer, optional, intent(in) :: verbose
264 !! Verbosity level
265
266 ! Local variables
267 character(len=256) :: buffer
268
269
270 this%name = "full"
271 this%type = "full"
272 this%input_rank = 1
273 this%output_rank = 1
274 this%use_bias = use_bias
275 this%num_outputs = num_outputs
276 if(allocated(this%activation)) deallocate(this%activation)
277 if(.not.allocated(activation))then
278 this%activation = activation_setup("none")
279 else
280 allocate(this%activation, source=activation)
281 end if
282 if(allocated(this%kernel_init)) deallocate(this%kernel_init)
283 if(.not.allocated(kernel_initialiser))then
284 buffer = get_default_initialiser(this%activation%name)
285 this%kernel_init = initialiser_setup(buffer)
286 else
287 allocate(this%kernel_init, source=kernel_initialiser)
288 end if
289 if(allocated(this%bias_init)) deallocate(this%bias_init)
290 if(.not.allocated(bias_initialiser))then
291 buffer = get_default_initialiser( &
292 this%activation%name, &
293 is_bias=.true. &
294 )
295 this%bias_init = initialiser_setup(buffer)
296 else
297 if(allocated(this%bias_init)) deallocate(this%bias_init)
298 allocate(this%bias_init, source=bias_initialiser)
299 end if
300 if(present(verbose))then
301 if(abs(verbose).gt.0)then
302 write(*,'("FULL activation function: ",A)') &
303 trim(this%activation%name)
304 write(*,'("FULL kernel initialiser: ",A)') &
305 trim(this%kernel_init%name)
306 write(*,'("FULL bias initialiser: ",A)') &
307 trim(this%bias_init%name)
308 end if
309 end if
310
311 end subroutine set_hyperparams_full
312 !###############################################################################
313
314
315 !###############################################################################
316 subroutine init_full(this, input_shape, verbose)
317 !! Initialise fully connected layer
318 implicit none
319
320 ! Arguments
321 class(full_layer_type), intent(inout) :: this
322 !! Instance of the fully connected layer
323 integer, dimension(:), intent(in) :: input_shape
324 !! Input shape
325 integer, optional, intent(in) :: verbose
326 !! Verbosity level
327
328 ! Local variables
329 integer :: num_inputs
330 !! Temporary variable
331 integer :: verbose_ = 0
332
333
334 !---------------------------------------------------------------------------
335 ! Initialise optional arguments
336 !---------------------------------------------------------------------------
337 if(present(verbose)) verbose_ = verbose
338
339
340 !---------------------------------------------------------------------------
341 ! Initialise number of inputs
342 !---------------------------------------------------------------------------
343 if(.not.allocated(this%input_shape)) call this%set_shape(input_shape)
344 this%num_inputs = this%input_shape(1)
345 this%output_shape = [this%num_outputs]
346 this%num_params = this%get_num_params()
347
348
349 !---------------------------------------------------------------------------
350 ! Allocate weight, weight steps (velocities), output, and activation
351 !---------------------------------------------------------------------------
352 allocate(this%weight_shape(2,1))
353 this%weight_shape(:,1) = [ this%num_outputs, this%num_inputs ]
354
355 if(this%use_bias)then
356 this%bias_shape = [ this%num_outputs ]
357 allocate(this%params(2))
358 else
359 allocate(this%params(1))
360 end if
361 call this%params(1)%allocate([this%weight_shape(:,1), 1])
362 call this%params(1)%set_requires_grad(.true.)
363 this%params(1)%fix_pointer = .true.
364 this%params(1)%is_sample_dependent = .false.
365 this%params(1)%is_temporary = .false.
366 num_inputs = this%num_inputs
367 if(this%use_bias)then
368 num_inputs = this%num_inputs + 1
369 call this%params(2)%allocate([this%bias_shape, 1])
370 call this%params(2)%set_requires_grad(.true.)
371 this%params(2)%fix_pointer = .true.
372 this%params(2)%is_sample_dependent = .false.
373 this%params(2)%is_temporary = .false.
374 end if
375
376
377 !---------------------------------------------------------------------------
378 ! Initialise weights (kernels)
379 !---------------------------------------------------------------------------
380 call this%kernel_init%initialise( &
381 this%params(1)%val(:,1), &
382 fan_in = num_inputs, fan_out = this%num_outputs, &
383 spacing = [ this%num_outputs ] &
384 )
385
386 ! Initialise biases
387 !---------------------------------------------------------------------------
388 if(this%use_bias)then
389 call this%bias_init%initialise( &
390 this%params(2)%val(:,1), &
391 fan_in = num_inputs, fan_out = this%num_outputs &
392 )
393 end if
394
395
396 !---------------------------------------------------------------------------
397 ! Allocate arrays
398 !---------------------------------------------------------------------------
399 if(allocated(this%output)) deallocate(this%output)
400 allocate(this%output(1,1))
401 if(this%z(1)%allocated) call this%z(1)%deallocate()
402
403 end subroutine init_full
404 !###############################################################################
405
406
407 !##############################################################################!
408 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
409 !##############################################################################!
410
411
412 !###############################################################################
413 subroutine print_to_unit_full(this, unit)
414 !! Print fully connected layer to unit
415 use coreutils, only: to_upper
416 implicit none
417
418 ! Arguments
419 class(full_layer_type), intent(in) :: this
420 !! Instance of the fully connected layer
421 integer, intent(in) :: unit
422 !! File unit
423
424
425 ! Write initial parameters
426 !---------------------------------------------------------------------------
427 write(unit,'(3X,"NUM_INPUTS = ",I0)') this%num_inputs
428 write(unit,'(3X,"NUM_OUTPUTS = ",I0)') this%num_outputs
429
430 write(unit,'(3X,"USE_BIAS = ",L1)') this%use_bias
431 if(this%activation%name .ne. 'none')then
432 call this%activation%print_to_unit(unit)
433 end if
434
435
436 ! Write fully connected weights and biases
437 !---------------------------------------------------------------------------
438 write(unit,'("WEIGHTS")')
439 write(unit,'(5(E16.8E2))') this%params(1)%val(:,1)
440 if(this%use_bias)then
441 write(unit,'(5(E16.8E2))') this%params(2)%val(:,1)
442 end if
443 write(unit,'("END WEIGHTS")')
444
445 end subroutine print_to_unit_full
446 !###############################################################################
447
448
449 !###############################################################################
450 subroutine read_full(this, unit, verbose)
451 !! Read fully connected layer from file
452 use athena__tools_infile, only: assign_val, assign_vec, move
453 use coreutils, only: to_lower, to_upper, icount
454 use athena__activation, only: read_activation
455 use athena__initialiser, only: initialiser_setup
456 implicit none
457
458 ! Arguments
459 class(full_layer_type), intent(inout) :: this
460 !! Instance of the fully connected layer
461 integer, intent(in) :: unit
462 !! Unit number
463 integer, optional, intent(in) :: verbose
464 !! Verbosity level
465
466 ! Local variables
467 integer :: stat
468 !! Status of read
469 integer :: verbose_ = 0
470 !! Verbosity level
471 integer :: i, j, k, c, itmp1, iline, num_params
472 !! Loop variables and temporary integer
473 integer :: num_inputs, num_outputs
474 !! Number of inputs and outputs
475 logical :: use_bias = .true.
476 !! Whether to use bias
477 character(14) :: kernel_initialiser_name='', bias_initialiser_name=''
478 !! Initialisers
479 character(20) :: activation_name=''
480 !! Activation function
481 class(base_actv_type), allocatable :: activation
482 !! Activation function
483 class(base_init_type), allocatable :: kernel_initialiser, bias_initialiser
484 !! Initialisers
485 character(256) :: buffer, tag, err_msg
486 !! Buffer, tag, and error message
487 integer, dimension(2) :: input_shape
488 !! Input shape
489 real(real32), allocatable, dimension(:) :: data_list
490 !! Data list
491 integer :: param_line, final_line
492 !! Parameter line number
493
494
495 ! Initialise optional arguments
496 !---------------------------------------------------------------------------
497 if(present(verbose)) verbose_ = verbose
498
499
500 ! Loop over tags in layer card
501 !---------------------------------------------------------------------------
502 iline = 0
503 param_line = 0
504 final_line = 0
505 tag_loop: do
506
507 ! Check for end of file
508 !------------------------------------------------------------------------
509 read(unit,'(A)',iostat=stat) buffer
510 if(stat.ne.0)then
511 write(err_msg,'("file encountered error (EoF?) before END ",A)') &
512 to_upper(this%name)
513 call stop_program(err_msg)
514 return
515 end if
516 if(trim(adjustl(buffer)).eq."") cycle tag_loop
517
518 ! Check for end of layer card
519 !------------------------------------------------------------------------
520 if(trim(adjustl(buffer)).eq."END "//to_upper(trim(this%name)))then
521 final_line = iline
522 backspace(unit)
523 exit tag_loop
524 end if
525 iline = iline + 1
526
527 tag=trim(adjustl(buffer))
528 if(scan(buffer,"=").ne.0) tag=trim(tag(:scan(tag,"=")-1))
529
530 ! Read parameters from file
531 !------------------------------------------------------------------------
532 select case(trim(tag))
533 case("NUM_INPUTS")
534 call assign_val(buffer, num_inputs, itmp1)
535 case("NUM_OUTPUTS")
536 call assign_val(buffer, num_outputs, itmp1)
537 case("USE_BIAS")
538 call assign_val(buffer, use_bias, itmp1)
539 case("ACTIVATION")
540 iline = iline - 1
541 backspace(unit)
542 activation = read_activation(unit, iline)
543 case("KERNEL_INITIALISER", "KERNEL_INIT", "KERNEL_INITIALIZER")
544 call assign_val(buffer, kernel_initialiser_name, itmp1)
545 case("BIAS_INITIALISER", "BIAS_INIT", "BIAS_INITIALIZER")
546 call assign_val(buffer, bias_initialiser_name, itmp1)
547 case("WEIGHTS")
548 kernel_initialiser_name = 'zeros'
549 bias_initialiser_name = 'zeros'
550 param_line = iline
551 case default
552 ! Don't look for "e" due to scientific notation of numbers
553 ! ... i.e. exponent (E+00)
554 if(scan(to_lower(trim(adjustl(buffer))),&
555 'abcdfghijklmnopqrstuvwxyz').eq.0)then
556 cycle tag_loop
557 elseif(tag(:3).eq.'END')then
558 cycle tag_loop
559 end if
560 write(err_msg,'("Unrecognised line in input file: ",A)') &
561 trim(adjustl(buffer))
562 call stop_program(err_msg)
563 return
564 end select
565 end do tag_loop
566 kernel_initialiser = initialiser_setup(kernel_initialiser_name)
567 bias_initialiser = initialiser_setup(bias_initialiser_name)
568
569
570 ! Set hyperparameters and initialise layer
571 !---------------------------------------------------------------------------
572 call this%set_hyperparams( &
573 num_outputs = num_outputs, &
574 use_bias = use_bias, &
575 activation = activation, &
576 kernel_initialiser = kernel_initialiser, &
577 bias_initialiser = bias_initialiser, &
578 verbose = verbose_ &
579 )
580 call this%init(input_shape=[num_inputs])
581
582
583 ! Check if WEIGHTS card was found
584 !---------------------------------------------------------------------------
585 if(param_line.eq.0)then
586 write(0,*) "WARNING: WEIGHTS card in "//to_upper(trim(this%name))//" not found"
587 else
588 call move(unit, param_line - iline, iostat=stat)
589 num_params = this%num_inputs * this%num_outputs
590 allocate(data_list(num_params), source=0._real32)
591 c = 1
592 k = 1
593 data_concat_loop: do while(c.le.num_params)
594 read(unit,'(A)',iostat=stat) buffer
595 if(stat.ne.0) exit data_concat_loop
596 k = icount(buffer)
597 read(buffer,*,iostat=stat) (data_list(j),j=c,c+k-1)
598 c = c + k
599 end do data_concat_loop
600 this%params(1)%val(:,1) = data_list
601 deallocate(data_list)
602 if(use_bias)then
603 allocate(data_list(num_outputs), source=0._real32)
604 c = 1
605 k = 1
606 data_concat_loop2: do while(c.le.num_outputs)
607 read(unit,'(A)',iostat=stat) buffer
608 if(stat.ne.0) exit data_concat_loop2
609 k = icount(buffer)
610 read(buffer,*,iostat=stat) (data_list(j),j=c,c+k-1)
611 c = c + k
612 end do data_concat_loop2
613 this%params(2)%val(:,1) = data_list(1:num_outputs)
614 deallocate(data_list)
615 end if
616
617 ! Check for end of weights card
618 !------------------------------------------------------------------------
619 read(unit,'(A)') buffer
620 if(trim(adjustl(buffer)).ne."END WEIGHTS")then
621 write(0,*) trim(adjustl(buffer))
622 call stop_program("END WEIGHTS not where expected")
623 return
624 end if
625 end if
626
627
628 !---------------------------------------------------------------------------
629 ! Check for end of layer card
630 !---------------------------------------------------------------------------
631 call move(unit, final_line - iline, iostat=stat)
632 read(unit,'(A)') buffer
633 if(trim(adjustl(buffer)).ne."END "//to_upper(trim(this%name)))then
634 write(0,*) trim(adjustl(buffer))
635 write(err_msg,'("END ",A," not where expected")') to_upper(this%name)
636 call stop_program(err_msg)
637 return
638 end if
639
640 end subroutine read_full
641 !###############################################################################
642
643
644 !###############################################################################
645 function read_full_layer(unit, verbose) result(layer)
646 !! Read fully connected layer from file and return layer
647 implicit none
648
649 ! Arguments
650 integer, intent(in) :: unit
651 !! Unit number
652 integer, optional, intent(in) :: verbose
653 !! Verbosity level
654 class(base_layer_type), allocatable :: layer
655 !! Instance of the fully connected layer
656
657 ! Local variables
658 integer :: verbose_ = 0
659 !! Verbosity level
660
661 if(present(verbose)) verbose_ = verbose
662 allocate(layer, source=full_layer_type(num_outputs=0))
663 call layer%read(unit, verbose=verbose_)
664
665 end function read_full_layer
666 !###############################################################################
667
668
669 !###############################################################################
670 subroutine build_from_onnx_full(this, node, initialisers, value_info, verbose )
671 !! Read ONNX attributes for fully connected layer
672 use athena__activation, only: activation_setup
673 implicit none
674
675 ! Arguments
676 class(full_layer_type), intent(inout) :: this
677 !! Instance of the fully connected layer
678 type(onnx_node_type), intent(in) :: node
679 !! Instance of ONNX node information
680 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
681 !! Instance of ONNX initialiser information
682 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
683 !! Instance of ONNX value info information
684 integer, intent(in) :: verbose
685 !! Verbosity level
686
687 ! Local variables
688 integer :: i
689 !! Loop index
690 logical :: use_bias = .true.
691 !! Whether to use bias
692 integer, dimension(:), allocatable :: dims
693 !! Initialiser dimensions
694 integer :: weight_idx, bias_idx
695 !! Indices for weight and bias initialisers
696 integer :: num_outputs
697 !! Number of outputs
698 class(base_actv_type), allocatable :: activation
699 !! Activation function
700 class(base_init_type), allocatable :: kernel_initialiser, bias_initialiser
701
702
703 weight_idx = -1
704 bias_idx = -1
705 allocate(dims(0))
706 if(size(initialisers).lt.1)then
707 call stop_program("ONNX FULL layer requires at least 1 initialiser")
708 return
709 else
710 ! check which initialiser has weights and which has biases,
711 ! look for dimensions
712 do i = 1, size(initialisers)
713 if(allocated(initialisers(i)%dims))then
714 dims = [ dims, product(initialisers(i)%dims) ]
715 end if
716 end do
717 end if
718 ! if both weight and bias have dimension 1, check which is larger and that
719 ! the division of it by the kernel size is equal to the length of the other
720 select case(size(dims))
721 case(1)
722 weight_idx = 1
723 use_bias = .false.
724 case(2)
725 ! check which is weight and which is bias
726 if(mod(dims(1), dims(2)).eq.0)then
727 weight_idx = 1
728 bias_idx = 2
729 elseif(mod(dims(2), dims(1)).eq.0)then
730 weight_idx = 2
731 bias_idx = 1
732 else
733 call stop_program("ONNX FULL layer initialiser dimensions not compatible")
734 return
735 end if
736 case default
737 call stop_program("ONNX FULL layer number of initialisers not supported")
738 return
739 end select
740 num_outputs = value_info(1)%dims(2)
741
742 kernel_initialiser = data_init_type( data = initialisers(weight_idx)%data )
743 if(use_bias)then
744 bias_initialiser = data_init_type( data = initialisers(bias_idx)%data )
745 end if
746
747 activation = activation_setup("none")
748 call this%set_hyperparams( &
749 num_outputs = num_outputs, &
750 use_bias = use_bias, &
751 activation = activation, &
752 verbose = verbose, &
753 kernel_initialiser = kernel_initialiser, &
754 bias_initialiser = bias_initialiser &
755 )
756
757 end subroutine build_from_onnx_full
758 !###############################################################################
759
760
761 !###############################################################################
762 function create_from_onnx_full_layer(node, initialisers, value_info, verbose) &
763 result(layer)
764 !! Build fully connected layer from attributes and return layer
765 implicit none
766
767 ! Arguments
768 type(onnx_node_type), intent(in) :: node
769 !! Instance of ONNX node information
770 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
771 !! Instance of ONNX initialiser information
772 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
773 !! Instance of ONNX value info information
774 integer, optional, intent(in) :: verbose
775 !! Verbosity level
776 class(base_layer_type), allocatable :: layer
777 !! Instance of the 2D convolutional layer
778
779 ! Local variables
780 integer :: verbose_ = 0
781 !! Verbosity level
782
783 if(present(verbose)) verbose_ = verbose
784 allocate(layer, source=full_layer_type(num_outputs=0))
785 call layer%build_from_onnx(node, initialisers, value_info, verbose=verbose_)
786
787 end function create_from_onnx_full_layer
788 !###############################################################################
789
790
791 !##############################################################################!
792 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
793 !##############################################################################!
794
795
796 !###############################################################################
797 subroutine forward_full(this, input)
798 !! Forward propagation
799 implicit none
800
801 ! Arguments
802 class(full_layer_type), intent(inout) :: this
803 !! Instance of the fully connected layer
804 class(array_type), dimension(:,:), intent(in) :: input
805 !! Input values
806
807 type(array_type), pointer :: ptr => null()
808
809
810 ! Generate outputs from weights, biases, and inputs
811 !---------------------------------------------------------------------------
812 if(this%use_bias)then
813 ptr => matmul(this%params(1), input(1,1) ) + this%params(2)
814 else
815 ptr => matmul(this%params(1), input(1,1) )
816 end if
817
818 ! Apply activation function to activation
819 !---------------------------------------------------------------------------
820 call this%output(1,1)%zero_grad()
821 if(trim(this%activation%name) .eq. "none") then
822 call this%output(1,1)%assign_and_deallocate_source(ptr)
823 else
824 call this%z(1)%zero_grad()
825 call this%z(1)%assign_and_deallocate_source(ptr)
826 this%z(1)%is_temporary = .false.
827 ptr => this%activation%apply(this%z(1))
828 call this%output(1,1)%assign_and_deallocate_source(ptr)
829 end if
830 this%output(1,1)%is_temporary = .false.
831
832 end subroutine forward_full
833 !###############################################################################
834
835 end module athena__full_layer
836