• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

eT-program / eT / 25045

22 Jan 2026 12:06AM UTC coverage: 87.716% (-0.3%) from 88.059%
25045

push

gitlab-ci

Merge branch 'hotfix-coverage-tested' into 'master'

Attempt to fix coverage pipeline

See merge request eT-program/eT!1604

53441 of 60925 relevant lines covered (87.72%)

3252742.36 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

75.26
/src/memory/memory_manager_class.F90
1

2
! eT - a coupled cluster program
3
! Copyright (C) 2016-2025 the authors of eT
4
!
5
! eT is free software: you can redistribute it and/or modify
6
! it under the terms of the GNU General Public License as published by
7
! the Free Software Foundation, either version 3 of the License, or
8
! (at your option) any later version.
9
!
10
! eT is distributed in the hope that it will be useful,
11
! but WITHOUT ANY WARRANTY; without even the implied warranty of
12
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
13
! GNU General Public License for more details.
14
!
15
! You should have received a copy of the GNU General Public License
16
! along with this program. If not, see <https://www.gnu.org/licenses/>.
17

18

19
module memory_manager_class
20

21
   !!
22
   !! Memory manager class module
23
   !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Dec 2017
24
   !!
25
   !! The memory manager class handles the memory used by the model calculation,
26
   !! and there is an object called 'mem' in the wavefunction object of this class.
27
   !!
28
   !! To account for the available memory, all large arrays must be allocated and deallocated
29
   !! using the memory manager. A typical usage of the 'mem' object is as follows:
30
   !!
31
   !!    real(dp), dimension(:,:), allocatable :: array -> declares an allocatable array
32
   !!
33
   !!    call mem%alloc(array, M, N)   -> allocates the array of dimension M x N
34
   !!
35
   !!    ... Do stuff with the array
36
   !!
37
   !!    call mem%dealloc(array, M, N) -> deallocates the array of dimension M x N
38
   !!
39
   !! Analogous calls are made to make one, three and four dimensional tensors as well,
40
   !! e.g. call mem%alloc(X, M, N, K) for an M x N x K tensor.
41
   !!
42
   !! Note: Large arrays MUST always be allocated using the memory manager object. Small arrays,
43
   !! integers, strings, etc., which use a negligible amount of memory, do not have to pass
44
   !! through the memory manager.
45
   !!
46
   !! The 'alloc' and 'dealloc' routines allow the memory manager keep track of the
47
   !! the memory available at a given time. From the specified total memory, the class
48
   !! can then set the batching information for a batching index (see the batching
49
   !! index class) or set of such indices (see the batch_setup routines below).
50
   !!
51

52
   use parameters
53
   use global_out,           only: output
54
   use batching_index_class, only: batching_index
55
   use memory_tracker_class, only: memory_tracker
56
   use array_initialization, only: zero_array, zero_array_complex
57
   use array_initialization, only: zero_array_int, zero_array_int32, zero_array_int64
58

59
   ! Debug option:
60
   ! Require that batch setup always gives batching
61

62
#ifdef _FORCED_BATCHING
63
   logical, parameter, private :: force_batch = .true.
64
#else
65
   logical, parameter, private :: force_batch = .false.
66
#endif
67

68
   ! Class definition
69

70
   type :: memory_manager
71

72
      ! The total amount of memory specified by user (standard: 8 GB)
73

74
      integer(i64), private :: total
75

76
      ! The amount of memory currently available, based on the arrays currently allocated
77
      ! (memory used by objects and local variables are not included in this estimate)
78

79
      integer(i64), private :: available
80

81
      ! Maximum amount of memory used at the same time
82

83
      integer(i64), private :: max_used
84

85
      ! Unit for memory, default is GB
86

87
      character(len=2), private :: units
88

89
      ! Batch memory tracking
90

91
      logical, private :: batching_on
92
      type(memory_tracker), allocatable :: batch_mem_tracker
93

94
   contains
95

96
      ! Check if there are memory leaks - on exit of program
97

98
      procedure, public :: check_for_leak => check_for_leak_memory_manager
99

100
      ! Printing
101

102
      procedure, public :: print_settings  => print_settings_memory_manager
103
      procedure, public :: print_max_used  => print_max_used_memory_manager
104
      procedure, public :: print_available => print_available_memory_manager
105

106
      procedure, public :: get_available   => get_available_memory_manager
107

108
      procedure, nopass, public :: get_memory_as_character &
109
                                => get_memory_as_character_memory_manager
110

111
      ! Routines for batching
112

113
      generic, public :: batch_setup => batch_setup_1, &
114
                                        batch_setup_2, &
115
                                        batch_setup_3
116

117
      procedure, public :: batch_finalize &
118
                        => batch_finalize_memory_manager
119

120
      ! Allocation and deallocation routines for arrays
121

122
      generic, public :: alloc => alloc_r_1,       &
123
                                  alloc_r_2,       &
124
                                  alloc_r_3,       &
125
                                  alloc_r_4,       &
126
                                  alloc_r_5,       &
127
                                  alloc_r_6,       &
128
                                  alloc_c_1,       &
129
                                  alloc_c_2,       &
130
                                  alloc_c_3,       &
131
                                  alloc_c_4,       &
132
                                  alloc_i64_1,     &
133
                                  alloc_i64_2,     &
134
                                  alloc_i64_3,     &
135
                                  alloc_i32_1,     &
136
                                  alloc_i32_2,     &
137
                                  alloc_i32_3,     &
138
                                  alloc_l_1,       &
139
                                  alloc_l_2,       &
140
                                  alloc_i_2_ranges
141

142
      generic, public :: dealloc => dealloc_real,           &
143
                                    dealloc_complex,        &
144
                                    dealloc_64bit_integer,  &
145
                                    dealloc_32bit_integer,  &
146
                                    dealloc_logical,        &
147
                                    dealloc_char
148

149

150
      procedure, private :: alloc_r_1
151
      procedure, private :: alloc_r_2
152
      procedure, private :: alloc_r_3
153
      procedure, private :: alloc_r_4
154
      procedure, private :: alloc_r_5
155
      procedure, private :: alloc_r_6
156
      procedure, private :: alloc_c_1
157
      procedure, private :: alloc_c_2
158
      procedure, private :: alloc_c_3
159
      procedure, private :: alloc_c_4
160
      procedure, private :: alloc_i64_1
161
      procedure, private :: alloc_i64_2
162
      procedure, private :: alloc_i64_3
163
      procedure, private :: alloc_i32_1
164
      procedure, private :: alloc_i32_2
165
      procedure, private :: alloc_i32_3
166
      procedure, private :: alloc_l_1
167
      procedure, private :: alloc_l_2
168
      procedure, private :: alloc_i_2_ranges
169

170
      procedure, private :: dealloc_real
171
      procedure, private :: dealloc_complex
172
      procedure, private :: dealloc_64bit_integer
173
      procedure, private :: dealloc_32bit_integer
174
      procedure, private :: dealloc_logical
175
      procedure, private :: dealloc_char
176

177
      procedure, private :: batch_setup_1
178
      procedure, private :: batch_setup_2
179
      procedure, private :: batch_setup_3
180

181
      procedure, private :: initialize_batching_tracker
182

183
      procedure, private :: update_memory_after_alloc
184
      procedure, private :: update_memory_after_dealloc
185

186
      procedure, nopass, private :: print_allocation_error
187
      procedure, nopass, private :: print_deallocation_error
188

189
   end type memory_manager
190

191

192
   interface memory_manager
193

194
      procedure :: new_memory_manager
195

196
   end interface memory_manager
197

198
   ! Main memory object
199

200
   type(memory_manager) :: mem
201

202
contains
203

204

205
   function new_memory_manager(total, units) result(mem)
3,182✔
206
      !!
207
      !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Dec 2017
208
      !!
209
      !! Creates the memory manager object and sets the
210
      !! total and initial available memory.
211
      !!
212
      implicit none
213

214
      type(memory_manager) :: mem
215

216
      integer(i64), intent(in) :: total
217

218
      character(len=*), intent(in) :: units
219

220
      ! Set standard and read settings
221
      !
222
      ! Default is 8 GB
223

224
      mem%total = total
3,182✔
225
      mem%units = trim(units)
3,182✔
226

227
      ! Convert from current unit to B
228

229
      if (mem%units == 'gb') then
3,182✔
230

231
         mem%total =  mem%total*1000000000
3,164✔
232

233
      elseif (mem%units == 'mb') then
18✔
234

235
         mem%total =  mem%total*1000000
6✔
236

237
      elseif (mem%units == 'kb') then
12✔
238

239
         mem%total =  mem%total*1000
6✔
240

241
      elseif (trim(mem%units) == 'b') then
6✔
242

243
         ! Do nothing
244

245
      else
246

247
         call output%error_msg('did not recognize the memory unit specified in input')
×
248

249
      endif
250

251
      mem%available = mem%total
3,182✔
252
      mem%max_used = mem%total - mem%available
3,182✔
253

254
      mem%batching_on = .false.
3,182✔
255

256
      call mem%print_settings()
3,182✔
257

258
   end function new_memory_manager
3,182✔
259

260

261
   subroutine check_for_leak_memory_manager(mem)
3,152✔
262
      !!
263
      !! Written by Eirik F. Kjønstad, Apr 2019
264
      !!
265
      !! Issues a warning if there has been a leak since the
266
      !! the memory manager was prepared. Should only be called
267
      !! at the end of the program, when all arrays that were
268
      !! allocated since mem%prepare() should have been deallocated.
269
      !!
270
      implicit none
271

272
      class(memory_manager), intent(in) :: mem
273

274
      character(len=200) :: difference_string
275

276
      if (mem%available .ne. mem%total) then
3,152✔
277

