GCC Code Coverage Report


Directory: src/athena/
File: athena_dropblock3d_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__dropblock3d_layer
2 !! Module containing implementation of a 3D dropblock layer
3 !!
4 !! This module implements DropBlock regularization for 3D convolutional layers,
5 !! dropping contiguous 3D regions (blocks) instead of individual elements.
6 !! Extension of 2D DropBlock for volumetric/spatiotemporal data.
7 !!
8 !! Mathematical operation (training):
9 !! 1. Compute drop probability per spatial location:
10 !! gamma = p * (feature_size^3) / (block_size^3 * valid_positions)
11 !! 2. Sample Bernoulli mask M_i ~ Bernoulli(gamma)
12 !! 3. Expand mask to block_size x block_size x block_size blocks
13 !! 4. Apply and normalize:
14 !! y = x * M * (count_elements / count_ones)
15 !!
16 !! where block_size is the spatial extent of each dropped block in all 3 dims
17 !!
18 !! Inference: acts as identity (no dropout applied)
19 !! \[
20 !! y_i = x_i
21 !! \]
22 !!
23 !! Benefits: Spatial/temporal coherence for 3D CNNs, better for video/volumetric,
24 !! removes spatiotemporal semantic information
25 !! Typical: block_size=5-7, keep_prob=0.9 for 3D ResNets
26 !! Reference: Ghiasi et al. (2018), NeurIPS - https://arxiv.org/abs/1810.12890
27 use coreutils, only: real32, stop_program
28 use athena__base_layer, only: drop_layer_type, base_layer_type
29 use diffstruc, only: array_type, operator(*)
30 use athena__misc_types, only: &
31 onnx_node_type, onnx_initialiser_type, onnx_tensor_type
32 use athena__diffstruc_extd, only: merge_over_channels
33 implicit none
34
35
36 private
37
38 public :: dropblock3d_layer_type
39 public :: read_dropblock3d_layer
40
41
42 type, extends(drop_layer_type) :: dropblock3d_layer_type
43 !! Type for 3D dropblock layer with overloaded procedures
44 integer :: block_size, half
45 !! Block size and half block size
46 !! Block size is the width of the block to drop (typical = 5)
47 real(real32) :: gamma
48 !! Number of activation units to drop
49 integer :: num_channels
50 !! Number of channels
51 logical, allocatable, dimension(:,:,:) :: mask
52 !! Mask for dropblock
53 contains
54 procedure, pass(this) :: set_hyperparams => set_hyperparams_dropblock3d
55 !! Set hyperparameters for 3D dropblock layer
56 procedure, pass(this) :: init => init_dropblock3d
57 !! Initialise 3D dropblock layer
58 procedure, pass(this) :: print_to_unit => print_to_unit_dropblock3d
59 !! Print 3D dropblock layer to unit
60 procedure, pass(this) :: read => read_dropblock3d
61 !! Read 3D dropblock layer from file
62
63 procedure, pass(this) :: forward => forward_dropblock3d
64 !! Forward propagation derived type handler
65
66 procedure, pass(this) :: generate_mask => generate_bernoulli_mask
67 !! Generate Bernoulli mask
68 end type dropblock3d_layer_type
69
70 interface dropblock3d_layer_type
71 !! Interface for setting up the 3D dropblock layer
72 module function layer_setup( &
73 rate, block_size, &
74 input_shape, &
75 verbose ) result(layer)
76 !! Set up the 3D dropblock layer
77 real(real32), intent(in) :: rate
78 !! Drop rate
79 integer, intent(in) :: block_size
80 !! Block size
81 integer, dimension(:), optional, intent(in) :: input_shape
82 !! Input shape
83 integer, optional, intent(in) :: verbose
84 !! Verbosity level
85 type(dropblock3d_layer_type) :: layer
86 !! Instance of the 3D dropblock layer
87 end function layer_setup
88 end interface dropblock3d_layer_type
89
90
91
92 contains
93
94 !###############################################################################
95 module function layer_setup( &
96 rate, block_size, &
97 input_shape, &
98 verbose ) result(layer)
99 !! Set up the 3D dropblock layer
100 implicit none
101
102 ! Arguments
103 real(real32), intent(in) :: rate
104 !! Drop rate
105 integer, intent(in) :: block_size
106 !! Block size
107 integer, dimension(:), optional, intent(in) :: input_shape
108 !! Input shape
109 integer, optional, intent(in) :: verbose
110 !! Verbosity level
111
112 type(dropblock3d_layer_type) :: layer
113 !! Instance of the 3D dropblock layer
114
115 ! Local variables
116 integer :: verbose_ = 0
117 !! Verbosity level
118
119 if(present(verbose)) verbose_ = verbose
120
121 !---------------------------------------------------------------------------
122 ! Initialise hyperparameters
123 !---------------------------------------------------------------------------
124 call layer%set_hyperparams(rate, block_size, verbose=verbose_)
125
126
127 !---------------------------------------------------------------------------
128 ! Initialise layer shape
129 !---------------------------------------------------------------------------
130 if(present(input_shape)) call layer%init(input_shape=input_shape)
131
132 end function layer_setup
133 !###############################################################################
134
135
136 !###############################################################################
137 subroutine set_hyperparams_dropblock3d(this, rate, block_size, verbose)
138 !! Set hyperparameters for 3D dropblock layer
139 implicit none
140
141 ! Arguments
142 class(dropblock3d_layer_type), intent(inout) :: this
143 !! Instance of the 3D dropblock layer
144 real(real32), intent(in) :: rate
145 !! Drop rate
146 integer, intent(in) :: block_size
147 !! Block size
148 integer, optional, intent(in) :: verbose
149 !! Verbosity level
150
151 this%name = "dropblock3d"
152 this%type = "drop"
153 this%input_rank = 4
154 this%output_rank = 4
155
156 this%rate = rate
157 this%block_size = block_size
158 this%half = (this%block_size-1)/2
159
160 end subroutine set_hyperparams_dropblock3d
161 !###############################################################################
162
163
164 !###############################################################################
165 subroutine init_dropblock3d(this, input_shape, verbose)
166 !! Initialise 3D dropblock layer
167 implicit none
168
169 ! Arguments
170 class(dropblock3d_layer_type), intent(inout) :: this
171 !! Instance of the 3D dropblock layer
172 integer, dimension(:), intent(in) :: input_shape
173 !! Input shape
174 integer, optional, intent(in) :: verbose
175 !! Verbosity level
176
177 ! Local variables
178 integer :: verbose_ = 0
179 !! Verbosity level
180
181 !---------------------------------------------------------------------------
182 ! initialise optional arguments
183 !---------------------------------------------------------------------------
184 if(present(verbose)) verbose_ = verbose
185
186
187 !---------------------------------------------------------------------------
188 ! initialise input shape
189 !---------------------------------------------------------------------------
190 if(.not.allocated(this%input_shape)) call this%set_shape(input_shape)
191
192
193 !---------------------------------------------------------------------------
194 ! set up number of channels, width, height
195 !---------------------------------------------------------------------------
196 this%num_channels = this%input_shape(4)
197 allocate(this%output_shape(2))
198 this%output_shape = this%input_shape
199
200
201 !---------------------------------------------------------------------------
202 ! set gamma
203 !---------------------------------------------------------------------------
204 ! original paper uses keep_prob, we use drop_rate
205 ! drop_rate = 1 - keep_prob
206 this%gamma = ( this%rate/this%block_size**3._real32 ) * &
207 this%input_shape(1) / &
208 (this%input_shape(1) - this%block_size + 1._real32) * &
209 this%input_shape(2) / &
210 (this%input_shape(2) - this%block_size + 1._real32) * &
211 this%input_shape(3) / &
212 (this%input_shape(3) - this%block_size + 1._real32)
213 allocate(this%mask( &
214 this%input_shape(1), &
215 this%input_shape(2), &
216 this%input_shape(3)), source=.true.)
217
218
219 !---------------------------------------------------------------------------
220 ! generate mask
221 !---------------------------------------------------------------------------
222 call this%generate_mask()
223
224
225 !---------------------------------------------------------------------------
226 ! Allocate arrays
227 !---------------------------------------------------------------------------
228 if(this%use_graph_input)then
229 call stop_program( &
230 "Graph input not supported for 3D dropblock layer" &
231 )
232 return
233 end if
234 if(allocated(this%output)) deallocate(this%output)
235 allocate( this%output(1,1) )
236
237 end subroutine init_dropblock3d
238 !###############################################################################
239
240
241 !###############################################################################
242 subroutine generate_bernoulli_mask(this)
243 !! Generate Bernoulli mask
244 implicit none
245
246 ! Arguments
247 class(dropblock3d_layer_type), intent(inout) :: this
248 !! Instance of the 3D dropblock layer
249
250 ! Local variables
251 real(real32), allocatable, dimension(:,:,:) :: mask_real
252 !! Real mask
253 integer :: i, j, k
254 !! Loop indices
255 integer, dimension(2) :: ilim, jlim, klim
256 !! Limits for mask
257
258
259 ! Generate Bernoulli mask
260 !---------------------------------------------------------------------------
261 ! assume random number already seeded and don't need to again
262 allocate(mask_real(size(this%mask,1), size(this%mask,2), size(this%mask,3)))
263 call random_number(mask_real) ! Generate random values in [0..1]
264
265 this%mask = .true. ! 1 = keep
266
267 !! Apply threshold to create binary mask
268 !---------------------------------------------------------------------------
269 do k = 1 + this%half, size(this%mask, dim=3) - this%half
270 do j = 1 + this%half, size(this%mask, dim=2) - this%half
271 do i = 1 + this%half, size(this%mask, dim=1) - this%half
272 if(mask_real(i, j, k).lt.this%gamma)then
273 ilim(:) = [ &
274 max(i - this%half, lbound(this%mask,1)), &
275 min(i + this%half, ubound(this%mask,1)) ]
276 jlim(:) = [ &
277 max(j - this%half, lbound(this%mask,2)), &
278 min(j + this%half, ubound(this%mask,2)) ]
279 klim(:) = [ &
280 max(k - this%half, lbound(this%mask,3)), &
281 min(k + this%half, ubound(this%mask,3)) ]
282 this%mask( &
283 ilim(1):ilim(2), &
284 jlim(1):jlim(2), &
285 klim(1):klim(2)) = .false. ! 0 = drop
286 end if
287 end do
288 end do
289 end do
290
291 end subroutine generate_bernoulli_mask
292 !###############################################################################
293
294
295 !##############################################################################!
296 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
297 !##############################################################################!
298
299
300 !###############################################################################
301 subroutine print_to_unit_dropblock3d(this, unit)
302 !! Print 3D dropblock layer to unit
303 use coreutils, only: to_upper
304 implicit none
305
306 ! Arguments
307 class(dropblock3d_layer_type), intent(in) :: this
308 !! Instance of the 3D dropblock layer
309 integer, intent(in) :: unit
310 !! File unit
311
312
313 ! Write initial parameters
314 !---------------------------------------------------------------------------
315 write(unit,'(3X,"INPUT_SHAPE = ",4(1X,I0))') this%input_shape
316 write(unit,'(3X,"RATE = ",F0.9)') this%rate
317 write(unit,'(3X,"BLOCK_SIZE = ",I0)') this%block_size
318
319 end subroutine print_to_unit_dropblock3d
320 !###############################################################################
321
322
323 !###############################################################################
324 subroutine read_dropblock3d(this, unit, verbose)
325 !! Read 3D dropblock layer from file
326 use athena__tools_infile, only: assign_val, assign_vec
327 use coreutils, only: to_lower, to_upper, icount
328 implicit none
329
330 ! Arguments
331 class(dropblock3d_layer_type), intent(inout) :: this
332 !! Instance of the 3D dropblock layer
333 integer, intent(in) :: unit
334 !! File unit
335 integer, intent(in), optional :: verbose
336 !! Verbosity level
337
338 ! Local variables
339 integer :: stat, verbose_ = 0
340 !! File status and verbosity level
341 integer :: itmp1
342 !! Temporary integer
343 integer :: block_size
344 !! Block size
345 real(real32) :: rate
346 !! Drop rate
347 integer, dimension(4) :: input_shape
348 !! Input shape
349 character(256) :: buffer, tag, err_msg
350 !! Buffer, tag, and error message
351
352
353 ! Initialise optional arguments
354 !---------------------------------------------------------------------------
355 if(present(verbose)) verbose_ = verbose
356
357
358 ! Loop over tags in layer card
359 !---------------------------------------------------------------------------
360 tag_loop: do
361
362 ! Check for end of file
363 !------------------------------------------------------------------------
364 read(unit,'(A)',iostat=stat) buffer
365 if(stat.ne.0)then
366 write(err_msg,'("file encountered error (EoF?) before END ",A)') &
367 to_upper(this%name)
368 call stop_program(err_msg)
369 return
370 end if
371 if(trim(adjustl(buffer)).eq."") cycle tag_loop
372
373 ! Check for end of layer card
374 !------------------------------------------------------------------------
375 if(trim(adjustl(buffer)).eq."END "//to_upper(trim(this%name)))then
376 backspace(unit)
377 exit tag_loop
378 end if
379
380 tag=trim(adjustl(buffer))
381 if(scan(buffer,"=").ne.0) tag=trim(tag(:scan(tag,"=")-1))
382
383 ! Read parameters from save file
384 !------------------------------------------------------------------------
385 select case(trim(tag))
386 case("INPUT_SHAPE")
387 call assign_vec(buffer, input_shape, itmp1)
388 case("RATE")
389 call assign_val(buffer, rate, itmp1)
390 case("BLOCK_SIZE")
391 call assign_val(buffer, block_size, itmp1)
392 case default
393 ! Don't look for "e" due to scientific notation of numbers
394 ! ... i.e. exponent (E+00)
395 if(scan(to_lower(trim(adjustl(buffer))),&
396 'abcdfghijklmnopqrstuvwxyz').eq.0)then
397 cycle tag_loop
398 elseif(tag(:3).eq.'END')then
399 cycle tag_loop
400 end if
401 write(err_msg,'("Unrecognised line in input file: ",A)') &
402 trim(adjustl(buffer))
403 call stop_program(err_msg)
404 return
405 end select
406 end do tag_loop
407
408
409 ! Set hyperparameters and initialise layer
410 !---------------------------------------------------------------------------
411 call this%set_hyperparams( &
412 rate = rate, block_size = block_size, &
413 verbose = verbose_ &
414 )
415 call this%init(input_shape = input_shape)
416
417
418 ! Check for end of layer card
419 !---------------------------------------------------------------------------
420 read(unit,'(A)') buffer
421 if(trim(adjustl(buffer)).ne."END "//to_upper(trim(this%name)))then
422 write(0,*) trim(adjustl(buffer))
423 write(err_msg,'("END ",A," not where expected")') to_upper(this%name)
424 call stop_program(err_msg)
425 return
426 end if
427
428 end subroutine read_dropblock3d
429 !###############################################################################
430
431
432 !###############################################################################
433 function read_dropblock3d_layer(unit, verbose) result(layer)
434 !! Read 3D dropblock layer from file and return layer
435 implicit none
436 integer, intent(in) :: unit
437 !! File unit
438 integer, optional, intent(in) :: verbose
439 !! Verbosity level
440 class(base_layer_type), allocatable :: layer
441 !! Instance of the 3D dropblock layer
442
443 integer :: verbose_ = 0
444 !! Verbosity level
445
446 if(present(verbose)) verbose_ = verbose
447 allocate(layer, source=dropblock3d_layer_type(rate=0._real32, block_size=0))
448 call layer%read(unit, verbose=verbose_)
449
450 end function read_dropblock3d_layer
451 !###############################################################################
452
453
454 !##############################################################################!
455 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
456 !##############################################################################!
457
458
459 !###############################################################################
460 subroutine build_from_onnx_dropblock3d( &
461 this, node, initialisers, value_info, verbose &
462 )
463 !! Read ONNX attributes for 3D dropblock layer
464 implicit none
465
466 ! Arguments
467 class(dropblock3d_layer_type), intent(inout) :: this
468 !! Instance of the 3D dropblock layer
469 type(onnx_node_type), intent(in) :: node
470 !! ONNX node information
471 type(onnx_initialiser_type), dimension(:), intent(in) :: initialisers
472 !! ONNX initialiser information
473 type(onnx_tensor_type), dimension(:), intent(in) :: value_info
474 !! ONNX value info
475 integer, intent(in) :: verbose
476 !! Verbosity level
477
478 ! Local variables
479 integer :: i
480 !! Loop index
481 real(real32) :: rate
482 !! Dropout rate
483 integer :: block_size
484 !! Block size
485 character(256) :: val
486 !! Attribute value
487
488 ! Set default values
489 rate = 0.1_real32
490 block_size = 7
491
492 ! Parse ONNX attributes
493 do i = 1, size(node%attributes)
494 val = node%attributes(i)%val
495 select case(trim(adjustl(node%attributes(i)%name)))
496 case("drop_prob")
497 read(val,*) rate
498 case("block_size")
499 read(val,*) block_size
500 case default
501 ! Do nothing
502 write(0,*) "WARNING: Unrecognised attribute in ONNX &
503 &DROPBLOCK3D layer: ", trim(adjustl(node%attributes(i)%name))
504 end select
505 end do
506
507 ! Check size of initialisers is zero
508 if(size(initialisers).ne.0)then
509 write(0,*) "WARNING: initialisers not used for ONNX DROPBLOCK3D layer"
510 end if
511
512 call this%set_hyperparams( &
513 rate = rate, &
514 block_size = block_size, &
515 verbose = verbose &
516 )
517
518 end subroutine build_from_onnx_dropblock3d
519 !###############################################################################
520
521
522 !##############################################################################!
523 ! * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * !
524 !##############################################################################!
525
526
527 !###############################################################################
528 subroutine forward_dropblock3d(this, input)
529 !! Forward propagation
530 implicit none
531
532 ! Arguments
533 class(dropblock3d_layer_type), intent(inout) :: this
534 !! Instance of the 3D dropblock layer
535 class(array_type), dimension(:,:), intent(in) :: input
536 !! Input values
537
538 ! Local variables
539 real(real32) :: rtmp1
540 !! Temporary variable
541 type(array_type), pointer :: ptr
542 !! Pointer array
543
544
545 rtmp1 = 1._real32 - this%rate
546 select case(this%inference)
547 case(.true.)
548 ! Do not perform the drop operation
549 ptr => input(1,1) * rtmp1
550 case default
551 ! Perform the drop operation
552 rtmp1 = 1._real32 / rtmp1
553 ptr => merge_over_channels( &
554 input(1,1), 0._real32, &
555 reshape(this%mask, shape = [product(shape(this%mask)), 1]) &
556 ) * rtmp1
557 end select
558 call this%output(1,1)%assign_and_deallocate_source(ptr)
559 this%output(1,1)%is_temporary = .false.
560
561 end subroutine forward_dropblock3d
562 !###############################################################################
563
564 end module athena__dropblock3d_layer
565