GCC Code Coverage Report


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