GCC Code Coverage Report


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