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

gyrokinetics / gs2 / 2021218321

04 Sep 2025 07:44AM UTC coverage: 10.606% (+0.03%) from 10.577%
2021218321

push

gitlab-ci

David Dickinson
Merged in feature/move_more_initialisation_to_init_levels (pull request #1161)

4710 of 44407 relevant lines covered (10.61%)

125698.1 hits per line

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

0.0
/src/gs2_optimisation.f90
1
!> This module sits on top of gs2_main and provides
2
!! a toolkit for measuring and optimising performance
3
module gs2_optimisation
4
  use gs2_main, only: gs2_program_state_type
5

6
  implicit none
7

8
contains
9

10
  !> FIXME : Add documentation
11
  subroutine initialize_gs2_optimisation(state)
×
12
    use optimisation_configuration, only: init_optimisation_config
13
    use gs2_main, only: initialize_gs2, finalize_gs2
14
    use gs2_main, only: initialize_wall_clock_timer
15
    use mp, only: init_mp, mp_comm
16
    implicit none
17
    type(gs2_program_state_type), intent(inout) :: state
18
    call init_mp
×
19
    state%mp_comm = mp_comm
×
20
    allocate(state%optim%sorted_optimisations(0))
×
21
    allocate(state%optim%sorted_results(0))
×
22
    ! We have to initialize_gs2 so that we
23
    ! can read the optimisation_config namelist
24
    call initialize_gs2(state, quiet=.true.)
×
25
    call init_optimisation_config(state%optim)
×
26
    call finalize_gs2(state, quiet=.true.)
×
27
  end subroutine initialize_gs2_optimisation
×
28

29
  !> FIXME : Add documentation
30
  subroutine finalize_gs2_optimisation(state)
×
31
    use optimisation_configuration, only: finish_optimisation_config
32
    implicit none
33
    type(gs2_program_state_type), intent(inout) :: state
34
    call finish_optimisation_config(state%optim)
×
35
  end subroutine finalize_gs2_optimisation
×
36

37
  !> Setup, run, and teardown GS2 optimisation preprocessing.
38
  !>
39
  !> If the result is true, main GS2 program should continue and run
40
  !> simulation, possibly applying optimised overrides
41
  logical function run_optimise_gs2(state) result(should_continue)
×
42
    !> GS2 program state. Depending on settings, this may be modified
43
    !> to set [[optimisations_overrides_type]]
44
    type(gs2_program_state_type), intent(inout) :: state
45

46
    call initialize_gs2_optimisation(state)
×
47
    if (state%optim%on) call optimise_gs2(state)
×
48
    should_continue = (state%optim%auto .or. .not. state%optim%on)
×
49
    call finalize_gs2_optimisation(state)
×
50
  end function run_optimise_gs2
×
51

52
  !> FIXME : Add documentation
53
  subroutine optimise_gs2(state)
×
54
    use mp, only: mp_abort
55
    use fields_implicit, only: skip_initialisation
56
    use fields_local, only: fieldmat
57
    implicit none
58
    type(gs2_program_state_type), intent(inout) :: state
59
    integer :: i,n
60
    real,dimension(10) :: time_array
61
    real :: mean,sd
62
    state%print_times = .false.
×
63
    state%print_full_timers = .false.
×
64
    state%is_external_job = .true.
×
65
    ! Initialize optimisation results
66
    state%optim%results%optimal_time = -1.0
×
67
    state%optim%results%optimal_cost = -1.0
×
68
    state%optim%results%optimal = .false.
×
69

70
    skip_initialisation = .true.
×
71
    fieldmat%no_prepare = .true.
×
72
    fieldmat%no_populate = .true.
×
73
    state%dont_change_timestep = .true.
×
74
    state%init%config%knobs_config%immediate_reset = .false.
×
75

76
    if (state%optim%estimate_timing_error) then
×
77
       do i = 1,10
×
78
          call measure_timestep(state)
×
79
          time_array(i) = state%optim%results%time
×
80
       end do
81
       mean = sum(time_array(1:10)) / real(10)
×
82
       sd = sqrt (sum((time_array(1:10)-mean)**2) / real(10.0))
×
83
       state%optim%timing_rel_error = sd/mean
×
84
       state%optim%timing_max_rel_error = &
85
            (maxval(time_array)-minval(time_array))/mean
×
86

87
       write (*,*) 'Timing', mean, sd, sd/mean
×
88
       deallocate(state%optim%sorted_results)
×
89
       deallocate(state%optim%sorted_optimisations)
×
90
       allocate(state%optim%sorted_optimisations(0))
×
91
       allocate(state%optim%sorted_results(0))
×
92
       state%optim%results%optimal_time = -1.0
×
93
       state%optim%results%optimal_cost = -1.0
×
94
       state%optim%results%optimal = .false.
×
95
    else
96
       state%optim%timing_rel_error = -1.0
×
97
    end if
98

99
    if (state%optim%warm_up) then
×
100
       call optimise_simple(state)
×
101

102
       deallocate(state%optim%sorted_results)
×
103
       deallocate(state%optim%sorted_optimisations)
×
104
       allocate(state%optim%sorted_optimisations(0))
×
105
       allocate(state%optim%sorted_results(0))
×
106
       state%optim%results%optimal_time = -1.0
×
107
       state%optim%results%optimal_cost = -1.0
×
108
       state%optim%results%optimal = .false.
×
109
    end if
110

111
    call optimise_simple(state)
×
112
    skip_initialisation = .false.
×
113
    fieldmat%no_prepare = .false.
×
114
    fieldmat%no_populate = .false.
×
115
    state%dont_change_timestep = .false.
×
116

117
    call output_results(state)
×
118

119
    if (state%optim%auto) then
×
120
       ! Find the optimal configuration which satisfies
121
       ! constraints. Abort if one can't be found.
122
       n = size(state%optim%sorted_optimisations)
×
123
       do i = 1, n
×
124
          ! Find the most optimal configuration that satisfies
125
          ! max_unused_procs and max_imbalance and min_efficiency
126
          if (&
127
               (state%optim%max_unused_procs < 0 .or.&
128
               (state%optim%nproc_max - state%optim%sorted_results(i)%nproc) <=&
×
129
               state%optim%max_unused_procs)  &
130
               .and. &
131
               (state%optim%max_imbalance < 0.0 .or.&
132
               (state%optim%nproc_max - state%optim%sorted_results(i)%nproc) / &
×
133
               state%optim%nproc_max <=&
134
               state%optim%max_imbalance) &
135
               .and. &
×
136
               (state%optim%min_efficiency < 0.0 .or. &
×
137
               state%optim%sorted_results(i)%efficiency > &
138
               state%optim%min_efficiency) &
139
               ) exit
×
140
          if (i == n) then
×
141
             call mp_abort("Could not satisfy min_efficiency without &
142
                  & violating max_imbalance or max_unused_procs", .true.)
×
143
          end if
144
       end do
145

146
       !> This is the line which optimises GS2, by copying
147
       !> the optimal set of overrides into the init structure
148
       state%init%opt_ov = state%optim%sorted_optimisations(i)
×
149
    end if
150
  end subroutine optimise_gs2
×
151

152
  !> FIXME : Add documentation
153
  subroutine output_results(state)
×
154
    use mp, only: proc0
155
    implicit none
156
    type(gs2_program_state_type), intent(inout) :: state
157
    character(len=*), parameter :: formt =  &
158
         '(A10," ",A10," ",A10," ",A6," ",A6," ",A1," ",A1," ",A1," ",A1," ",A1,&
159
         &" ",A1," ",A1," ",A1," ",A1," ",A1," ",A1," ",A1," ",A7)'
160
    character(len=*), parameter :: bk = '               '
161
    character(len=*), parameter :: ul = '---------------'
162
    character(len=*), parameter :: h1 = "GS2 Timing"
163
    character(len=*), parameter :: h2 = "Data      "
164
    character(len=*), parameter :: h3 = " Est. Rel."
165
    character(len=*), parameter :: ha = " Est. Max."
166
    character(len=*), parameter :: h4 = "Timing Err"
167
    character(len=*), parameter :: h5 = " %        "
168
    character(len=6) :: er
169
    character(len=6) :: em
170
    integer :: i,n, ou
171

172
    ou = state%optim%outunit
×
173

174
    write(er, "(F6.2)") state%optim%timing_rel_error * 100.0
×
175
    write(em, "(F6.2)") state%optim%timing_max_rel_error * 100.0
×
176

177
    if (proc0) then
×
178

179
       write(ou,formt)h1,h2,bk,bk,bk,'o', bk, bk, bk, bk, bk, bk, bk,'d','f', bk, bk,bk
×
180
       write(ou,formt)h3,h4,er,h5,bk,'p', bk, bk,'l', bk, bk, bk,'f','|','l', bk, bk,bk
×
181
       write(ou,formt)ha,h4,em,h5,bk,'t', bk, bk,'o', bk, bk, bk,'i','s','o', bk,'f',bk
×
182
       write(ou,formt)bk,bk,bk,bk,bk,'|', bk, bk,'c', bk, bk,'i','e','m','c', bk,'i',bk
×
183
       write(ou,formt)bk,bk,bk,bk,bk,'r', bk, bk,'a','o','i','n','l','a','|', bk,'e',bk
×
184
       write(ou,formt)bk,bk,bk,bk,bk,'e', bk, bk,'l','p','n','t','d','r','a', bk,'l',bk
×
185
       write(ou,formt)bk,bk,bk,bk,bk,'d','|','|','|','t','t','s','|','t','l', bk,'d',bk
×
186
       write(ou,formt)bk,bk,bk,bk,bk,'i','p','o','f','|','m','p','s','|','l', bk,'|',bk
×
187
       write(ou,formt)bk,bk,bk,bk,bk,'s','e','v','|','s','o','e','u','u','r', bk,'o',bk
×
188
       write(ou,formt)bk,bk,bk,bk,bk,'t','r','e','s','o','m','c','b','p','e', bk,'p',bk
×
189
       write(ou,formt)bk,bk,bk,bk,bk,'|','s','r','o','u','|','|','g','d','d','|','t',bk
×
190
       write(ou,formt)bk,bk,bk,bk,bk,'n','i','l','l','r','s','s','a','a','u','s','i',bk
×
191
       write(ou,formt)bk,bk,bk,bk,bk,'b','s','a','v','c','u','u','t','t','c','u','o',bk
×
192
       write (ou, formt) &
193
            'wallclocktime', 'efficiency', 'cost', 'nproc', 'layout', &
×
194
            'k','t','p','e','e','b','b','h','e','e','b','n',&
×
195
            'minnrow'
×
196
       write (ou,formt) ul, ul, ul, ul, ul, ul, ul, ul, ul, ul, ul, ul, ul, ul,&
×
197
            ul, ul, ul, ul
×
198

199
       n = size(state%optim%sorted_results)
×
200
       do i = 1, n
×
201
          call write_summary(state%optim%outunit,&
202
               state%optim%sorted_results(i), &
×
203
               state%optim%sorted_optimisations(i))
×
204
       end do
205
    end if
206
  end subroutine output_results
×
207

208
  !> FIXME : Add documentation
209
  subroutine write_summary(unt, results, optimisations)
×
210
    use optimisation_configuration, only: optimisation_results_type
211
    use overrides, only: optimisations_overrides_type
212
    implicit none
213
    integer, intent(in) :: unt
214
    type(optimisation_results_type), intent(in) :: results
215
    type(optimisations_overrides_type), intent(in) :: optimisations
216
    write(unt, &
217
         '(E11.4," ",F10.6," ",E11.4," ",I6," ",A6," ",&
218
         &L1," ",L1," ",L1," ",L1," ",L1," ",L1," ",L1," ",&
219
         &L1," ",L1," ",L1," ",L1," ",A1," ",I7)') &
220
         results%time, &
×
221
         results%efficiency, &
×
222
         results%cost, &
×
223
         results%nproc, &
×
224
         optimisations%layout, &
×
225
         optimisations%opt_redist_nbk, &
×
226
         optimisations%opt_redist_persist, &
×
227
         optimisations%opt_redist_persist_overlap,&
×
228
         optimisations%local_field_solve, &
×
229
         optimisations%opt_source, &
×
230
         optimisations%intmom_sub,&
×
231
         optimisations%intspec_sub,&
×
232
         optimisations%field_subgath,&
×
233
         optimisations%do_smart_update,&
×
234
         optimisations%field_local_allreduce,&
×
235
         optimisations%field_local_allreduce_sub,&
×
236
         optimisations%field_option(1:1), &
×
237
         optimisations%minnrow
×
238
  end subroutine write_summary
×
239

240
  !> FIXME : Add documentation
241
  subroutine optimise_simple(state)
×
242
    use gs2_main, only: prepare_optimisations_overrides
243
    type(gs2_program_state_type), intent(inout) :: state
244
    call prepare_optimisations_overrides(state)
×
245
    call optimise_layout(state)
×
246
  end subroutine  optimise_simple
×
247

248
  !> FIXME : Add documentation
249
  subroutine optimise_nprocs(state)
×
250
    use mp, only: proc0
251
    use ingen_mod, only: init_ingen, finish_ingen, report, sweet_spots
252
    use gs2_main, only: initialize_gs2, initialize_equations
253
    use gs2_main, only: finalize_gs2, finalize_equations
254
    implicit none
255
    type(gs2_program_state_type), intent(inout) :: state
256
    integer :: i
257

258
    state%init%opt_ov%override_nproc = .false.
×
259
    ! First measure performance using all procs
260
    call optimise_fields(state)
×
261

262
    call init_ingen
×
263
    call initialize_gs2(state)
×
264
    call initialize_equations(state)
×
265
    if (proc0) call report
×
266
    call finalize_equations(state)
×
267
    call finalize_gs2(state)
×
268

269
    ! Loop through all sweet spots and measure performance
270
    do i = 1, size(sweet_spots)
×
271
       if (sweet_spots(i)%nproc > state%optim%nproc_max) exit
×
272

273
       ! If asked to check for inefficencies, check all proc numbers
274
       ! otherwise only check proc numbers that satisfy
275
       ! max_imbalance and max_unused_procs
276
       if (.not. (state%optim%min_efficiency > 0)) then
×
277
          if ( state%optim%max_unused_procs >= 0 .and. &
×
278
               (state%optim%nproc_max - sweet_spots(i)%nproc) >&
×
279
               state%optim%max_unused_procs ) cycle
×
280
          if ( state%optim%max_imbalance > 0.0 .and. &
×
281
               (state%optim%nproc_max - sweet_spots(i)%nproc) / &
×
282
               state%optim%nproc_max >&
283
               state%optim%max_imbalance ) cycle
×
284
       end if
285
       state%init%opt_ov%override_nproc = .true.
×
286
       state%init%opt_ov%nproc = sweet_spots(i)%nproc
×
287
       call optimise_fields(state)
×
288
    end do
289
    call finish_ingen
×
290
  end subroutine optimise_nprocs
×
291

292
  !> FIXME : Add documentation
293
  subroutine optimise_layout(state)
×
294
    implicit none
295
    type(gs2_program_state_type), intent(inout) :: state
296
    !> Measure default layout
297
    state%init%opt_ov%override_layout = .true.
×
298
    state%init%opt_ov%layout = 'lxyes'
×
299
    call optimise_nprocs(state)
×
300
    state%init%opt_ov%layout = 'lexys'
×
301
    call optimise_nprocs(state)
×
302
    state%init%opt_ov%layout = 'xyles'
×
303
    call optimise_nprocs(state)
×
304
    state%init%opt_ov%layout = 'yxles'
×
305
    call optimise_nprocs(state)
×
306
  end subroutine optimise_layout
×
307

308
  !> FIXME : Add documentation
309
  subroutine optimise_flags(state)
×
310
    implicit none
311
    type(gs2_program_state_type), intent(inout) :: state
312
    logical :: l1, l2, l3
313

314
    l1=.false.
×
315
    l2=.false.
×
316
    l3=.false.
×
317
    state%init%opt_ov%override_opt_redist_nbk = .true.
×
318
    state%init%opt_ov%opt_redist_nbk = .false.
×
319
    state%init%opt_ov%override_opt_redist_persist = .true.
×
320
    state%init%opt_ov%opt_redist_persist = .false.
×
321
    state%init%opt_ov%override_opt_redist_persist_overlap = .true.
×
322
    state%init%opt_ov%opt_redist_persist_overlap = .false.
×
323

324
    state%init%opt_ov%override_local_field_solve = .true.
×
325
    state%init%opt_ov%local_field_solve = .false.
×
326

327
    state%init%opt_ov%override_opt_source = .true.
×
328
    state%init%opt_ov%opt_source = .false.
×
329

330
    state%init%opt_ov%override_intmom_sub = .true.
×
331
    state%init%opt_ov%intmom_sub = .false.
×
332
    state%init%opt_ov%override_intspec_sub = .true.
×
333
    state%init%opt_ov%intspec_sub = .false.
×
334

335
    state%init%opt_ov%override_field_subgath = .true.
×
336
    state%init%opt_ov%field_subgath = .false.
×
337
    state%init%opt_ov%override_do_smart_update = .true.
×
338
    state%init%opt_ov%do_smart_update = .false.
×
339

340
    state%init%opt_ov%override_field_local_allreduce = .true.
×
341
    state%init%opt_ov%field_local_allreduce = .false.
×
342
    state%init%opt_ov%override_field_local_allreduce_sub = .true.
×
343
    state%init%opt_ov%field_local_allreduce_sub = .false.
×
344

345
    call measure_timestep(state)
×
346
    state%init%opt_ov%opt_redist_nbk = .true.
×
347
    call measure_timestep(state)
×
348
    l1 = state%optim%results%optimal
×
349
    state%init%opt_ov%opt_redist_persist = .true.
×
350
    call measure_timestep(state)
×
351
    l2 = state%optim%results%optimal
×
352
    state%init%opt_ov%opt_redist_persist_overlap = .true.
×
353
    call measure_timestep(state)
×
354
    l3 = state%optim%results%optimal
×
355

356
    ! Here we pick the optimal solution
357
    if (.not. l3) then
×
358
       state%init%opt_ov%opt_redist_persist_overlap = .false.
×
359
       if (.not. l2) then
×
360
          state%init%opt_ov%opt_redist_persist_overlap = .false.
×
361
          if (.not. l1) then
×
362
             state%init%opt_ov%opt_redist_nbk = .false.
×
363
          end if
364
       end if
365
    end if
366

367
    state%init%opt_ov%opt_source = .true.
×
368
    call measure_timestep(state)
×
369
    state%init%opt_ov%opt_source = state%optim%results%optimal
×
370

371
    state%init%opt_ov%local_field_solve = .true.
×
372
    call measure_timestep(state)
×
373
    state%init%opt_ov%local_field_solve = state%optim%results%optimal
×
374

375
    state%init%opt_ov%intmom_sub = .true.
×
376
    call measure_timestep(state)
×
377
    state%init%opt_ov%intmom_sub = state%optim%results%optimal
×
378

379
    state%init%opt_ov%intspec_sub = .true.
×
380
    call measure_timestep(state)
×
381
    l1 = state%optim%results%optimal
×
382
    if (state%init%opt_ov%field_option == "local") then
×
383
       ! Why do we tie intspec_sub to these other field flags given
384
       ! intspec_sub should impact more than just the field calculation?
385
       state%init%opt_ov%field_local_allreduce = .true.
×
386
       call measure_timestep(state)
×
387
       l2 = state%optim%results%optimal
×
388
       state%init%opt_ov%field_local_allreduce_sub = .true.
×
389
       call measure_timestep(state)
×
390
       l3 = state%optim%results%optimal
×
391
       if (.not. l3) then
×
392
          state%init%opt_ov%field_local_allreduce_sub = .false.
×
393
          if (.not. l2) then
×
394
             state%init%opt_ov%field_local_allreduce = .false.
×
395
             if (.not. l1) then
×
396
                state%init%opt_ov%intspec_sub = .false.
×
397
             end if
398
          end if
399
       end if
400
    else
401
       state%init%opt_ov%intspec_sub = state%optim%results%optimal
×
402
    end if
403

404
    if (state%init%opt_ov%field_option == "implicit") then
×
405
       state%init%opt_ov%field_subgath = .true.
×
406
       call measure_timestep(state)
×
407
       state%init%opt_ov%field_subgath = state%optim%results%optimal
×
408
    else if (state%init%opt_ov%field_option == "local") then
×
409
       state%init%opt_ov%do_smart_update = .true.
×
410
       call measure_timestep(state)
×
411
       state%init%opt_ov%do_smart_update = state%optim%results%optimal
×
412
    end if
413
  end subroutine optimise_flags
×
414

415
  !> FIXME : Add documentation
416
  subroutine optimise_fields(state)
×
417
    implicit none
418
    type(gs2_program_state_type), intent(inout) :: state
419
    state%init%opt_ov%override_field_option = .true.
×
420
    state%init%opt_ov%field_option = "implicit"
×
421
    call optimise_flags(state)
×
422
    state%init%opt_ov%field_option = "local"
×
423
    state%init%opt_ov%override_minnrow = .true.
×
424
    ! Why do we try different minnrow but then don't keep track of which of
425
    ! these is actually optimal?
426
    state%init%opt_ov%minnrow = 64
×
427
    call optimise_flags(state)
×
428
    state%init%opt_ov%minnrow = 32
×
429
    call optimise_flags(state)
×
430
    state%init%opt_ov%minnrow = 128
×
431
    call optimise_flags(state)
×
432
  end subroutine optimise_fields
×
433

434
  !> FIXME : Add documentation
435
  subroutine measure_timestep(state)
×
436
    use gs2_main, only: gs2_program_state_type, evolve_equations
437
    use gs2_main, only: initialize_gs2, initialize_equations
438
    use gs2_main, only: finalize_gs2, finalize_equations
439
    use overrides, only: optimisations_overrides_type
440
    use optimisation_configuration, only: optimisation_results_type
441
    use mp, only: proc0, broadcast, mp_abort
442
    use iso_fortran_env, only: output_unit
443
    implicit none
444
    type(gs2_program_state_type), intent(inout) :: state
445
    type(optimisations_overrides_type), &
446
         dimension(:), allocatable :: sorted_opts_temp
×
447
    type(optimisation_results_type), &
448
         dimension(:), allocatable :: sorted_res_temp
×
449
    integer :: i,n, iresult
450
    real :: t, cost
451
    logical :: completed_steps
452

453
    completed_steps = .true.
×
454

455
    call initialize_gs2(state)
×
456
    call initialize_equations(state)
×
457
    call evolve_equations(state, state%optim%nstep_measure)
×
458
    if (state%included .and. state%istep_end /= state%optim%nstep_measure) then
×
459
       completed_steps = .false.
×
460
       write(*,*) 'istep_end', state%istep_end, state%optim%nstep_measure
×
461
    end if
462
    call finalize_equations(state)
×
463
    call finalize_gs2(state)
×
464
    if (.not. completed_steps) &
×
465
         call mp_abort('Optimisation has failed because gs2 is not completing &
466
         & the required number of steps. It may be hitting a convergence &
467
         & criterion, or a time limit, or it may be a numerical instability. &
468
         & Check exit_when_converged, avail_cpu_time, omegatol, omegatinst.',&
469
         .true.)
×
470

471

472
    if (state%optim%measure_all) then
×
473
       t = state%timers%advance(1)/real(state%optim%nstep_measure)
×
474
    else
475
       t = state%timers%timestep(1)/real(state%optim%nstep_measure)
×
476
    endif
477
    cost = t*real(state%nproc_actual)
×
478
    call broadcast(t)
×
479
    call broadcast(cost)
×
480
    state%optim%results%nproc = state%nproc_actual
×
481
    call broadcast(state%optim%results%nproc)
×
482

483
    state%optim%results%time = t
×
484
    state%optim%results%cost = cost
×
485

486
    if (t < state%optim%results%optimal_time .or. &
×
487
         state%optim%results%optimal_time < 0.0) then
488
       state%optim%results%optimal_time = t
×
489
       state%optim%results%optimal = .true.
×
490
    end if
491
    if (cost < state%optim%results%optimal_cost .or. &
×
492
         state%optim%results%optimal_cost < 0.0) then
493
       state%optim%results%optimal_cost = cost
×
494
    end if
495

496
    n = size(state%optim%sorted_results)
×
497
    if (n > 0) then
×
498
       sorted_opts_temp = state%optim%sorted_optimisations(1:n)
×
499
       sorted_res_temp = state%optim%sorted_results
×
500
    end if
501

502
    deallocate(state%optim%sorted_optimisations)
×
503
    deallocate(state%optim%sorted_results)
×
504
    allocate(state%optim%sorted_optimisations(n+1))
×
505
    allocate(state%optim%sorted_results(n+1))
×
506

507
    i = 1
×
508
    do
×
509
       if (i > n) exit
×
510
       ! If the time recorded for a previous setup is worse than this
511
       ! one then don't bother saving it any more. Doesn't this mean
512
       ! we only ever save at most two setups (the best so far and the
513
       ! current test case)? At this point yes, but we copy in the
514
       ! slower cases just after we've stored the current result. This
515
       ! is how we construct a sorted set of results, basically
516
       ! construct the sorted list case by case using something like
517
       ! insertion sort.
518
       if (sorted_res_temp(i)%time > t) exit
×
519
       state%optim%sorted_optimisations(i) = sorted_opts_temp(i)
×
520
       state%optim%sorted_results(i) = sorted_res_temp(i)
×
521
       i = i + 1
×
522
    end do
523
    ! Store the current test case results
524
    state%optim%sorted_optimisations(i) = state%init%opt_ov
×
525
    state%optim%sorted_results(i) = state%optim%results
×
526
    iresult = i
×
527

528
    ! Copy in the cases which are slower than the current case
529
    if (i /= n + 1) then
×
530
       state%optim%sorted_optimisations(i+1:) = sorted_opts_temp(i:)
×
531
       state%optim%sorted_results(i+1:) = sorted_res_temp(i:)
×
532
    end if
533

534
    ! Recalculate and store the optimal cost results for all cases to date
535
    do i = 1, size(state%optim%sorted_results)
×
536
       state%optim%sorted_results(i)%optimal_cost = &
×
537
            state%optim%results%optimal_cost
×
538
       state%optim%sorted_results(i)%optimal_time = &
×
539
            state%optim%results%optimal_time
×
540
       state%optim%sorted_results(i)%efficiency = &
×
541
            state%optim%sorted_results(i)%optimal_cost / &
×
542
            state%optim%sorted_results(i)%cost
×
543
    end do
544

545
    if(proc0) call write_summary(output_unit, state%optim%sorted_results(iresult), &
×
546
         state%optim%sorted_optimisations(iresult))
×
547

548
    deallocate(sorted_opts_temp, sorted_res_temp)
×
549
  end subroutine measure_timestep
×
550
end module gs2_optimisation
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