278
         call output%printf('m', 'Mismatch in memory according to eT and &
279
                            &specified on input:', fs='(/t3,a)')
×
280

281
         call output%printf('m', 'Memory available (eT):    (a0)', &
282
                            chars=[mem%get_memory_as_character(mem%available,.true.)], fs='(/t6,a)')
×
283

284
         call output%printf('m', 'Memory available (input): (a0)', &
285
                            chars=[mem%get_memory_as_character(mem%total,.true.)], fs='(t6,a)')
×
286

287

288
         difference_string = mem%get_memory_as_character(mem%total-mem%available,.true.)
×
289
         call output%printf('m', 'Difference:               (a0)', &
290
                            chars=[trim(difference_string)], fs='(t6,a)')
×
291

292
         call output%error_msg('Deallocations are missing or specified with &
293
                                 &incorrect dimensionalities.')
×
294

295
      endif
296

297
   end subroutine check_for_leak_memory_manager
3,152✔
298

299

300
   pure function get_available_memory_manager(mem) result(memory)
139,387✔
301
      !!
302
      !! Get available
303
      !! Written by Eirik F. Kjønstad, Jan 2019
304
      !!
305
      implicit none
306

307
      class(memory_manager), intent(in) :: mem
308

309
      integer(i64) :: memory
310

311
      memory = mem%available
139,387✔
312

313
   end function get_available_memory_manager
139,387✔
314

315

316
   pure function get_memory_as_character_memory_manager(input_mem, all_digits) result(memory)
9,486✔
317
      !!
318
      !! Get available memory as character
319
      !! Written by Alexander C. Paul, Oct 2019
320
      !!
321
      !! Receives an 8 byte integer containing the memory in byte.
322
      !! Returns character containing the same the number with a reasonable unit
323
      !!
324
      !! If all_digits is .true. the full memory is returned in bytes
325
      !!
326
      implicit none
327

328
      integer(i64), intent(in) :: input_mem
329

330
      logical, intent(in), optional :: all_digits
331

332
      character(len=17) :: memory
333

334
      logical :: all_digits_local
335

336
      ! Print all digits? (i.e. give memory in B)
337

338
      all_digits_local = .false.
339
      if (present(all_digits)) all_digits_local = all_digits
9,486✔
340

341
      if (all_digits_local) then
×
342

343
         write(memory,'(i0, a)') input_mem, ' B'
×
344
         memory = trim(adjustl(memory))
×
345

346
      else if (abs(input_mem) .lt. 1d6) then
9,486✔
347

348
         write(memory,'(f10.3, a)') dble(input_mem)/1.0d3, ' KB'
2,252✔
349
         memory = trim(adjustl(memory))
2,252✔
350

351
      else if (abs(input_mem) .lt. 1d9) then
7,234✔
352

353
         write(memory,'(f10.6, a)') dble(input_mem)/1.0d6, ' MB'
4,058✔
354
         memory = trim(adjustl(memory))
4,058✔
355

356
      else if (abs(input_mem) .lt. 1d12) then
3,176✔
357

358
         write(memory,'(f10.6, a)') dble(input_mem)/1.0d9, ' GB'
3,176✔
359
         memory = trim(adjustl(memory))
3,176✔
360

361
      else if (abs(input_mem) .lt. 1d15) then
×
362

363
         write(memory,'(f13.6, a)') dble(input_mem)/1.0d12, ' TB'
×
364
         memory = trim(adjustl(memory))
×
365

366
      end if
367

368
   end function get_memory_as_character_memory_manager
9,486✔
369

370

371
   subroutine print_available_memory_manager(mem)
×
372
      !!
373
      !! Written by Eirik F. Kjønstad, Jan 2019
374
      !!
375
      implicit none
376

377
      class(memory_manager), intent(in) :: mem
378

379
      call output%printf('m', 'Currently available memory: (a0)', &
380
                         chars=[mem%get_memory_as_character(mem%available, .true.)])
×
381

382
   end subroutine print_available_memory_manager
×
383

384

385
   subroutine print_max_used_memory_manager(mem)
3,152✔
386
      !!
387
      !! Written by Alexander C. Paul, May 2020
388
      !!
389
      implicit none
390

391
      class(memory_manager), intent(in) :: mem
392

393
      call output%printf('n', 'Peak memory usage during the execution of eT: (a0)', &
394
                         chars=[mem%get_memory_as_character(mem%max_used)], fs='(/t3,a)')
6,304✔
395

396
   end subroutine print_max_used_memory_manager
3,152✔
397

398

399
   subroutine initialize_memory_real(array, N)
169,350,688✔
400
      !!
401
      !! Written by Marcus T. Lexander, 2023
402
      !!
403
      use, intrinsic :: ieee_arithmetic, only: IEEE_Value, IEEE_QUIET_NAN
404
      use warning_suppressor, only: do_nothing
405

406
      implicit none
407

408
      integer, intent(in) :: N
409

410
      real(dp), dimension(N), intent(inout) :: array
411

412
      real(dp) :: nan
413

414
#ifdef INITIALIZE_NAN
415
      nan = IEEE_Value(nan, IEEE_QUIET_NAN)
416

417
      call dscal(N, nan, array, 1)
418
#else
419
      call do_nothing(array)
84,675,344✔
420
      call do_nothing(nan)
84,675,344✔
421
#endif
422

423
   end subroutine initialize_memory_real
84,675,344✔
424

425

426
   subroutine initialize_memory_complex(array, N)
3,486,128✔
427
      !!
428
      !! Written by Marcus T. Lexander, 2023
429
      !!
430
      use, intrinsic :: ieee_arithmetic, only: IEEE_Value, IEEE_QUIET_NAN
84,675,344✔
431
      use warning_suppressor, only: do_nothing
432

433
      implicit none
434

435
      integer, intent(in) :: N
436

437
      complex(dp), dimension(N), intent(inout) :: array
438

439
      real(dp) :: nan
440

441
#ifdef INITIALIZE_NAN
442
      nan = IEEE_Value(nan, IEEE_QUIET_NAN)
443

444
      call zscal(N, cmplx(nan, nan, dp), array, 1)
445
#else
446
      call do_nothing(array)
1,743,064✔
447
      call do_nothing(nan)
1,743,064✔
448
#endif
449

450
   end subroutine initialize_memory_complex
1,743,064✔
451

452

453
   subroutine alloc_r_1(mem, array, M, set_zero)
6,605,748✔
454
      !!
455
      !! Written by Rolf H. Myhre, January 2019
456
      !!
457
      !! Allocates a one dimensional double precision array and updates the available
458
      !! memory accordingly.
459
      !!
460
      !! set_zero: optional initialize array to zero
461
      !!
462
      implicit none
463

464
      class(memory_manager) :: mem
465

466
      real(dp), dimension(:), allocatable :: array
467
      logical, intent(in), optional :: set_zero
468

469
      integer, intent(in) :: M ! Dimension of array that is being allocated
470

471
      integer(i64) :: size_array ! Total size of array (M)
472
      integer :: error = 0
473
      logical :: set_zero_ = .false.
474

475
      character(len=100) :: error_msg
476

477
      size_array = M
6,605,748✔
478

479
      allocate(array(M), stat=error, errmsg=error_msg)
11,055,448✔
480

481
      if (error .ne. 0) call mem%print_allocation_error(size_array, error_msg)
6,605,748✔
482

483
      call initialize_memory_real(array, int(size_array))
6,605,748✔
484

485
      if (present(set_zero)) set_zero_ = set_zero
6,605,748✔
486
      if (set_zero_) call zero_array(array, int(size_array))
6,605,748✔
487

488
      call mem%update_memory_after_alloc(size_array, dp)
6,605,748✔
489

490
   end subroutine alloc_r_1
1,743,064✔
491

492

493
   subroutine alloc_r_2(mem, array, M, N, set_zero)
24,872,658✔
494
      !!
495
      !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Dec 2017
496
      !!
497
      !! Allocates a two dimensional double precision array and updates the available
498
      !! memory accordingly.
499
      !!
500
      !! set_zero: optional initialize array to zero
501
      !!
502
      implicit none
503

504
      class(memory_manager) :: mem
505

506
      real(dp), dimension(:,:), allocatable :: array
507
      logical, intent(in), optional :: set_zero
508

509
      integer, intent(in) :: M, N ! First and second dimension of array that is being allocated
510

511
      integer(i64) :: size_array ! Total size of array (M*N)
512
      integer :: error = 0
513
      logical :: set_zero_ = .false.
514

515
      character(len=100) :: error_msg
516

517
      size_array = M*N
24,872,658✔
518

519
      allocate(array(M,N), stat=error, errmsg=error_msg)
66,416,911✔
520

521
      if (error .ne. 0) then
24,872,658✔
522
         call mem%print_allocation_error(size_array, error_msg)
×
523
      endif
524

525
      call initialize_memory_real(array, int(size_array))
24,872,658✔
526

527
      if (present(set_zero)) set_zero_ = set_zero
24,872,658✔
528
      if (set_zero_) call zero_array(array, int(size_array))
24,872,658✔
529

530
      call mem%update_memory_after_alloc(size_array, dp)
24,872,658✔
531

532
   end subroutine alloc_r_2
24,872,658✔
533

534

535
   subroutine alloc_r_3(mem, array, M, N, O, set_zero)
29,318,752✔
536
      !!
537
      !! Written by Rolf H. Myhre, January 2019
538
      !!
539
      !! Allocates a three dimensional double precision array and updates the available
540
      !! memory accordingly.
541
      !!
542
      !! set_zero: optional initialize array to zero
543
      !!
544
      implicit none
545

546
      class(memory_manager) :: mem
547

548
      real(dp), dimension(:,:,:), allocatable :: array
549
      logical, intent(in), optional :: set_zero
550

551
      integer, intent(in) :: M, N, O ! First, second and third dimension of array
552

553
      integer(i64) :: size_array ! Total size of array (M*N*O)
554
      integer :: error = 0
555
      logical :: set_zero_ = .false.
556

557
      character(len=100) :: error_msg
558

559
      size_array = M*N*O
29,318,752✔
560

561
      allocate(array(M,N,O), stat=error, errmsg=error_msg)
107,644,777✔
562

563
      if (error .ne. 0) then
29,318,752✔
564
         call mem%print_allocation_error(size_array, error_msg)
×
565
      endif
566

567
      call initialize_memory_real(array, int(size_array))
29,318,752✔
568

569
      if (present(set_zero)) set_zero_ = set_zero
29,318,752✔
570
      if (set_zero_) call zero_array(array, int(size_array))
29,318,752✔
571

572
      call mem%update_memory_after_alloc(size_array, dp)
29,318,752✔
573

574
   end subroutine alloc_r_3
29,318,752✔
575

576

577
   subroutine alloc_r_4(mem, array, M, N, O, P, set_zero)
23,477,147✔
578
      !!
579
      !! Written by Rolf H. Myhre, January 2019
580
      !!
581
      !! Allocates a four dimensional double precision array and updates the available
582
      !! memory accordingly.
583
      !!
584
      !! set_zero: optional initialize array to zero
585
      !!
586
      implicit none
587

588
      class(memory_manager) :: mem
589

590
      real(dp), dimension(:,:,:,:), allocatable :: array
591
      logical, intent(in), optional :: set_zero
592

593
      integer, intent(in) :: M, N, O, P ! First, second, third and fourth dimension of array
594

595
      integer(i64) :: size_array ! Total size of array (M*N*O*P)
596
      integer :: error = 0
597
      logical :: set_zero_ = .false.
598

599
      character(len=100) :: error_msg
600

601
      size_array = M*N*O*P
23,477,147✔
602

603
      allocate(array(M,N,O,P), stat=error, errmsg=error_msg)
109,571,284✔
604

605
      if (error .ne. 0) then
23,477,147✔
606
         call mem%print_allocation_error(size_array, error_msg)
×
607
      endif
608

609
      call initialize_memory_real(array, int(size_array))
23,477,147✔
610

611
      if (present(set_zero)) set_zero_ = set_zero
23,477,147✔
612
      if (set_zero_) call zero_array(array, int(size_array))
23,477,147✔
613

614
      call mem%update_memory_after_alloc(size_array, dp)
23,477,147✔
615

616
   end subroutine alloc_r_4
23,477,147✔
617

618

619
   subroutine alloc_r_5(mem, array, M, N, O, P, Q, set_zero)
12,155✔
620
      !!
621
      !! Written by Rolf H. Myhre, January 2019
622
      !!
623
      !! Allocates a five dimensional double precision array and updates the available
624
      !! memory accordingly.
625
      !!
626
      !! set_zero: optional initialize array to zero
627
      !!
628
      implicit none
629

630
      class(memory_manager) :: mem
631

632
      real(dp), dimension(:,:,:,:,:), allocatable :: array
633
      logical, intent(in), optional :: set_zero
634

635
      integer, intent(in) :: M, N, O, P, Q ! First, second, third, fourth, fifth dimension of array
636

637
      integer(i64) :: size_array ! Total size of array (M*N*O*P*Q)
638
      integer :: error = 0
639
      logical :: set_zero_ = .false.
640

641
      character(len=100) :: error_msg
642

643
      size_array = M*N*O*P*Q
12,155✔
644

645
      allocate(array(M,N,O,P,Q), stat=error, errmsg=error_msg)
69,102✔
646

647
      if (error .ne. 0) then
12,155✔
648
         call mem%print_allocation_error(size_array, error_msg)
×
649
      endif
650

651
      call initialize_memory_real(array, int(size_array))
12,155✔
652

653
      if (present(set_zero)) set_zero_ = set_zero
12,155✔
654
      if (set_zero_) call zero_array(array, int(size_array))
12,155✔
655

656
      call mem%update_memory_after_alloc(size_array, dp)
12,155✔
657

658
   end subroutine alloc_r_5
12,155✔
659

660

661
   subroutine alloc_r_6(mem, array, M, N, O, P, Q, R, set_zero)
388,884✔
662
      !!
663
      !! Alloc (memory manager)
664
      !! Written by Rolf H. Myhre, January 2019
665
      !!
666
      !! Allocates a six dimensional double precision array and updates the available
667
      !! memory accordingly.
668
      !!
669
      !! set_zero: optional initialize array to zero
670
      !!
671
      implicit none
672

673
      class(memory_manager) :: mem
674

675
      real(dp), dimension(:,:,:,:,:,:), allocatable :: array
676
      logical, intent(in), optional :: set_zero
677

678
      integer, intent(in) :: M, N, O, P, Q, R ! First, second, third, fourth, fifth, sixth dimension of array
679

680
      integer(i64) :: size_array ! Total size of array (M*N*O*P*Q)
681
      integer :: error = 0
682
      logical :: set_zero_ = .false.
683

684
      character(len=100) :: error_msg
685

686
      size_array = M*N*O*P*Q*R
388,884✔
687

688
      allocate(array(M,N,O,P,Q,R), stat=error, errmsg=error_msg)
2,592,560✔
689

690
      if (error .ne. 0) then
388,884✔
691
         call mem%print_allocation_error(size_array, error_msg)
×
692
      endif
693

694
      call initialize_memory_real(array, int(size_array))
388,884✔
695

696
      if (present(set_zero)) set_zero_ = set_zero
388,884✔
697
      if (set_zero_) call zero_array(array, int(size_array))
388,884✔
698

699
      call mem%update_memory_after_alloc(size_array, dp)
388,884✔
700

701
   end subroutine alloc_r_6
388,884✔
702

703

704
   subroutine alloc_c_1(mem, array, M, set_zero)
123,164✔
705
      !!
706
      !! Written by Rolf H. Myhre, January 2019
707
      !!
708
      !! Allocates a one dimensional double precision array and updates the available
709
      !! memory accordingly.
710
      !!
711
      !! set_zero: optional initialize array to zero
712
      !!
713
      implicit none
714

715
      class(memory_manager) :: mem
716

717
      complex(dp), dimension(:), allocatable :: array
718
      logical, intent(in), optional :: set_zero
719

720
      integer, intent(in) :: M ! Dimension of array that is being allocated
721

722
      integer(i64) :: size_array ! Total size of array (M)
723
      integer :: error = 0
724
      logical :: set_zero_ = .false.
725

726
      character(len=100) :: error_msg
727

728
      size_array = M
123,164✔
729

730
      allocate(array(M), stat=error, errmsg=error_msg)
205,416✔
731

732
      if (error .ne. 0) then
123,164✔
733
         call mem%print_allocation_error(size_array, error_msg)
×
734
      endif
735

736
      call initialize_memory_complex(array, int(size_array))
123,164✔
737

738
      if (present(set_zero)) set_zero_ = set_zero
123,164✔
739
      if (set_zero_) call zero_array_complex(array, int(size_array))
123,164✔
740

741
      call mem%update_memory_after_alloc(size_array, 2*dp)
123,164✔
742

743
   end subroutine alloc_c_1
123,164✔
744

745

746
   subroutine alloc_c_2(mem, array, M, N, set_zero)
290,526✔
747
      !!
748
      !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Dec 2017
749
      !!
750
      !! Allocates a two dimensional double precision array and updates the available
751
      !! memory accordingly.
752
      !!
753
      !! set_zero: optional initialize array to zero
754
      !!
755
      implicit none
756

757
      class(memory_manager) :: mem
758

759
      complex(dp), dimension(:,:), allocatable :: array
760
      logical, intent(in), optional :: set_zero
761

762
      integer, intent(in) :: M, N ! First and second dimension of array that is being allocated
763

764
      integer(i64) :: size_array ! Total size of array (M*N)
765
      integer :: error = 0
766
      logical :: set_zero_ = .false.
767

768
      character(len=100) :: error_msg
769

770
      size_array = M*N
290,526✔
771

772
      allocate(array(M,N), stat=error, errmsg=error_msg)
774,853✔
773

774
      if (error .ne. 0) then
290,526✔
775
         call mem%print_allocation_error(size_array, error_msg)
×
776
      endif
777

778
      call initialize_memory_complex(array, int(size_array))
290,526✔
779

780
      if (present(set_zero)) set_zero_ = set_zero
290,526✔
781
      if (set_zero_) call zero_array_complex(array, int(size_array))
290,526✔
782

783
      call mem%update_memory_after_alloc(size_array, 2*dp)
290,526✔
784

785
   end subroutine alloc_c_2
290,526✔
786

787

788
   subroutine alloc_c_3(mem, array, M, N, O, set_zero)
712,908✔
789
      !!
790
      !! Written by Rolf H. Myhre, January 2019
791
      !!
792
      !! Allocates a three dimensional double precision array and updates the available
793
      !! memory accordingly.
794
      !!
795
      !! set_zero: optional initialize array to zero
796
      !!
797
      implicit none
798

799
      class(memory_manager) :: mem
800

801
      complex(dp), dimension(:,:,:), allocatable :: array
802

803
      integer, intent(in) :: M, N, O ! First, second and third dimension of array
804
      logical, intent(in), optional :: set_zero
805

806
      integer(i64) :: size_array ! Total size of array (M*N*O)
807
      integer :: error = 0
808
      logical :: set_zero_ = .false.
809

810
      character(len=100) :: error_msg
811

812
      size_array = M*N*O
712,908✔
813

814
      allocate(array(M,N,O), stat=error, errmsg=error_msg)
2,614,071✔
815

816
      if (error .ne. 0) then
712,908✔
817
         call mem%print_allocation_error(size_array, error_msg)
×
818
      endif
819

820
      call initialize_memory_complex(array, int(size_array))
712,908✔
821

822
      if (present(set_zero)) set_zero_ = set_zero
712,908✔
823
      if (set_zero_) call zero_array_complex(array, int(size_array))
712,908✔
824

825
      call mem%update_memory_after_alloc(size_array, 2*dp)
712,908✔
826

827
   end subroutine alloc_c_3
712,908✔
828

829

830
   subroutine alloc_c_4(mem, array, M, N, O, P, set_zero)
616,466✔
831
      !!
832
      !! Written by Rolf H. Myhre, January 2019
833
      !!
834
      !! Allocates a four dimensional double precision array and updates the available
835
      !! memory accordingly.
836
      !!
837
      !! set_zero: optional initialize array to zero
838
      !!
839
      implicit none
840

841
      class(memory_manager) :: mem
842

843
      complex(dp), dimension(:,:,:,:), allocatable :: array
844
      logical, intent(in), optional :: set_zero
845

846
      integer, intent(in) :: M, N, O, P ! First, second, third and fourth dimension of array
847

848
      integer(i64) :: size_array ! Total size of array (M*N*O*P)
849
      integer :: error = 0
850
      logical :: set_zero_ = .false.
851

852
      character(len=100) :: error_msg
853

854
      size_array = M*N*O*P
616,466✔
855

856
      allocate(array(M,N,O,P), stat=error, errmsg=error_msg)
2,877,171✔
857

858
      if (error .ne. 0) then
616,466✔
859
         call mem%print_allocation_error(size_array, error_msg)
×
860
      endif
861

862
      call initialize_memory_complex(array, int(size_array))
616,466✔
863

864
      if (present(set_zero)) set_zero_ = set_zero
616,466✔
865
      if (set_zero_) call zero_array_complex(array, int(size_array))
616,466✔
866

867
      call mem%update_memory_after_alloc(size_array, 2*dp)
616,466✔
868

869
   end subroutine alloc_c_4
616,466✔
870

871

872
   subroutine alloc_i64_1(mem, array, M, set_zero)
1,712,595✔
873
      !!
874
      !! Written by Rolf H. Myhre, January 2019
875
      !!
876
      !! Allocates a one dimensional integer array and updates the available
877
      !! memory accordingly.
878
      !!
879
      !! set_zero: optional initialize array to zero
880
      !!
881
      implicit none
882

883
      class(memory_manager) :: mem
884

885
      integer(i64), dimension(:), allocatable :: array
886
      logical, intent(in), optional :: set_zero
887

888
      integer, intent(in) :: M ! Dimension of array
889

890
      integer(i64) :: size_array ! Total size of array (M)
891
      integer :: error = 0
892
      logical :: set_zero_ = .false.
893

894
      character(len=100) :: error_msg
895

896
      size_array = M
1,712,595✔
897

898
      allocate(array(M), stat=error, errmsg=error_msg)
3,425,190✔
899

900
      if (error .ne. 0) then
1,712,595✔
901
         call mem%print_allocation_error(size_array, error_msg)
×
902
      endif
903

904
      if (present(set_zero)) set_zero_ = set_zero
1,712,595✔
905
      if (set_zero_) call zero_array_int64(array, int(size_array))
1,712,595✔
906

907
      call mem%update_memory_after_alloc(size_array, 8)
1,712,595✔
908

909
   end subroutine alloc_i64_1
1,712,595✔
910

911

912
   subroutine alloc_i64_2(mem, array, M, N, set_zero)
375,526✔
913
      !!
914
      !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Dec 2017
915
      !!
916
      !! Allocates a two dimensional integer array and updates the available
917
      !! memory accordingly.
918
      !!
919
      !! set_zero: optional initialize array to zero
920
      !!
921
      implicit none
922

923
      class(memory_manager) :: mem
924

925
      integer(i64), dimension(:,:), allocatable :: array
926
      logical, intent(in), optional :: set_zero
927

928
      integer, intent(in) :: M, N ! First and second dimension of array
929

930
      integer(i64) :: size_array ! Total size of array (M*N)
931
      integer :: error = 0
932
      logical :: set_zero_ = .false.
933

934
      character(len=100) :: error_msg
935

936
      size_array = M*N
375,526✔
937

938
      allocate(array(M,N), stat=error, errmsg=error_msg)
1,126,578✔
939

940
      if (error .ne. 0) then
375,526✔
941
         call mem%print_allocation_error(size_array, error_msg)
×
942
      endif
943

944
      if (present(set_zero)) set_zero_ = set_zero
375,526✔
945
      if (set_zero_) call zero_array_int64(array, int(size_array))
375,526✔
946

947
      call mem%update_memory_after_alloc(size_array, 8)
375,526✔
948

949
   end subroutine alloc_i64_2
375,526✔
950

951

952
   subroutine alloc_i64_3(mem, array, M, N, K, set_zero)
480✔
953
      !!
954
      !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Dec 2017
955
      !!
956
      !! Allocates a three dimensional integer array and updates the available
957
      !! memory accordingly.
958
      !!
959
      !! set_zero: optional initialize array to zero
960
      !!
961
      implicit none
962

963
      class(memory_manager) :: mem
964

965
      integer(i64), dimension(:,:,:), allocatable :: array
966
      logical, intent(in), optional :: set_zero
967

968
      integer, intent(in) :: M, N, K ! First and second dimension of array
969

970
      integer(i64) :: size_array ! Total size of array (M*N*K)
971
      integer :: error = 0
972
      logical :: set_zero_ = .false.
973

974
      character(len=100) :: error_msg
975

976
      size_array = M*N*K
480✔
977

978
      allocate(array(M,N,K), stat=error, errmsg=error_msg)
1,920✔
979

980
      if (error .ne. 0) then
480✔
981
         call mem%print_allocation_error(size_array, error_msg)
×
982
      endif
983

984
      if (present(set_zero)) set_zero_ = set_zero
480✔
985
      if (set_zero_) call zero_array_int64(array, int(size_array))
480✔
986

987
      call mem%update_memory_after_alloc(size_array, 8)
480✔
988

989
   end subroutine alloc_i64_3
480✔
990

991

992
   subroutine alloc_i32_1(mem, array, M, set_zero)
808,203✔
993
      !!
994
      !! Written by Rolf H. Myhre, January 2019
995
      !!
996
      !! Allocates a one dimensional integer array and updates the available
997
      !! memory accordingly.
998
      !!
999
      !! set_zero: optional initialize array to zero
1000
      !!
1001
      implicit none
1002

1003
      class(memory_manager) :: mem
1004

1005
      integer(i32), dimension(:), allocatable :: array
1006
      logical, intent(in), optional :: set_zero
1007

1008
      integer, intent(in) :: M ! Dimension of array
1009

1010
      integer(i64) :: size_array ! Total size of array (M)
1011
      integer :: error = 0
1012
      logical :: set_zero_ = .false.
1013

1014
      character(len=100) :: error_msg
1015

1016
      size_array = M
808,203✔
1017

1018
      allocate(array(M), stat=error, errmsg=error_msg)
808,203✔
1019

1020
      if (error .ne. 0) then
808,203✔
1021
         call mem%print_allocation_error(size_array, error_msg)
×
1022
      endif
1023

1024
      if (present(set_zero)) set_zero_ = set_zero
808,203✔
1025
      if (set_zero_) call zero_array_int32(array, int(size_array))
808,203✔
1026

1027
      call mem%update_memory_after_alloc(size_array, 4)
808,203✔
1028

1029
   end subroutine alloc_i32_1
808,203✔
1030

1031

1032
   subroutine alloc_i32_2(mem, array, M, N, set_zero)
226,580✔
1033
      !!
1034
      !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Dec 2017
1035
      !!
1036
      !! Allocates a two dimensional integer array and updates the available
1037
      !! memory accordingly.
1038
      !!
1039
      !! set_zero: optional initialize array to zero
1040
      !!
1041
      implicit none
1042

1043
      class(memory_manager) :: mem
1044

1045
      integer(i32), dimension(:,:), allocatable :: array
1046
      logical, intent(in), optional :: set_zero
1047

1048
      integer, intent(in) :: M, N ! First and second dimension of array
1049

1050
      integer(i64) :: size_array ! Total size of array (M*N)
1051
      integer :: error = 0
1052
      logical :: set_zero_ = .false.
1053

1054
      character(len=100) :: error_msg
1055

1056
      size_array = M*N
226,580✔
1057

1058
      allocate(array(M,N), stat=error, errmsg=error_msg)
306,468✔
1059

1060
      if (error .ne. 0) then
226,580✔
1061
         call mem%print_allocation_error(size_array, error_msg)
×
1062
      endif
1063

1064
      if (present(set_zero)) set_zero_ = set_zero
226,580✔
1065
      if (set_zero_) call zero_array_int32(array, int(size_array))
226,580✔
1066

1067
      call mem%update_memory_after_alloc(size_array, 4)
226,580✔
1068

1069
   end subroutine alloc_i32_2
226,580✔
1070

1071

1072
   subroutine alloc_i32_3(mem, array, M, N, K, set_zero)
240✔
1073
      !!
1074
      !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Dec 2017
1075
      !!
1076
      !! Allocates a three dimensional integer array and updates the available
1077
      !! memory accordingly.
1078
      !!
1079
      !! set_zero: optional initialize array to zero
1080
      !!
1081
      implicit none
1082

1083
      class(memory_manager) :: mem
1084

1085
      integer(i32), dimension(:,:,:), allocatable :: array
1086
      logical, intent(in), optional :: set_zero
1087

1088
      integer, intent(in) :: M, N, K ! First and second dimension of array
1089

1090
      integer(i64) :: size_array ! Total size of array (M*N*K)
1091
      integer :: error = 0
1092
      logical :: set_zero_ = .false.
1093

1094
      character(len=100) :: error_msg
1095

1096
      size_array = M*N*K
240✔
1097

1098
      allocate(array(M,N,K), stat=error, errmsg=error_msg)
720✔
1099

1100
      if (error .ne. 0) then
240✔
1101
         call mem%print_allocation_error(size_array, error_msg)
×
1102
      endif
1103

1104
      if (present(set_zero)) set_zero_ = set_zero
240✔
1105
      if (set_zero_) call zero_array_int32(array, int(size_array))
240✔
1106

1107
      call mem%update_memory_after_alloc(size_array, 4)
240✔
1108

1109
   end subroutine alloc_i32_3
240✔
1110

1111

1112
   subroutine alloc_i_2_ranges(mem, array, range1, range2, set_zero)
304✔
1113
      !!
1114
      !! Written by Alexander C. Paul, Oct 2022
1115
      !!
1116
      !! Allocates a two dimensional integer array given 2 index ranges
1117
      !! and updates the available memory accordingly.
1118
      !!
1119
      !! set_zero: optional initialize array to zero
1120
      !!
1121
      use range_class, only: range_
1122

1123
      implicit none
1124

1125
      class(memory_manager) :: mem
1126

1127
      integer, dimension(:,:), allocatable :: array
1128
      logical, intent(in), optional :: set_zero
1129

1130
      ! First and second dimension of array that is being allocated
1131
      type(range_), intent(in) :: range1, range2
1132

1133
      integer(i64) :: size_array
1134
      integer :: first_1, last_1, first_2, last_2, error = 0
1135
      logical :: set_zero_ = .false.
1136

1137
      character(len=100) :: error_msg
1138

1139
      size_array = range1%get_length() * range2%get_length()
304✔
1140
      first_1 = range1%get_first()
304✔
1141
      last_1 = range1%get_last()
304✔
1142

1143
      first_2 = range2%get_first()
304✔
1144
      last_2 = range2%get_last()
304✔
1145

1146
      allocate(array(first_1:last_1, first_2:last_2), &
1147
               stat=error, errmsg=error_msg)
912✔
1148

1149
      if (present(set_zero)) set_zero_ = set_zero
304✔
1150
      if (set_zero_) call zero_array_int(array, int(size_array))
304✔
1151

1152
      if (error .ne. 0) then
304✔
1153
         call mem%print_allocation_error(size_array, error_msg)
×
1154
      endif
1155

1156
      call mem%update_memory_after_alloc(size_array, int_size)
304✔
1157

1158
   end subroutine alloc_i_2_ranges
304✔
1159

1160

1161
   subroutine alloc_l_1(mem, array, M, set_to)
355,295✔
1162
      !!
1163
      !! Written by Rolf H. Myhre, September 2019
1164
      !!
1165
      !! Allocates a one dimensional logical array and updates the available
1166
      !! memory accordingly.
1167
      !!
1168
      !! set_to: optional, initialize array to the value of set_to
1169
      !!
1170
      use array_initialization, only: set_logicals
1171

1172
      implicit none
1173

1174
      class(memory_manager) :: mem
1175

1176
      logical, dimension(:), allocatable :: array
1177
      logical, intent(in), optional :: set_to
1178

1179
      integer, intent(in) :: M ! Dimension of array
1180

1181
      integer(i64) :: size_array ! Total size of array (M)
1182
      integer :: error = 0, log_size
1183

1184
      character(len=100) :: error_msg
1185

1186
      size_array = M
355,295✔
1187

1188
      allocate(array(M), stat=error, errmsg=error_msg)
593,233✔
1189

1190
      if (present(set_to)) call set_logicals(array, int(size_array), set_to)
355,295✔
1191

1192
      if (error .ne. 0) then
355,295✔
1193
         call mem%print_allocation_error(size_array, error_msg)
×
1194
      endif
1195
      ! Figure out how big a logical is.
1196

1197
      log_size = storage_size(array(1))/8
355,295✔
1198
      call mem%update_memory_after_alloc(size_array, log_size)
355,295✔
1199

1200
   end subroutine alloc_l_1
355,295✔
1201

1202

1203
   subroutine alloc_l_2(mem, array, M, N, set_to)
568,016✔
1204
      !!
1205
      !! Written by Rolf H. Myhre, September 2019
1206
      !!
1207
      !! Allocates a two dimensional logical array and updates the available
1208
      !! memory accordingly.
1209
      !!
1210
      !! set_to: optional, initialize array to the value of set_to
1211
      !!
1212
      use array_initialization, only: set_logicals
1213

1214
      implicit none
1215

1216
      class(memory_manager) :: mem
1217

1218
      logical, dimension(:,:), allocatable :: array
1219
      logical, intent(in), optional :: set_to
1220

1221
      integer, intent(in) :: M, N ! Dimension of array
1222

1223
      integer(i64) :: size_array ! Total size of array (M*N)
1224
      integer :: error = 0, log_size
1225

1226
      character(len=100) :: error_msg
1227

1228
      size_array = M * N
568,016✔
1229

1230
      allocate(array(M,N), stat=error, errmsg=error_msg)
1,331,704✔
1231
      if (present(set_to)) call set_logicals(array, int(size_array), set_to)
568,016✔
1232

1233
      if (error .ne. 0) then
568,016✔
1234
         call mem%print_allocation_error(size_array, error_msg)
×
1235
      endif
1236

1237
      ! Figure out how big a logical is.
1238
      log_size = storage_size(array(1,1))/8
568,016✔
1239
      call mem%update_memory_after_alloc(size_array, log_size)
568,016✔
1240

1241
   end subroutine alloc_l_2
568,016✔
1242

1243

1244
   subroutine dealloc_real(mem, array)
84,672,824✔
1245
      !!
1246
      !! Written by Rolf H. Myhre and Alexander C. Paul, 2019-2023
1247
      !!
1248
      !! Deallocates a real double precision array and updates the available
1249
      !! memory accordingly.
1250
      !!
1251
      implicit none
1252

1253
      class(memory_manager),                intent(inout) :: mem
1254
      real(dp), dimension(..), allocatable, intent(inout) :: array
1255

1256
      integer(i64) :: size_array
1257
      integer :: error = 0
1258

1259
      character(len=100) :: error_msg
1260

1261
      if(.not. allocated(array)) call output%error_msg("Trying to deallocate an unallocated array!")
84,672,824✔
1262

1263
      size_array = size(array, kind=i64)
325,279,233✔
1264

1265
      select rank(array)
1266
         rank(1)
1267
            deallocate(array, stat=error, errmsg=error_msg)
6,604,136✔
1268
         rank(2)
1269
            deallocate(array, stat=error, errmsg=error_msg)
24,871,888✔
1270
         rank(3)
1271
            deallocate(array, stat=error, errmsg=error_msg)
29,318,626✔
1272
         rank(4)
1273
            deallocate(array, stat=error, errmsg=error_msg)
23,477,135✔
1274
         rank(5)
1275
            deallocate(array, stat=error, errmsg=error_msg)
12,155✔
1276
         rank(6)
1277
            deallocate(array, stat=error, errmsg=error_msg)
388,884✔
1278
         rank default ! GCC 10.2 does not allow a call to output%error_msg here
1279
            error stop 'Deallocation not implemented for real array of rank 7+'
×
1280
      end select
1281

1282
      if (error .ne. 0) call mem%print_deallocation_error(size_array, error_msg)
84,672,824✔
1283

1284
      call mem%update_memory_after_dealloc(size_array, dp)
84,672,824✔
1285

1286
   end subroutine dealloc_real
84,672,824✔
1287

1288

1289
   subroutine dealloc_complex(mem, array)
1,743,064✔
1290
      !!
1291
      !! Written by Rolf H. Myhre and Alexander C. Paul, 2019-2023
1292
      !!
1293
      !! Deallocates a complex double precision array and updates the available
1294
      !! memory accordingly.
1295
      !!
1296
      implicit none
1297

1298
      class(memory_manager),               intent(inout) :: mem
1299
      complex(dp), dimension(..), allocatable, intent(inout) :: array
1300

1301
      integer(i64) :: size_array
1302
      integer :: error = 0
1303

1304
      character(len=100) :: error_msg
1305

1306
      if(.not. allocated(array)) call output%error_msg("Trying to deallocate an unallocated array!")
1,743,064✔
1307

1308
      size_array = size(array, kind=i64)
7,051,868✔
1309

1310
      select rank(array)
1311
         rank(1)
1312
            deallocate(array, stat=error, errmsg=error_msg)
123,164✔
1313
         rank(2)
1314
            deallocate(array, stat=error, errmsg=error_msg)
290,526✔
1315
         rank(3)
1316
            deallocate(array, stat=error, errmsg=error_msg)
712,908✔
1317
         rank(4)
1318
            deallocate(array, stat=error, errmsg=error_msg)
616,466✔
1319
         rank default ! GCC 10.2 does not allow a call to output%error_msg here
1320
            error stop 'Deallocation not implemented for complex array of rank 5+'
×
1321
      end select
1322

1323
      if (error .ne. 0) call mem%print_deallocation_error(size_array, error_msg)
1,743,064✔
1324

1325
      call mem%update_memory_after_dealloc(size_array, 2*dp)
1,743,064✔
1326

1327
   end subroutine dealloc_complex
1,743,064✔
1328

1329

1330
   subroutine dealloc_64bit_integer(mem, array)
2,088,471✔
1331
      !!
1332
      !! Written by Rolf H. Myhre and Alexander C. Paul, 2019-2023
1333
      !!
1334
      !! Deallocates a 64 bit integer array and updates the available memory accordingly.
1335
      !!
1336
      implicit none
1337

1338
      class(memory_manager),               intent(inout) :: mem
1339
      integer(i64), dimension(..), allocatable, intent(inout) :: array
1340

1341
      integer(i64) :: size_array
1342
      integer :: error = 0
1343

1344
      character(len=100) :: error_msg
1345

1346
      if(.not. allocated(array)) call output%error_msg("Trying to deallocate an unallocated array!")
2,088,471✔
1347

1348
      size_array = size(array, kind=i64)
4,553,556✔
1349

1350
      select rank(array)
1351
         rank(1)
1352
            deallocate(array, stat=error, errmsg=error_msg)
1,712,337✔
1353
         rank(2)
1354
            deallocate(array, stat=error, errmsg=error_msg)
375,654✔
1355
         rank(3)
1356
            deallocate(array, stat=error, errmsg=error_msg)
480✔
1357
         rank default ! GCC 10.2 does not allow a call to output%error_msg here
1358
            error stop 'Deallocation not implemented for 64-bit integer array of rank 4+'
×
1359
      end select
1360

1361
      if (error .ne. 0) call mem%print_deallocation_error(size_array, error_msg)
2,088,471✔
1362

1363
      mem%available = mem%available + 8*size_array
2,088,471✔
1364

1365
   end subroutine dealloc_64bit_integer
2,088,471✔
1366

1367

1368
   subroutine dealloc_32bit_integer(mem, array)
1,034,943✔
1369
      !!
1370
      !! Written by Marcus T. Lexander and Alexander C. Paul, 2022-2023
1371
      !!
1372
      !! Deallocates a 32 bit integer array and updates the available memory accordingly.
1373
      !!
1374
      implicit none
1375

1376
      class(memory_manager),               intent(inout) :: mem
1377
      integer(i32), dimension(..), allocatable, intent(inout) :: array
1378

1379
      integer(i64) :: size_array
1380
      integer :: error = 0
1381

1382
      character(len=100) :: error_msg
1383

1384
      if(.not. allocated(array)) call output%error_msg("Trying to deallocate an unallocated array!")
1,034,943✔
1385

1386
      size_array = size(array, kind=i64)
2,296,946✔
1387

1388
      select rank(array)
1389
         rank(1)
1390
            deallocate(array, stat=error, errmsg=error_msg)
808,123✔
1391
         rank(2)
1392
            deallocate(array, stat=error, errmsg=error_msg)
226,580✔
1393
         rank(3)
1394
            deallocate(array, stat=error, errmsg=error_msg)
240✔
1395
         rank default ! GCC 10.2 does not allow a call to output%error_msg here
1396
            error stop 'Deallocation not implemented for 32-bit integer array of rank 4+'
×
1397
      end select
1398

1399
      if (error .ne. 0) call mem%print_deallocation_error(size_array, error_msg)
1,034,943✔
1400

1401
      mem%available = mem%available + 4*size_array
1,034,943✔
1402

1403
   end subroutine dealloc_32bit_integer
1,034,943✔
1404

1405

1406
   subroutine dealloc_logical(mem, array)
923,233✔
1407
      !!
1408
      !! Written by Rolf H. Myhre and Alexander C. Paul, 2019-2023
1409
      !!
1410
      !! Deallocates a logical array and updates the available memory accordingly.
1411
      !!
1412
      implicit none
1413

1414
      class(memory_manager),               intent(inout) :: mem
1415
      logical, dimension(..), allocatable, intent(inout) :: array
1416

1417
      integer(i64) :: size_array
1418
      integer :: error = 0, log_size
1419
      logical :: dummy_logical
1420

1421
      character(len=100) :: error_msg
1422

1423
      if(.not. allocated(array)) call output%error_msg("Trying to deallocate an unallocated array!")
923,233✔
1424

1425
      size_array = size(array, kind=i64)
2,414,482✔
1426

1427
      select rank(array)
1428
         rank(1)
1429
            deallocate(array, stat=error, errmsg=error_msg)
355,217✔
1430
         rank(2)
1431
            deallocate(array, stat=error, errmsg=error_msg)
568,016✔
1432
         rank default ! GCC 10.2 does not allow a call to output%error_msg here
1433
            error stop 'Deallocation not implemented for logical array of rank 3+'
×
1434
      end select
1435

1436
      if (error .ne. 0) call mem%print_deallocation_error(size_array, error_msg)
923,233✔
1437

1438
      log_size = storage_size(dummy_logical)/8
1439
      mem%available = mem%available + log_size*size_array
923,233✔
1440

1441
   end subroutine dealloc_logical
923,233✔
1442

1443

1444
   subroutine dealloc_char(mem, array)
×
1445
      !!
1446
      !! Written by Marcus T. Lexander, 2025
1447
      !!
1448
      !! Deallocates a character array and updates the available memory accordingly.
1449
      !!
1450
      implicit none
1451

1452
      class(memory_manager),                        intent(inout) :: mem
1453
      character(len=:), dimension(..), allocatable, intent(inout) :: array
1454

1455
      integer(i64) :: size_array, char_len
1456
      integer :: error = 0
1457

1458
      character(len=100) :: error_msg
1459

1460
      if(.not. allocated(array)) call output%error_msg("Trying to deallocate an unallocated array!")
×
1461

1462
      char_len = len(array)
×
1463
      size_array = size(array)
×
1464

1465
      select rank(array)
1466
         rank(1)
1467
            deallocate(array, stat=error, errmsg=error_msg)
×
1468
         rank default ! GCC 10.2 does not allow a call to output%error_msg here
1469
            error stop 'Deallocation not implemented for character array of rank 2+'
×
1470
      end select
1471

1472
      if (error .ne. 0) call mem%print_deallocation_error(size_array, error_msg)
×
1473

1474
      mem%available = mem%available + char_len*size_array
×
1475

1476
   end subroutine dealloc_char
×
1477

1478

1479
   subroutine print_allocation_error(size_array, error_msg)
×
1480
      !!
1481
      !! Written by Alexander C. Paul, March 2020
1482
      !!
1483
      implicit none
1484

1485
      integer(i64), intent(in) :: size_array
1486
      character (len=*), intent(in) :: error_msg
1487

1488
      character(len=17) :: number_string
1489

1490
      if (size_array < 0) &
×
1491
         call output%error_msg('Trying to allocate array with negative number of elements. &
1492
                               &This could be an integer overflow.')
×
1493

1494
      write(number_string, '(i0)') size_array
×
1495

1496
      call output%printf('m', error_msg, fs='(/t3,a)')
×
1497
      call output%printf('m', 'Note: Error message from gfortran might not be accurate.', &
1498
                          fs='(t3,a)')
×
1499
      call output%error_msg('Could not allocate array with #elements = (a0).', &
1500
                             chars=[trim(number_string)], ffs='(t3,a)')
×
1501

1502
   end subroutine print_allocation_error
×
1503

1504

1505
   subroutine print_deallocation_error(size_array, error_msg)
×
1506
      !!
1507
      !! Written by Alexander C. Paul, March 2020
1508
      !!
1509
      implicit none
1510

1511
      integer(i64), intent(in) :: size_array
1512
      character (len=*), intent(in) :: error_msg
1513

1514
      character(len=17) :: number_string
1515

1516
      write(number_string, '(i0)') size_array
×
1517

1518
      call output%printf('m', error_msg)
×
1519
      call output%printf('m', 'Note: Error message from gfortran might not be accurate.')
×
1520
      call output%error_msg('Could not deallocate array with #elements = (a0).', &
1521
                             chars=[trim(number_string)])
×
1522

1523
   end subroutine print_deallocation_error
×
1524

1525

1526
   subroutine update_memory_after_alloc(mem, size_array, size_type)
90,465,647✔
1527
      !!
1528
      !! Written by Alexander C. Paul, May 2020
1529
      !!
1530
      !! size_array: total size of the array allocated
1531
      !! size_type : storage size of one element of the array in Byte
1532
      !!
1533
      implicit none
1534

1535
      class(memory_manager) :: mem
1536

1537
      integer(i64), intent(in) :: size_array
1538
      integer, intent(in) :: size_type
1539

1540
      integer(i64) :: bytes
1541
      character(len=17) :: number_string
1542

1543
      bytes = size_array*int(size_type, kind=i64)
90,465,647✔
1544

1545
      if (bytes < 0) &
90,465,647✔
1546
         call output%error_msg('Trying to allocate array with less than 0 B. &
1547
                               &This could be an integer overflow.')
×
1548

1549
      mem%available = mem%available - bytes
90,465,647✔
1550

1551
      if (mem%available .lt. 0) then
90,465,647✔
1552

1553
         write(number_string, '(i0)') size_array
×
1554

1555
         call output%error_msg('User-specified memory insufficient in mem%alloc. &
1556
                               &Tried to allocate array with (a0) elements.', &
1557
                                chars=[trim(number_string)], ll=50)
×
1558

1559
      endif
1560

1561
      ! Update max used memory if needed
1562
      if (mem%max_used < (mem%total - mem%available)) &
90,465,647✔
1563
          mem%max_used =  mem%total - mem%available
699,686✔
1564

1565
      if (mem%batching_on) call mem%batch_mem_tracker%update(bytes)
90,465,647✔
1566

1567
   end subroutine update_memory_after_alloc
90,465,647✔
1568

1569

1570
   subroutine update_memory_after_dealloc(mem, size_array, size_type)
86,415,888✔
1571
      !!
1572
      !! Written by Alexander C. Paul, May 2020
1573
      !!
1574
      !! size_array: total size of the array allocated
1575
      !! size_type : storage size of one element of the array in Byte
1576
      !!
1577
      implicit none
1578

1579
      class(memory_manager) :: mem
1580

1581
      integer(i64), intent(in) :: size_array
1582
      integer, intent(in) :: size_type
1583

1584
      integer(i64) :: bytes
1585

1586
      bytes = size_array*int(size_type, kind=i64)
86,415,888✔
1587

1588
      mem%available = mem%available + bytes
86,415,888✔
1589

1590
      if (mem%batching_on) call mem%batch_mem_tracker%update(-bytes)
86,415,888✔
1591

1592
   end subroutine update_memory_after_dealloc
86,415,888✔
1593

1594

1595
   subroutine print_settings_memory_manager(mem)
3,182✔
1596
      !!
1597
      !! Written by Sarai D. Folkestad and Eirik F. Kjønstad, Sep 2018
1598
      !!
1599
      implicit none
1600

1601
      class(memory_manager) :: mem
1602

1603
      call output%printf('m', 'Memory available for calculation: ' //  &
1604
                         mem%get_memory_as_character(mem%total))
3,182✔
1605

1606
   end subroutine print_settings_memory_manager
3,182✔
1607

1608

1609
   subroutine batch_finalize_memory_manager(mem)
4,746,940✔
1610
      !!
1611
      !! Written by Eirik F. Kjønstad, June 2021
1612
      !!
1613
      !! Must be called after a batching loop is finished.
1614
      !!
1615
      !! The routine turns of batching mode and deallocates the
1616
      !! memory tracker for the batching procedure.
1617
      !!
1618
      implicit none
1619

1620
      class(memory_manager), intent(inout) :: mem
1621

1622
      mem%batching_on = .false.
4,746,940✔
1623

1624
      if (allocated(mem%batch_mem_tracker)) then
4,746,940✔
1625

1626
         deallocate(mem%batch_mem_tracker)
4,746,940✔
1627

1628
      else
1629

1630
         call output%error_msg('Asked to finalize batch, but batching tracker &
1631
                               &not allocated! Was batch_finalize already called &
1632
                               &for the current batching loop?')
×
1633

1634
      endif
1635

1636
   end subroutine batch_finalize_memory_manager
4,746,940✔
1637

1638

1639
   subroutine initialize_batching_tracker(mem, max_memory_usage, tag)
4,746,940✔
1640
      !!
1641
      !! Written by Eirik F. Kjønstad, June 2021
1642
      !!
1643
      !! To be called when batching has been determined.
1644
      !!
1645
      !! Makes sure memory usage is tracked during the batching loops.
1646
      !!
1647
      implicit none
1648

1649
      class(memory_manager), intent(inout) :: mem
1650

1651
      integer(i64), intent(in) :: max_memory_usage
1652
      character(len=*), intent(in) :: tag
1653

1654
      if (mem%batching_on) then
4,746,940✔
1655

1656
         call output%error_msg('Tried to initialize memory tracker for batching loop, &
1657
                               &but the memory manager is already in batching mode! &
1658
                               &Have you forgotten to finalize the previous batching loop?')
×
1659

1660
      endif
1661

1662
      mem%batching_on = .true.
4,746,940✔
1663
      mem%batch_mem_tracker = memory_tracker(max_memory_usage, tag)
4,746,940✔
1664

1665
   end subroutine initialize_batching_tracker
4,746,940✔
1666

1667

1668
   subroutine batch_setup_1(mem, batch_p, req0, req1, tag, element_size)
3,715,376✔
1669
      !!
1670
      !! Written by Rolf H. Myhre and Eirik F. Kjønstad, December 2018
1671
      !!
1672
      !! Batching setup for a single index.
1673
      !!
1674
      !! batch_p:  Initialized batching object.
1675
      !!
1676
      !! req0:     Memory required that does not change with the index dimension.
1677
      !!           E.g., n_o**2*n_v**2 for (vo|vo) if none of the indices
1678
      !!           in the integral is batched over.
1679
      !!
1680
      !! req1:     Memory required per batching index (linear with batch size).
1681
      !!           E.g., n_v**3 for (vv|vo) when batching over the
1682
      !!           occupied index.
1683
      !!
1684
      implicit none
1685

1686
      class(memory_manager) :: mem
1687

1688
      class(batching_index) :: batch_p ! The index being batched over
1689

1690
      integer, intent(in) :: req0
1691
      integer, intent(in) :: req1
1692

1693
      character(len=*), intent(in) :: tag
1694

1695
      integer, intent(in), optional :: element_size
1696

1697

1698
      integer(i64):: req0_tot
1699
      integer(i64):: req1_min
1700
      integer(i64):: req_min
1701

1702
      integer(i64):: req_tot
1703

1704
      integer :: e_size
1705
      character(len=17), allocatable :: reqChar
1706

1707
      if (.not. batch_p%initialized) then
3,715,376✔
1708

1709
         call output%error_msg('batch_setup_1 called on uninitialized batch')
×
1710

1711
      endif
1712

1713
      e_size = dp
1714
      if(present(element_size)) then
3,715,376✔
1715
         e_size = element_size
128,352✔
1716
      endif
1717

1718
      req0_tot = int(req0, kind=i64) * int(e_size, kind=i64)
3,715,376✔
1719
      req1_min = int(req1, kind=i64) * int(e_size, kind=i64)
3,715,376✔
1720

1721
      req_min = req0_tot + req1_min
3,715,376✔
1722
      req_tot = req0_tot + req1_min*int(batch_p%index_dimension, kind=i64)
3,715,376✔
1723

1724
      if (req_tot .lt. mem%available) then
3,715,376✔
1725

1726
         ! No need to batch
1727

1728
         batch_p%num_batches = 1
3,715,376✔
1729
         batch_p%max_length  = batch_p%index_dimension
3,715,376✔
1730

1731
      else if (req_min .gt. mem%available) then
×
1732

1733
         ! Hack because intel flips out if we put two functions in chars=[]
1734

1735
         reqChar = mem%get_memory_as_character(req_min, .true.)
×
1736
         call output%printf('m', 'Need at least (a0) but only have (a0)', &
1737
                            chars=[reqChar, mem%get_memory_as_character(mem%available, .true.)])
×
1738
         call output%error_msg('Not enough memory for a batch.')
×
1739

1740
      else
1741

1742
         ! We need to batch
1743
         !
1744
         ! Determine maximum batch length
1745

1746
         batch_p%max_length = int((mem%available - req0_tot)/req1_min)
×
1747

1748
         ! Number of full batches
1749

1750
         batch_p%num_batches = (batch_p%index_dimension-1)/(batch_p%max_length)+1
×
1751

1752
      endif
1753

1754
      if (force_batch) call batch_p%force_batch()
3,715,376✔
1755

1756
      if (batch_p%num_batches > 1) call output%printf('v', 'Batching in (a0)', chars=[tag])
10,683,554✔
1757

1758
      call mem%initialize_batching_tracker(req0_tot + req1_min*int(batch_p%max_length, kind=i64), &
1759
                                           tag)
3,715,376✔
1760

1761
   end subroutine batch_setup_1
7,430,752✔
1762

1763

1764
   subroutine batch_setup_2(mem, batch_p, batch_q, req0, req1_p, req1_q, &
963,178✔
1765
                                           req2, tag, element_size, req_single_batch)
1766
      !!
1767
      !! Written by Rolf H. Myhre and Eirik F. Kjønstad, Dec 2018
1768
      !!
1769
      !! Batching setup for two batching indices.
1770
      !!
1771
      !! batch_p: Initialized batching object
1772
      !! batch_q: Initialized batching object
1773
      !!
1774
      !! req0: required memory that does not scale with batch size
1775
      !!
1776
      !! req1_p: required memory that scales linearly with p batch size
1777
      !! req1_q: required memory that scales linearly with q batch size
1778
      !!
1779
      !! req2: required memory that scales quadratically with batch size
1780
      !!
1781
      !! element_size: memory per element, default is double precision
1782
      !!
1783
      !! req_single_batch: optional specifying the minimal memory needed to not batch
1784
      !!
1785
      !! If you are batching over i and j and need to keep g_abij, g_abci and g_abcj in memory,
1786
      !! req1_i = n_v**3, req1_j = n_v**3 and req2 = n_v**2.
1787
      !! Memory per batch is then batch_size*(req1_i + req1_j) + batch_size**2*req2
1788
      !!
1789
      !! If you are batching over a and j and need to keep g_abij, g_abci and g_abcj in memory,
1790
      !! req1_a = n_o*n_v**2, req1_j = 0, and req2 = n_o*n_v + n_v**2. Note that one integral (g_abci)
1791
      !! scales linearly with the a-index but that there are no such integrals for the j-index.
1792
      !!
1793
      !! Be careful with symmetries and permutations!
1794
      !!
1795
      implicit none
1796

1797
      class(memory_manager) :: mem
1798

1799
      class(batching_index) :: batch_p ! An index being batched over
1800
      class(batching_index) :: batch_q ! An index being batched over
1801

1802
      integer, intent(in) :: req0
1803
      integer, intent(in) :: req1_p
1804
      integer, intent(in) :: req1_q
1805
      integer, intent(in) :: req2
1806

1807
      character(len=*), intent(in) :: tag
1808

1809
      integer, intent(in), optional :: element_size
1810
      integer, intent(in), optional :: req_single_batch
1811

1812

1813
      logical :: figured_out
1814

1815
      integer(i64):: req0_tot
1816
      integer(i64):: req1_p_min
1817
      integer(i64):: req1_q_min
1818
      integer(i64):: req2_min
1819
      integer(i64):: req_min
1820
      integer(i64):: req_tot
1821

1822
      integer(i64):: p_elements, q_elements
1823

1824
      integer :: e_size
1825
      character(len=17), allocatable :: reqChar
1826

1827
      integer(i64) :: max_memory_usage
1828

1829
      if ((.not. batch_p%initialized) .or. (.not. batch_q%initialized)) then
963,178✔
1830

1831
         call output%error_msg('batch_setup_2 called on uninitialized batch')
×
1832

1833
      endif
1834

1835
      e_size = dp
1836
      if(present(element_size)) then
963,178✔
1837
         e_size = element_size
21,930✔
1838
      endif
1839

1840
      req0_tot   = int(req0, kind=i64) * int(e_size, kind=i64)
963,178✔
1841
      req1_p_min = int(req1_p, kind=i64) * int(e_size, kind=i64)
963,178✔
1842
      req1_q_min = int(req1_q, kind=i64) * int(e_size, kind=i64)
963,178✔
1843
      req2_min   = int(req2, kind=i64) * int(e_size, kind=i64)
963,178✔
1844

1845
      req_min = req0_tot + req1_p_min + req1_q_min + req2_min
963,178✔
1846

1847
      ! Determine or copy the memory needed to not batch
1848

1849
      if (present(req_single_batch)) then
963,178✔
1850
         req_tot = int(req_single_batch, kind=i64)*int(e_size, kind=i64)
268,681✔
1851
      else
1852

1853
         req_tot = req0_tot + req1_p_min*int(batch_p%index_dimension, kind=i64)  &
1854
                  + req1_q_min*int(batch_q%index_dimension, kind=i64)  &
1855
                  + req2_min*int(batch_p%index_dimension, kind=i64)    &
1856
                     *int(batch_q%index_dimension, kind=i64)
694,497✔
1857

1858
      end if
1859

1860
      if (req_tot .lt. mem%available) then
963,178✔
1861

1862
         ! No need to batch
1863

1864
         batch_p%num_batches = 1
963,178✔
1865
         batch_p%max_length  = batch_p%index_dimension
963,178✔
1866

1867
         batch_q%num_batches = 1
963,178✔
1868
         batch_q%max_length  = batch_q%index_dimension
963,178✔
1869

1870
      else if (req_min .gt. mem%available) then
×
1871

1872
         ! Hack because intel flips out if we put two functions in chars=[]
1873
         reqChar = mem%get_memory_as_character(req_min, .true.)
×
1874
         call output%printf('m', 'Need at least (a0) but only have (a0)', &
1875
                            chars=[reqChar, mem%get_memory_as_character(mem%available, .true.)])
×
1876
         call output%error_msg('Not enough memory for a batch.')
×
1877

1878
      else
1879

1880
         ! We need to batch
1881
         !
1882
         ! Figure out how many we have room for
1883
         !
1884
         ! I. First, try to increment both indices simultaneously
1885

1886
         p_elements = 1
1887
         q_elements = 1
1888

1889
         figured_out = .false.
1890
         do while (.not. figured_out                                    &
1891
                     .and. int(p_elements) .lt. batch_p%index_dimension &
1892
                     .and. int(q_elements) .lt. batch_q%index_dimension)
×
1893

1894
            if (((p_elements+1)*(q_elements+1)*req2_min &
×
1895
                  + (p_elements+1)*req1_p_min          &
1896
                  + (q_elements+1)*req1_q_min          &
1897
                  + req0_tot) .lt. mem%available) then
×
1898

1899
               p_elements = p_elements + 1 ! can hold +1 batch size
1900
               q_elements = q_elements + 1
1901

1902
            else
1903

1904
               figured_out = .true.       ! cannot hold +1 batch size
1905

1906
            endif
1907

1908
         enddo
1909

1910

1911
         ! II. If simultaneous incrementation was not sufficient,
1912
         !      then try to increment the largest index further. This is
1913
         !      guaranteed to work, so let's just go ahead and increment
1914
         !      with no safeguards in place.
1915

1916
         if (.not. figured_out) then
×
1917

1918
            if (batch_p%index_dimension .gt. batch_q%index_dimension) then
×
1919

1920
               ! Increment p
1921

1922
               do while (((p_elements+1)*q_elements*req2_min &
×
1923
                           + (p_elements+1)*req1_p_min       &
1924
                           + q_elements*req1_q_min           &
1925
                           + req0_tot) .lt. mem%available)
1926

1927
                  p_elements = p_elements + 1
×
1928

1929
               enddo
1930

1931
            elseif (batch_p%index_dimension .lt. batch_q%index_dimension) then
×
1932

1933
               ! Increment q
1934

1935
               do while ((p_elements*(q_elements+1)*req2_min &
×
1936
                           + p_elements*req1_p_min           &
1937
                           + (q_elements+1)*req1_q_min       &
1938
                           + req0_tot) .lt. mem%available)
1939

1940
                  q_elements = q_elements + 1
×
1941

1942
               enddo
1943

1944
            else
1945

1946
               call output%error_msg('Something went very wrong! Expected different-sized' // &
1947
                                      'indices, but got same-sized indices (in batching setup).')
×
1948

1949
            endif
1950

1951
            figured_out = .true.
1952

1953
         endif
1954

1955
         batch_p%max_length = int(p_elements)
×
1956
         batch_q%max_length = int(q_elements)
×
1957

1958
         ! Figure out how many batches
1959

1960
         batch_p%num_batches = (batch_p%index_dimension-1)/(batch_p%max_length)+1
×
1961
         batch_q%num_batches = (batch_q%index_dimension-1)/(batch_q%max_length)+1
×
1962

1963
      endif
1964

1965
      ! Debug feature: enforced random batching
1966

1967
      if (force_batch) then
1968

1969
         if (batch_p%index_dimension == batch_q%index_dimension) then
963,178✔
1970

1971
            call batch_p%force_batch()
349,337✔
1972

1973
            batch_q%max_length  = batch_p%max_length
349,337✔
1974
            batch_q%num_batches = batch_p%num_batches
349,337✔
1975

1976
         else
1977

1978
            call batch_p%force_batch()
613,841✔
1979
            call batch_q%force_batch()
613,841✔
1980

1981
         endif
1982

1983
      endif
1984

1985
      max_memory_usage = req0_tot + &
1986
                         req1_p_min*int(batch_p%max_length, kind=i64) + &
1987
                         req1_q_min*int(batch_q%max_length, kind=i64) + &
1988
                         req2_min*int(batch_q%max_length, kind=i64)     &
1989
                                 *int(batch_q%max_length, kind=i64)
963,178✔
1990

1991
      if (batch_p%num_batches .eq. 1 .and. &
963,178✔
1992
          batch_q%num_batches .eq. 1) then
1993

1994
         if (present(req_single_batch)) then
22,112✔
1995

1996
            max_memory_usage = int(req_single_batch, kind=i64)*int(e_size, kind=i64)
×
1997

1998
         endif
1999

2000
      endif
2001

2002
      if (any([batch_p%num_batches, batch_q%num_batches] > 1)) then
963,178✔
2003
         call output%printf('v', 'Batching in (a0)', chars=[tag])
2,823,198✔
2004
      end if
2005

2006
      call mem%initialize_batching_tracker(max_memory_usage, tag)
963,178✔
2007

2008
   end subroutine batch_setup_2
1,926,356✔
2009

2010

2011
   subroutine batch_setup_3(mem, batch_p, batch_q, batch_r, req0, &
68,386✔
2012
                                           req1_p, req1_q, req1_r, req2_pq,      &
2013
                                           req2_pr, req2_qr, req3, tag,          &
2014
                                           element_size, req_single_batch)
2015
      !!
2016
      !! Written by Rolf H. Myhre December 2018
2017
      !!
2018
      !! Batching setup for three batching indices.
2019
      !!
2020
      !! batch_p: Initialized batching object
2021
      !! batch_q: Initialized batching object
2022
      !! batch_r: Initialized batching object
2023
      !!
2024
      !! req0: required memory that does not scale with batch size
2025
      !!
2026
      !! req1_p: required memory that scales linearly with p batch size
2027
      !! req1_q: required memory that scales linearly with q batch size
2028
      !! req1_r: required memory that scales linearly with r batch size
2029
      !!
2030
      !! req2_pq: required memory that scales quadratically with pq batch size
2031
      !! req2_pr: required memory that scales quadratically with pr batch size
2032
      !! req2_qr: required memory that scales quadratically with qr batch size
2033
      !!
2034
      !! req3: required memory that scales cubically with batch indices pqr
2035
      !!
2036
      !! element_size: memory per element, default is double precision
2037
      !!
2038
      !! req_single_batch: optional specifying the minimal memory needed to not batch
2039
      !!
2040
      !! Be careful with symmetries and permutations!
2041
      !!
2042
      implicit none
2043

2044
      class(memory_manager) :: mem
2045

2046
      class(batching_index) :: batch_p ! An index being batched over
2047
      class(batching_index) :: batch_q ! An index being batched over
2048
      class(batching_index) :: batch_r ! An index being batched over
2049

2050
      integer, intent(in) :: req0
2051

2052
      integer, intent(in) :: req1_p
2053
      integer, intent(in) :: req1_q
2054
      integer, intent(in) :: req1_r
2055

2056
      integer, intent(in) :: req2_pq
2057
      integer, intent(in) :: req2_pr
2058
      integer, intent(in) :: req2_qr
2059

2060
      integer, intent(in) :: req3
2061

2062
      character(len=*), intent(in) :: tag
2063

2064
      integer, intent(in), optional :: element_size
2065
      integer, intent(in), optional :: req_single_batch
2066

2067

2068
      integer(i64):: req0_tot
2069

2070
      integer(i64):: req1_p_min
2071
      integer(i64):: req1_q_min
2072
      integer(i64):: req1_r_min
2073

2074
      integer(i64):: req2_pq_min
2075
      integer(i64):: req2_pr_min
2076
      integer(i64):: req2_qr_min
2077

2078
      integer(i64):: req3_min
2079

2080
      integer(i64):: req_min
2081
      integer(i64):: req_tot
2082

2083
      integer(i64):: p_elements, q_elements, r_elements
2084

2085
      logical :: found_batch_size, p_incremented, q_incremented, r_incremented
2086

2087
      integer :: e_size
2088
      character(len=17), allocatable :: reqChar
2089

2090
      integer(i64) :: max_memory_usage
2091

2092
      if ((.not. batch_p%initialized)        &
2093
            .or. (.not. batch_q%initialized) &
2094
            .or. (.not. batch_r%initialized)) then
68,386✔
2095

2096
         call output%error_msg('batch_setup_3 called on uninitialized batch')
×
2097

2098
      endif
2099

2100
      e_size = dp
2101
      if(present(element_size)) then
68,386✔
2102
         e_size = element_size
×
2103
      endif
2104

2105
      req0_tot   = int(req0, kind=i64) * int(e_size, kind=i64)
68,386✔
2106

2107
      req1_p_min = int(req1_p, kind=i64) * int(e_size, kind=i64)
68,386✔
2108
      req1_q_min = int(req1_q, kind=i64) * int(e_size, kind=i64)
68,386✔
2109
      req1_r_min = int(req1_r, kind=i64) * int(e_size, kind=i64)
68,386✔
2110

2111
      req2_pq_min = int(req2_pq, kind=i64) * int(e_size, kind=i64)
68,386✔
2112
      req2_pr_min = int(req2_pr, kind=i64) * int(e_size, kind=i64)
68,386✔
2113
      req2_qr_min = int(req2_qr, kind=i64) * int(e_size, kind=i64)
68,386✔
2114

2115
      req3_min = int(req3, kind=i64) * int(e_size, kind=i64)
68,386✔
2116

2117
      req_min = req0_tot + req1_p_min + req1_q_min + req1_r_min &
2118
              + req2_pq_min + req2_pr_min + req2_qr_min + req3_min
68,386✔
2119

2120
      ! Determine or copy the memory needed to not batch
2121

2122
      if (present(req_single_batch)) then
68,386✔
2123
         req_tot = int(req_single_batch, kind=i64) * int(e_size, kind=i64)
66,472✔
2124
      else
2125

2126
         req_tot = req0_tot + req1_p_min                              &
2127
                              *int(batch_p%index_dimension, kind=i64) &
2128
                            + req1_q_min                              &
2129
                              *int(batch_q%index_dimension, kind=i64) &
2130
                            + req1_r_min                              &
2131
                              *int(batch_r%index_dimension, kind=i64) &
2132
                            + req2_pq_min                             &
2133
                              *int(batch_p%index_dimension, kind=i64) &
2134
                              *int(batch_q%index_dimension, kind=i64) &
2135
                            + req2_pr_min                             &
2136
                              *int(batch_p%index_dimension, kind=i64) &
2137
                              *int(batch_r%index_dimension, kind=i64) &
2138
                            + req2_qr_min                             &
2139
                              *int(batch_q%index_dimension, kind=i64) &
2140
                              *int(batch_r%index_dimension, kind=i64) &
2141
                            + req3_min                                &
2142
                              *int(batch_p%index_dimension, kind=i64) &
2143
                              *int(batch_q%index_dimension, kind=i64) &
2144
                              *int(batch_r%index_dimension, kind=i64)
1,914✔
2145

2146
      end if
2147

2148
      if (req_tot .lt. mem%available) then
68,386✔
2149

2150
         ! No need to batch
2151

2152
         batch_p%num_batches = 1
68,386✔
2153
         batch_p%max_length  = batch_p%index_dimension
68,386✔
2154

2155
         batch_q%num_batches = 1
68,386✔
2156
         batch_q%max_length  = batch_q%index_dimension
68,386✔
2157

2158
         batch_r%num_batches = 1
68,386✔
2159
         batch_r%max_length  = batch_r%index_dimension
68,386✔
2160

2161
      else if (req_min .gt. mem%available) then
×
2162

2163
         ! Hack because intel flips out if we put two functions in chars=[]
2164
         reqChar = mem%get_memory_as_character(req_min, .true.)
×
2165
         call output%printf('m', 'Need at least (a0) but only have (a0)', &
2166
                            chars=[reqChar, mem%get_memory_as_character(mem%available, .true.)])
×
2167
         call output%error_msg('Not enough memory for a batch.')
×
2168

2169
      else
2170

2171
         ! First, try to increment all indices simultaneously
2172

2173
         p_elements = 1
2174
         q_elements = 1
2175
         r_elements = 1
2176

2177
         found_batch_size = .false.
2178
         p_incremented = .true.
2179
         q_incremented = .true.
2180
         r_incremented = .true.
2181

2182
         do while (.not. found_batch_size &
2183
                   .and. (p_incremented .or. q_incremented .or. r_incremented))
×
2184

2185
            if (int(p_elements) .lt. batch_p%index_dimension) then
×
2186
               p_elements = p_elements + 1
×
2187
               p_incremented = .true.
2188
            else
2189
               p_incremented = .false.
2190
            endif
2191

2192
            if (int(q_elements) .lt. batch_q%index_dimension) then
×
2193
               q_elements = q_elements + 1
×
2194
               q_incremented = .true.
2195
            else
2196
               q_incremented = .false.
2197
            endif
2198

2199
            if (int(r_elements) .lt. batch_r%index_dimension) then
×
2200
               r_elements = r_elements + 1
×
2201
               r_incremented = .true.
2202
            else
2203
               r_incremented = .false.
2204
            endif
2205

2206
            if (    p_elements*q_elements*r_elements*req3_min    &
×
2207
                  + p_elements*q_elements           *req2_pq_min &
2208
                  + p_elements*r_elements           *req2_pr_min &
2209
                  + q_elements*r_elements           *req2_qr_min &
2210
                  + p_elements                      *req1_p_min  &
2211
                  + q_elements                      *req1_q_min  &
2212
                  + r_elements                      *req1_r_min  &
2213
                  + req0_tot .ge. mem%available) then
×
2214

2215
               found_batch_size = .true.       ! cannot hold +1 batch size
2216
               if (p_incremented) p_elements = p_elements - 1
×
2217
               if (q_incremented) q_elements = q_elements - 1
×
2218
               if (r_incremented) r_elements = r_elements - 1
×
2219

2220
            endif
2221

2222
         enddo
2223

2224
         batch_p%max_length = int(p_elements)
×
2225
         batch_q%max_length = int(q_elements)
×
2226
         batch_r%max_length = int(r_elements)
×
2227

2228
         ! Figure out how many batches
2229

2230
         batch_p%num_batches = (batch_p%index_dimension-1)/(batch_p%max_length)+1
×
2231
         batch_q%num_batches = (batch_q%index_dimension-1)/(batch_q%max_length)+1
×
2232
         batch_r%num_batches = (batch_r%index_dimension-1)/(batch_r%max_length)+1
×
2233

2234
      endif
2235

2236
      if (force_batch) then
2237

2238
         call batch_p%force_batch()
68,386✔
2239

2240
         if (batch_p%index_dimension .eq. batch_q%index_dimension .and. &
68,386✔
2241
             batch_p%index_dimension .eq. batch_r%index_dimension) then
2242

2243
            batch_q%max_length  = batch_p%max_length
66,526✔
2244
            batch_q%num_batches = batch_p%num_batches
66,526✔
2245

2246
            batch_r%max_length  = batch_p%max_length
66,526✔
2247
            batch_r%num_batches = batch_p%num_batches
66,526✔
2248

2249
         else
2250

2251
            call batch_q%force_batch()
1,860✔
2252
            call batch_r%force_batch()
1,860✔
2253

2254
         end if
2255

2256
      endif
2257

2258
      max_memory_usage = req0_tot + &
2259
                         req1_p_min*int(batch_p%max_length, kind=i64)  +   &
2260
                         req1_q_min*int(batch_q%max_length, kind=i64)  +   &
2261
                         req1_r_min*int(batch_r%max_length, kind=i64)  +   &
2262
                         req2_pq_min*int(batch_p%max_length, kind=i64)     &
2263
                                    *int(batch_q%max_length, kind=i64) +   &
2264
                         req2_pr_min*int(batch_p%max_length, kind=i64)     &
2265
                                    *int(batch_r%max_length, kind=i64) +   &
2266
                         req2_qr_min*int(batch_q%max_length, kind=i64)     &
2267
                                    *int(batch_r%max_length, kind=i64) +   &
2268
                         req3_min   *int(batch_p%max_length, kind=i64)     &
2269
                                    *int(batch_q%max_length, kind=i64)     &
2270
                                    *int(batch_r%max_length, kind=i64)
68,386✔
2271

2272
      if (batch_p%num_batches .eq. 1 .and. &
2273
          batch_q%num_batches .eq. 1 .and. &
68,386✔
2274
          batch_r%num_batches .eq. 1) then
2275

2276
         if (present(req_single_batch)) then
×
2277

2278
            max_memory_usage = int(req_single_batch, kind=i64) * int(e_size, kind=i64)
×
2279

2280
         endif
2281

2282
      endif
2283

2284
      if (any([batch_p%num_batches, batch_q%num_batches, batch_r%num_batches] > 1)) then
68,386✔
2285
         call output%printf('v', 'Batching in (a0)', chars=[tag])
205,158✔
2286
      end if
2287

2288
      call mem%initialize_batching_tracker(max_memory_usage, tag)
68,386✔
2289

2290
   end subroutine batch_setup_3
136,772✔
2291

2292

2293
end module memory_manager_class
90,462,535✔
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc