GCC Code Coverage Report


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