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

gyrokinetics / gs2 / 2078172070

03 Oct 2025 09:22AM UTC coverage: 10.835% (+0.03%) from 10.806%
2078172070

push

gitlab-ci

David Dickinson
Merged in experimental/user_controlled_output_base_name (pull request #1184)

5049 of 46599 relevant lines covered (10.83%)

119786.99 hits per line

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

0.0
/src/gs2_main.fpp
1
!> This module provides the external interface to gs2. It contains functions
2
!> to initialize gs2, functions to run gs2, functions to finalize gs2 and
3
!> functions to override/tweak gs2 parameters.
4
!>
5
!> The main entry point is [[run_gs2]], which takes care of initialising all the
6
!> subsystems, solving the equations (either the time advance or eigensolver),
7
!> and then finalising all the subsystems. This looks something like:
8
!>
9
!>
10
!>     ! An object holding the state of the simulationg
11
!>     type(gs2_program_state_type) :: state
12
!>     ! Initialisation of subsystems
13
!>     call initialize_gs2(state)
14
!>     call initialize_equations(state)
15
!>     ! Solve the equations
16
!>     if (state%do_eigsolve) then
17
!>       call run_eigensolver(state)
18
!>     else
19
!>       call evolve_equations(state, state%nstep)
20
!>     end if
21
!>     ! Clean up
22
!>     call finalize_equations(state)
23
!>     call finalize_gs2(state)
24
!>
25
!> You can manipulate the [[gs2_program_state]] before running gs2.
26
!>
27
!> It is very important to note that just because this interface is presented
28
!> in an object-oriented way, it does not, unfortunately, mean that the entire
29
!> program state, i.e. data arrays etc, is encapsulated in the gs2_program_state
30
!> object. In fact most data is stored globally as module public variables.
31
!> The gs2_program_state object is provided for convenience, as a way of
32
!> monitoring the execution state of gs2, and because it is hoped that in the
33
!> future gs2 will, in fact, be thread safe and have proper data encapsulation.
34
!> A particular consequence of this is that only one instance of the
35
!> gs2_program_state object should exist on each process, i.e. in a given
36
!> memory space.
37
module gs2_main
38
  use gs2_init, only: init_type, init_level_list
39
  use optimisation_configuration, only: optimisation_type
40
  use constants, only: run_name_size
41
  use exit_codes, only: exit_code, EXIT_NOT_REQUESTED
42
  use command_line_handling, only: command_line_settings_type
43
  use mp, only: mp_comm_null
44
  implicit none
45
  private
46
  public :: run_gs2, finish_gs2, gs2_program_state_type, reset_time_step
47
  public :: initialize_gs2, finalize_equations, finalize_gs2
48
  public :: initialize_equations, evolve_equations, run_eigensolver
49
  public :: prepare_optimisations_overrides, finalize_overrides, initialize_wall_clock_timer
50
  public :: prepare_initial_values_overrides, set_initval_overrides_to_current_vals
51

52
  !> Holds data pertaining to some of the main algorithm timers.
53
  type gs2_timers_type
54
    real :: init(2) = 0.
55
    real :: advance(2) = 0.
56
    real :: timestep(2) = 0.
57
    real :: finish(2) = 0.
58
    real :: total(2) = 0.
59
    real :: diagnostics(2)=0.
60
    real :: eigval(2)=0.
61
    real :: main_loop(2) = 0.
62
  end type gs2_timers_type
63

64
  !> The object which specifies and records the gs2 program state.
65
  !> Some attributes of the object, like mp_comm_external, are
66
  !> designed to be directly manipulated by the user, and some are
67
  !> designed to store program state information and be manipulated
68
  !> internally, like `init%level`.
69
  type gs2_program_state_type
70
     !> A type for keeping track of the current initialization level
71
     !> of gs2, as well as storing all the overrides. See
72
     !> gs2_init::init_type for more information.
73
     type(init_type) :: init
74
     !> Do not set manually. If fewer than the available number of
75
     !> processors are being used, this is true for the processors that
76
     !> are active and false for those that lie idle.
77
     logical :: included = .true.
78
     !> Derived type [[gs2_timers_type]] holding some of the
79
     !> timer data for this run.
80
     type(gs2_timers_type) :: timers
81
     !> The exit flag is set to true by any part of the main timestep
82
     !> loop that wants to cause the loop to exit
83
     logical :: exit = .false.
84
     !> Whether the run has converged to a stationary state
85
     logical :: converged = .false.
86
     !> Whether to run the eigenvalue solver or not. Set equal to the
87
     !> input value in intialize_equations. Typically only important
88
     !> for the standalone gs2 program
89
     logical :: do_eigsolve = .false.
90
     !> This parameter is set equal to run_parameters::nstep in
91
     !> initialize_equations and is the maximum number of timesteps
92
     !> that can be run without reinitalising the diagnostics.  Do not
93
     !> modify. We should make this private but it is used in testing
94
     !> currently so we don't.
95
     integer :: nstep
96
     !> Gets set to the final value of istep in evolve equations. Any
97
     !> future calls to evolve_equations will increment this
98
     !> further. A call to finalize_equations will set it back to
99
     !> 0. Note that setting this manually is NOT advised.
100
     integer :: istep_end = 0
101
     !> Verbosity at which we print out debug messages
102
     integer :: verb = 3
103
     !> Parameters pertaining to cases when gs2 is being used as a
104
     !> library. external_job_id is not to be confused with the parameter
105
     !> job in mp, which identifies the subjob if running in list mode
106
     !> or with nensembles > 1
107
     integer :: external_job_id = -1
108
     !> is_external_job should be set to true when GS2 is being used
109
     !> as a library. Perhaps this could just check external_job_id instead?
110
     logical :: is_external_job = .false.
111
     !> If true, print full timing breakdown.
112
     logical :: print_full_timers = .true.
113
     !> If true, print run time or full timing breakdown, depending on
114
     !> the value of print_full_timers
115
     logical :: print_times = .true.
116
     !> MPI communicator. This MUST be set.
117
     integer :: mp_comm = mp_comm_null
118
     !> This is set in initialize_gs2 to the number of procs actually used
119
     integer :: nproc_actual = -1
120
     !> If true then we end up passing [[gs2_program_state_type:run_name]]
121
     !> as the base file name.
122
     logical :: run_name_external = .false.
123
     !> The run name to pass to [[init_file_utils]] if `run_name_external` is
124
     !> set to true. GS2 then uses this in place of any input file name passed
125
     !> at the command line.
126
     character(run_name_size) :: run_name = 'gs'
127
     !> If true then skip the call to diagnostics calculations in
128
     !> evolve_equations (main loop and after main loop)
129
     logical :: skip_diagnostics = .false.
130
     !> If true then ignore any requests to change the time step in
131
     !> evolve_equations as a part of the time advance algorithm
132
     logical :: dont_change_timestep = .false.
133
     !> Whether this is a list mode run
134
     logical :: list = .false.
135
     !> The number of identical runs happening simultaneously (used
136
     !> for ensemble averaging). Cannot be used in conjunction with
137
     !> list mode.
138
     integer :: nensembles = 1
139
     !> Optimisation configuration
140
     type(optimisation_type) :: optim
141
     !> Reason for end of simulation
142
     type(exit_code) :: exit_reason = EXIT_NOT_REQUESTED
143
     !> Flags and information derived from the command line arguments
144
     type(command_line_settings_type) :: command_line_settings
145
   contains
146
     procedure :: write_used_inputs_file => write_used_inputs_file_bound
147
     procedure :: action_command_line_settings
148
  end type gs2_program_state_type
149

150
contains
151

152
  !> Run whatever checks we can early in the initialisation process
153
  !> which might lead us to abort. Intended to help save compute resource
154
  !> by halting as early as we can.
155
  subroutine early_abort_checks(state)
×
156
    use config_collection, only: gs2_config_type
157
    use gs2_diagnostics, only: check_restart_file_writeable
158
    use gs2_save, only: set_restart_file
159
    use init_g, only: add_restart_dir_to_file, set_restart_dir
160
    use file_utils, only: run_name, dirname
161
    type(gs2_program_state_type), intent(inout) :: state
162
    logical :: logic_dummy
163

164
    associate(init_g => state%init%config%init_g_config, &
165
         diag => state%init%config%diagnostics_config)
166
      init_g%restart_file = trim(run_name)//".nc"
×
167
      call add_restart_dir_to_file(init_g%restart_dir, init_g%restart_file)
×
168
      call set_restart_file(init_g%restart_file)
×
169
      call set_restart_dir(dirname(init_g%restart_file))
×
170
      ! Use logic_dummy for extra_files as we can't change save_distfn now and it won't
171
      ! lead to an abort anyway so suppress warning message.
172
      call check_restart_file_writeable(diag%file_safety_check, diag%save_for_restart, &
173
           logic_dummy, diag%make_restart_dir)
×
174
    end associate
175
  end subroutine early_abort_checks
×
176

177
  subroutine action_command_line_settings(self)
×
178
    use ingen_mod, only : run_ingen
179
    use mp, only: proc0, finish_mp
180
    use file_utils, only: init_file_utils, finish_file_utils
181
    class(gs2_program_state_type), intent(inout) :: self
182

183
    associate(settings=>self%command_line_settings)
184
      ! Set input overides from command line options
185
      if (allocated(settings%input_variable_set)) &
×
186
           call self%init%config%set_from_strings(settings%input_variable_set)
×
187

188
      ! Now load basic settings from the input file, this will skip those
189
      ! set on the command line
190
      call self%init%config%populate_from_file
×
191
      ! We would usually rely on the init system to do this but
192
      ! we ideally stay as the basic level whilst initialising the code
193
      call self%init%config%set_configs()
×
194

195
      ! Note we have not updated any of the the configs based on the --set arguments
196
      ! yet which means the check/parse options will work on the raw input and not
197
      ! the updated form. This means they might not perfectly reflect the actual intended
198
      ! state. We should perhaps look at deferring these checks until later in the
199
      ! initialisation process.
200
      if (settings%check_input) then
×
201
         if (proc0) call run_ingen(input_file=settings%input_file)
×
202
         call finish_mp
×
203
         stop
×
204
      end if
205

206
      if (settings%parse_input) then
×
207
         call early_abort_checks(self)
×
208
         if (proc0) write(*, '(a)') "Input file '" // settings%input_file // "' parsed successfully."
×
209
         call finish_file_utils
×
210
         call finish_mp
×
211
         stop
×
212
      end if
213
    end associate
214
  end subroutine action_command_line_settings
×
215

216
  !> Starts the global wall clock timer used by check time. This is
217
  !> useful if you have multiple copies of gs2 running but you don't
218
  !> want to start them all at the same time, but you want them all to
219
  !> respect avail_cpu_time
220
  subroutine initialize_wall_clock_timer
×
221
    use job_manage, only: init_checktime
222
    call init_checktime
×
223
  end subroutine initialize_wall_clock_timer
×
224

225
  !> Initialise message passing, open the input file, split the
226
  !> communicator if running in list mode or if nensembles > 1,
227
  !> initialize the timers. After calling this function, gs2 reaches
228
  !> init\%level = basic. If it is desired to provide an external
229
  !> commuicator or set the input file name externally, these should
230
  !> be set before calling this function.
231
  subroutine initialize_gs2(state, header_in, quiet)
×
232
    use file_utils, only: init_file_utils, run_name
233
    use gs2_init, only: init_gs2_init
234
    use job_manage, only: time_message, job_fork
235
    use job_manage, only: init_checktime
236
    use mp, only: init_mp, broadcast, job, nproc, proc0, iproc, get_processor_name
237
    use mp, only: use_nproc, included, mp_comm, mp_comm_null
238
    use redistribute, only: using_measure_scatter
239
    use unit_tests, only: debug_message, set_job_id
240
    use runtime_tests, only: verbosity
241
    use standard_header, only: standard_header_type, get_default_header, set_default_header
242
    use optionals, only: get_option_with_default
243
#ifdef OPENMP
244
    use omp_lib, only: omp_get_num_threads
245
#endif
246
    implicit none
247
    type(gs2_program_state_type), intent(inout) :: state
248
    !> Header for files with build and run information
249
    type(standard_header_type), intent(in), optional :: header_in
250
    !> If true, don't print start-up messages/header
251
    logical, intent(in), optional :: quiet
252
    ! Actual value for optional `header` input
253
    type(standard_header_type) :: local_header
×
254
    ! Internal value for optional `quiet` input
255
    logical :: quiet_value
256
#ifdef OPENMP
257
    integer :: nthread
258
#endif
259

260
    if (state%init%level >= init_level_list%basic) then
×
261
       error stop "ERROR: Called initialize_gs2 twice &
262
        & without calling finalize_gs2? state%init%level on entry too high."
×
263
    end if
264

265
    ! Initialize the gs2 initialization system
266
    call init_gs2_init()
×
267

268
    state%init%level = init_level_list%basic
×
269

270
    !Ensure the job id reported in debug messages is set to something before we call debug message. Note
271
    !that this may get set to a different value later in the Initialisation.
272
    call set_job_id(0)
×
273
    call debug_message(4, 'gs2_main::initialize_gs2 starting initialization')
×
274

275
    call init_mp(state%mp_comm)
×
276
    call debug_message(state%verb, 'gs2_main::initialize_gs2 initialized mp')
×
277

278
    if (verbosity() >= 3) write(*, '("Processor rank ",I0," with name ",A)') iproc, get_processor_name()
×
279

280
    if (present(header_in)) call set_default_header(header_in)
×
281
    local_header = get_default_header()
×
282

283
    quiet_value = get_option_with_default(quiet, .false.)
×
284

285
    call initialize_wall_clock_timer
×
286

287
    ! If optimisations say to use a subset of available processors
288
    ! create the communicator for this here.
289
    if (state%init%opt_ov%is_initialised()) then
×
290
       if (state%init%opt_ov%override_nproc .and. state%init%opt_ov%nproc /= nproc) then
×
291
          state%init%opt_ov%old_comm = mp_comm
×
292
          call use_nproc(state%init%opt_ov%nproc)
×
293
       end if
294
    else
295
      state%init%opt_ov%old_comm = mp_comm_null
×
296
    end if
297
    state%included = included
×
298
    state%nproc_actual = nproc
×
299
    if (.not. state%included) return
×
300

301
    if (state%is_external_job) then 
×
302
      call broadcast(state%external_job_id)
×
303
      call set_job_id(state%external_job_id)
×
304
    end if
305

306
    call reset_timers(state%timers)
×
307
  
308
    if (proc0) then
×
309
      ! Report number of processors being used
310
      if (.not. quiet_value) then
×
311
         write(*, '(a)') local_header%to_string(comment_character=" ")
×
312
         if (state%external_job_id >= 0) then
×
313
            write(*, '(a, i0, a)', advance="no") "External job ", state%external_job_id, " "
×
314
         end if
315
         write(*, '(a, i0, a)', advance="no") "Running on ", nproc, " processor"
×
316
         ! Pluralise processor
317
         if (nproc > 1) write(*, '(a)', advance="no") "s"
×
318
#ifdef OPENMP
319
         !$OMP PARALLEL
320
         nthread = omp_get_num_threads()
321
         !$OMP END PARALLEL
322
         write(*, '(A, I0, A)',advance="no") " with ", nthread, " thread"
323
         ! Pluralise thread
324
         if (nthread > 1) write(*, '(a)', advance="no") "s"
325
#endif
326
         ! Make sure we still get a blank line
327
         write(*,*) new_line('a')
×
328
      end if
329

330
      ! Call init_file_utils, ie. initialize the run_name, checking
331
      !  whether we are doing a list of runs.
332
      ! Until the logic of init_file_utils is fixed we set trin_run
333
      ! when an external file name has been provided... this prevents
334
      ! it overriding the name from the command line.
335
      if (allocated(state%command_line_settings%input_file)) then
×
336
         call init_file_utils (state%list, trin_run = state%run_name_external, &
337
              name = state%run_name, n_ensembles = state%nensembles, &
338
              input_file = state%command_line_settings%input_file, &
339
              output_base_name = state%command_line_settings%output_base)
×
340
      else
341
         call init_file_utils (state%list, trin_run = state%run_name_external, &
342
              name = state%run_name, n_ensembles = state%nensembles)
×
343
      end if
344

345
      call debug_message(state%verb, 'gs2_main::initialize_gs2 initialized file_utils')
×
346
    end if
347
    
348
    call broadcast (state%list)
×
349
    call debug_message(state%verb, 'gs2_main::initialize_gs2 broadcasted list')
×
350

351
    if (state%list) then
×
352
       call job_fork
×
353
       call set_job_id(job)
×
354
       call debug_message(state%verb, 'gs2_main::initialize_gs2 called job fork')
×
355
    else if (state%nensembles > 1) then 
×
356
       call job_fork (n_ensembles=state%nensembles)
×
357
       call debug_message(state%verb, &
358
         'gs2_main::initialize_gs2 called job fork (nensembles>1)')
×
359
    end if
360

361
    call time_message(.false.,state%timers%total,' Total')
×
362

363
    ! Pass run name to other procs
364
    call broadcast (run_name)
×
365
    call debug_message(state%verb, 'gs2_main::initialize_gs2 run_name = '//trim(run_name))
×
366

367
    ! Process command line settings and corresponding actions
368
    call state%action_command_line_settings
×
369

370
    ! Check for early aborts
371
    call early_abort_checks(state)
×
372

373
    !Set using_measure_scatter to indicate we want to use in "gather/scatter" timings
374
    using_measure_scatter = .false.
×
375

376
    call time_message(.false.,state%timers%total,' Total')
×
377

378
    call debug_message(state%verb, 'gs2_main::initialize_gs2 finished')
×
379

380
  end subroutine initialize_gs2
×
381

382
  !> Initialize all the modules which are used to evolve the
383
  !> equations. After calling this function, gs2 reaches `init%level = full`.
384
  subroutine initialize_equations(state)
×
385
    use job_manage, only: time_message
386
    use run_parameters, only: nstep, do_eigsolve
387
    use unit_tests, only: debug_message
388
    use gs2_io, only: get_netcdf_file_id, nc_command_string
389
    implicit none
390
    type(gs2_program_state_type), intent(inout) :: state
391

392
    if (.not. state%included) return
×
393
    call debug_message(state%verb, 'gs2_main::initialize_equations starting')
×
394
    call time_message(.false.,state%timers%total,' Total')
×
395
    call time_message(.false., state%timers%init,' Initialization')
×
396

397
    ! This triggers initializing of all the grids, all the physics parameters
398
    ! and all the modules which solve the equations and the diagnostics
399
    call state%init%init(init_level_list%full)
×
400

401
    if (state%command_line_settings%initialised) &
×
402
         call nc_command_string(get_netcdf_file_id(), &
403
         state%command_line_settings%full_command)
×
404

405
    call time_message(.false.,state%timers%init,' Initialization')
×
406

407
    ! Set defaults. These are typically only important
408
    ! for the standalone gs2 program
409
    state%nstep = nstep
×
410
    state%do_eigsolve = do_eigsolve
×
411

412
    call debug_message(state%verb, 'gs2_main::initialize_equations finished')
×
413
    call time_message(.false.,state%timers%total,' Total')
×
414
  end subroutine initialize_equations
415

416
  !> Run the initial value solver. nstep_run must
417
  !> be less than or equal to `state%nstep`, which is
418
  !> set from the input file. The cumulative number of
419
  !> steps that can be run cannot exceed `state%nstep`,
420
  !> Examples:
421
  !>
422
  !>      call evolve_equations(state, state%nstep) ! Basic run
423
  !>
424
  !> Note that these two calls:
425
  !>
426
  !>      call evolve_equations(state, state%nstep/2)
427
  !>      call evolve_equations(state, state%nstep/2)
428
  !>
429
  !> will in general have the identical effect to the single call above.
430
  !> There are circumstances when this is not true,
431
  !> for example, if the first of the two calls to evolve_equations
432
  !> exits without running nstep/2 steps (perhaps because the
433
  !> growth rate has converged).
434
  !>
435
  !> This example will cause an error because the total number
436
  !> of steps exceeds `state%nstep`:
437
  !>
438
  !>      call evolve_equations(state, state%nstep/2)
439
  !>      call evolve_equations(state, state%nstep/2)
440
  !>      call evolve_equations(state, state%nstep/2)
441
  subroutine evolve_equations(state, nstep_run, header)
×
442
    use collisions, only: vnmult
443
    use dist_fn_arrays, only: gnew
444
    use fields, only: advance
445
    use gs2_diagnostics, only: nsave, loop_diagnostics
446
    use gs2_diagnostics_new, only: run_diagnostics, gnostics
447
    use gs2_reinit, only: check_time_step
448
    use gs2_save, only: gs2_save_for_restart
449
    use gs2_time, only: user_time, update_time, write_dt, user_dt
450
    use gs2_time, only: code_dt, code_dt_prev1, code_dt_prev2, code_dt_max
451
    use job_manage, only: time_message, checkstop, checktime
452
    use mp, only: proc0, scope, subprocs, broadcast
453
    use run_parameters, only: reset, has_phi, has_apar, has_bpar, nstep, max_sim_time
454
    use run_parameters, only: avail_cpu_time, margin_cpu_time, use_old_diagnostics
455
    use run_parameters, only: progress_frequency, ncheck_stop, save_timer_statistics
456
    use unit_tests, only: debug_message
457
    use standard_header, only: standard_header_type, get_default_header
458
    use exit_codes, only: EXIT_MAX_SIM_TIME
459
    use file_utils, only: open_output_file, close_output_file
460
    type(gs2_program_state_type), intent(inout) :: state
461
    type(standard_header_type), optional, intent(in) :: header
462
    integer :: istep, progress_unit
463
    integer, intent(in) :: nstep_run
464
    logical :: temp_initval_override_store, should_save_restart, show_progress
465
    integer :: istep_loop_start, istep_loop_max, istep_offset, nsteps_left
466
    real, dimension(2) :: progress_time
467
    real :: time_per_step
468
    character(len = 256) :: progress_message
469
    ! Actual value for optional `header` input
470
    type(standard_header_type) :: local_header
×
471

472
    if (.not. state%included) return
×
473

474
    local_header = get_default_header()
×
475
    if (present(header)) local_header = header
×
476

477
    call debug_message(state%verb, &
478
        'gs2_main::evolve_equations starting')
×
479

480
    temp_initval_override_store = state%init%initval_ov%override
×
481

482
    call time_message(.false.,state%timers%total,' Total')
×
483
    
484
    if (state%nensembles > 1) call scope (subprocs)
×
485

486
    call time_message(.false.,state%timers%main_loop,' Main Loop')
×
487

488
    ! Make sure exit is false before entering timestep loop
489
    state%exit = .false.
×
490

491
    call debug_message(state%verb, 'gs2_main::evolve_equations starting loop')
×
492

493
    progress_time = 0
×
494
    show_progress = proc0 .and. (progress_frequency > 0)
×
495
    if (show_progress .and. proc0) call open_output_file(progress_unit, '.progress')
×
496

497
    ! We run for nstep_run iterations, starting from whatever istep we got
498
    ! to in previous calls to this function. Note that calling
499
    ! finalize_equations resets state%istep_end
500
    istep_loop_start = state%istep_end + 1
×
501
    istep_loop_max = state%istep_end + nstep_run
×
502
    do istep = istep_loop_start, istep_loop_max
×
503
       if (istep > nstep) then
×
504
         if (proc0) write (*,*) 'Reached maximum number of steps allowed &
×
505
              & (set by nstep) without restarting diagnostics.'
×
506
         ! Should we set an exit_reason here?
507
         exit
×
508
       end if
509

510
       call time_message(.false.,state%timers%advance,' Advance time step')
×
511
       call time_message(.false.,progress_time,' Progress time')
×
512
       call debug_message(state%verb+1, 'gs2_main::evolve_equations calling advance')
×
513
       call time_message(.false.,state%timers%timestep,' Timestep')
×
514
       ! Try to take a time step
515
       call advance (istep)
×
516
       call time_message(.false.,state%timers%timestep,' Timestep')
×
517
       call debug_message(state%verb+1,'gs2_main::evolve_equations called advance')
×
518

519
       if(state%dont_change_timestep) reset = .false.
×
520

521
       !If the advance call has triggered a reset then change the timestep.
522
       !Currently this is triggered if immediate_reset is true and the nonlinear
523
       !cfl limit is exceeded.
524
       if (reset) then
×
525
         call prepare_initial_values_overrides(state)
×
526
         call debug_message(state%verb+1, 'gs2_main::evolve_equations resetting timestep')
×
527
         call set_initval_overrides_to_current_vals(state%init%initval_ov)
×
528
         state%init%initval_ov%override = .true.
×
529
         call reset_time_step (state%init, istep, state%exit, state%external_job_id)
×
530

531
         ! Now we've reset set the flag back to .false.
532
         reset = .false.
×
533

534
         ! If we've changed the timestep and have not decided to exit then
535
         ! we need to call advance to actually complete this timestep.
536
         if (.not. state%exit) call advance(istep)
×
537
       end if
538

539
       if (state%exit) exit
×
540

541
       call debug_message(state%verb+1, &
542
            'gs2_main::evolve_equations calling gs2_save_for_restart')
×
543

544
       should_save_restart = .false.
×
545
       if (use_old_diagnostics) then
×
546
          should_save_restart = (nsave > 0 .and. mod(istep, nsave) == 0)
×
547
       else
548
          should_save_restart = (gnostics%nsave > 0 .and. mod(istep, gnostics%nsave) == 0)
×
549
       end if
550
       if (should_save_restart) call gs2_save_for_restart (gnew, user_time, vnmult, &
×
551
            has_phi, has_apar, has_bpar, code_dt, code_dt_prev1, &
552
            code_dt_prev2, code_dt_max, header=local_header)
×
553

554
       call update_time
×
555
       call time_message(.false.,state%timers%diagnostics,' Diagnostics')
×
556

557
       call debug_message(state%verb+1, 'gs2_main::evolve_equations calling diagnostics')
×
558
       if (.not. state%skip_diagnostics) then 
×
559
         if (use_old_diagnostics) then 
×
560
           call loop_diagnostics (istep, state%exit)
×
561
         else 
562
           call run_diagnostics (istep, state%exit)
×
563
         end if
564
       end if
565

566
       if (state%exit) state%converged = .true.
×
567
       if (state%exit) call debug_message(state%verb+1, &
×
568
         'gs2_main::evolve_equations exit true after diagnostics')
×
569

570
       call time_message(.false.,state%timers%diagnostics,' Diagnostics')
×
571
       call time_message(.false.,state%timers%advance,' Advance time step')
×
572

573
       if (.not. state%exit) then
×
574
         call debug_message(state%verb+1, &
575
              'gs2_main::evolve_equations checking time step')
×
576

577
         !Note this should only trigger a reset for timesteps too small
578
         !as timesteps too large are already handled when immediate_reset is
579
         !.true. If immediate_reset is .false. then this is where we handle
580
         !all checking of the time step.
581
         call check_time_step(reset,state%exit)
×
582
         call debug_message(state%verb+1, &
583
              'gs2_main::evolve_equations checked time step')
×
584

585
         !If something has triggered a reset then reset here
586
         if (state%dont_change_timestep) reset = .false.
×
587
         if (reset) then
×
588
            call prepare_initial_values_overrides(state)
×
589
            call set_initval_overrides_to_current_vals(state%init%initval_ov)
×
590
            state%init%initval_ov%override = .true.
×
591
            call reset_time_step (state%init, istep, state%exit, state%external_job_id)
×
592

593
            ! Switch off the reset flag now, otherwise it can still be active
594
            ! on the next iteration.
595
            reset = .false.
×
596
         end if
597

598
         if ((mod(istep, ncheck_stop) == 0) .and. (.not.state%exit)) &
×
599
              call checkstop(state%exit,state%exit_reason)
×
600
         if (state%exit) call debug_message(state%verb+1, &
×
601
              'gs2_main::evolve_equations exit true after checkstop')
×
602
         if (.not.state%exit) call checktime(avail_cpu_time,state%exit,margin_cpu_time)
×
603
         if (state%exit) call debug_message(state%verb+1, &
×
604
              'gs2_main::evolve_equations exit true after checktime')
×
605
       end if
606
       call debug_message(state%verb+1, &
607
        'gs2_main::evolve_equations after reset and checks')
×
608

609
       state%istep_end = istep
×
610

611
       ! Check if the next step would exceed the maximum requested simulation time,
612
       ! and if so flag that we wish to exit. Only check this if we're not already exiting.
613
       if ((.not. state%exit) .and. user_time + user_dt > max_sim_time) then
×
614
          state%exit_reason = EXIT_MAX_SIM_TIME
×
615
          state%exit = .true.
×
616
       end if
617

618
       if (show_progress) then
×
619
          ! Have to split this from previous logic as we shouldn't call mod if
620
          ! progress_frequency is zero and we can't rely on short circuit logic
621
          if (mod(istep - istep_loop_start + 1, progress_frequency) == 0) then
×
622
             call time_message(.false.,progress_time,' Progress time')
×
623
             time_per_step = progress_time(1)/progress_frequency
×
624
             nsteps_left = min((istep_loop_max - istep), int((max_sim_time - user_time) / user_dt))
×
625
             write(progress_message, &
626
                  '("Done step ",I0," of ",I0," : Time/step ",G10.3," s ETA ",G10.3," s")') &
627
                  istep - istep_loop_start + 1, istep_loop_max - istep_loop_start + 1, &
×
628
                  time_per_step, nsteps_left * time_per_step
×
629
             write(6, '(A)') trim(progress_message)
×
630
             rewind(progress_unit)
×
631
             write(progress_unit, '(A)') trim(progress_message)
×
632
             ! Reset progress timer
633
             progress_time = 0
×
634
          end if
635
       end if
636

637
       if (state%exit) then
×
638
           call debug_message(state%verb, 'gs2_main::evolve_equations exiting loop')
×
639
          exit
×
640
       end if
641
    end do
642

643
    if (proc0 .and. show_progress) then
×
644
       write(progress_unit, '("Finished.")')
×
645
       call close_output_file(progress_unit)
×
646
    end if
647

648
    ! Try to ensure that we write the time dependent diagnostics at the end of the simulation
649
    ! even in cases where nstep does not have nwrite as a factor.
650
    if (.not. state%skip_diagnostics) then
×
651
       ! Note when we have completed all our iterations we pass istep - 1 as we assume istep has been 
652
       ! incremented once from the last step actually taken. In cases where we explicitly exit the loop
653
       ! we need to pass istep instead.
654
       istep_offset = 1
×
655
       if (state%exit) istep_offset = 0
×
656
       if (use_old_diagnostics) then
×
657
          call loop_diagnostics (istep - istep_offset, state%exit, force = .true.)
×
658
       else
659
          call run_diagnostics (istep - istep_offset, state%exit, force = .true.)
×
660
       end if
661
    end if
662

663
    call time_message(.false.,state%timers%main_loop,' Main Loop')
×
664
    if (proc0 .and. .not. state%is_external_job) call write_dt
×
665

666
    call time_message(.false.,state%timers%total,' Total')
×
667
    if (state%print_times) call print_times(state, state%timers)
×
668
    if (save_timer_statistics) call write_time_parallel_statistics(state%timers)
×
669

670
    ! We also restore the value of the override switch to what it
671
    ! was when this function was called.
672
    state%init%initval_ov%override = temp_initval_override_store
×
673
    call debug_message(state%verb,'gs2_main::evolve_equations finished')
×
674
  end subroutine evolve_equations
×
675

676
  subroutine reset_time_step(current_init, istep, my_exit, job_id)
×
677
    use gs2_reinit, only: prepare_reset_time_step, do_reset_time_step, time_reinit
678
    use gs2_init, only: init_type, init, init_level_list
679
    use run_parameters, only: reset
680
    use job_manage, only: time_message
681
    implicit none
682
    type(init_type), intent(inout) :: current_init
683
    integer, intent(in) :: istep
684
    logical, intent(in out) :: my_exit
685
    integer, intent (in), optional :: job_id
686
    logical :: reset_in
687
    call time_message(.false., time_reinit, ' Re-initialize')
×
688
    call prepare_reset_time_step(istep, my_exit)
×
689
    if (my_exit) return
×
690

691
    !First disable the reset flag so we can call
692
    !routines needed in reinit
693
    reset_in = reset
×
694
    reset = .false.
×
695

696
    call init(current_init, init_level_list%change_timestep)
×
697
    call do_reset_time_step(istep, my_exit, job_id)
×
698

699
    if (my_exit) then
×
700
       reset = reset_in
×
701
       return
×
702
    end if
703

704
    call init(current_init, init_level_list%full)
×
705
    call time_message(.false., time_reinit, ' Re-initialize')
×
706

707
    reset = reset_in
×
708
  end subroutine reset_time_step
709

710
  !> Employ the eigenvalue solver to seek eigenmodes using SLEPc
711
  subroutine run_eigensolver(state)
×
712
#ifdef WITH_EIG
713
#ifdef FIELDS_EIG
714
    use fields_eigval, only: init_eigval, finish_eigval, BasicSolve
715
#else
716
    use eigval, only: init_eigval, finish_eigval, BasicSolve
717
#endif
718
#endif 
719
    use job_manage, only: time_message
720
    use mp, only: mp_abort
721
    type(gs2_program_state_type), intent(inout) :: state
722
    if (.not. state%included) return
×
723
#ifdef WITH_EIG
724
   call time_message(.false.,state%timers%total,' Total')
725

726
   !Start timer
727
   call time_message(.false.,state%timers%eigval,' Eigensolver')
728

729
   !Initialise slepc and the default/input eigensolver parameters
730
   call init_eigval
731

732
   !Create a solver based on input paramters, use it to solve and
733
   !then destroy it.
734
   call BasicSolve
735

736
   !Tidy up
737
   call finish_eigval
738

739
   !Stop timer
740
   call time_message(.false.,state%timers%eigval,' Eigensolver')
741
#else
742
   call mp_abort("Eigensolver requires GS2 to be built with slepc/petsc", .true.)
×
743
#endif
744
   call time_message(.false.,state%timers%total,' Total')
×
745

746
  end subroutine run_eigensolver
747

748
  !> FIXME : Add documentation  
749
  subroutine finalize_equations(state)
×
750
    use job_manage, only: time_message
751
    use unit_tests, only: debug_message
752
    implicit none
753
    type(gs2_program_state_type), intent(inout) :: state
754

755
    if (.not. state%included) return
×
756

757
    call time_message(.false.,state%timers%finish,' Finished run')
×
758
    call time_message(.false.,state%timers%total,' Total')
×
759

760
    call debug_message(state%verb, 'gs2_main::finalize_equations starting')
×
761
    call state%init%init(init_level_list%basic)
×
762
    state%istep_end = 0
×
763
    call time_message(.false.,state%timers%finish,' Finished run')
×
764
    call time_message(.false.,state%timers%total,' Total')
×
765
  end subroutine finalize_equations
766

767
  !> FIXME : Add documentation  
768
  subroutine finalize_gs2(state, quiet)
×
769
    use file_utils, only: finish_file_utils
770
    use gs2_init, only: finish_gs2_init
771
    use job_manage, only: time_message
772
    use mp, only: finish_mp, proc0, barrier, unsplit_all, included, mp_comm_null
773
    use unit_tests, only: debug_message
774
    use standard_header, only: date_iso8601
775
    use optionals, only: get_option_with_default
776
    use run_parameters, only: save_timer_statistics
777
    implicit none
778
    type(gs2_program_state_type), intent(inout) :: state
779
    !> If true, don't print start-up messages/header
780
    logical, intent(in), optional :: quiet
781

782
    ! Internal value for optional `quiet` input
783
    logical :: quiet_value
784

785
    quiet_value = get_option_with_default(quiet, .false.)
×
786

787
    if (state%included) then
×
788
      if (state%init%level /= init_level_list%basic) then
×
789
        write  (*,*) "ERROR: Called finalize_gs2 at the &
790
          & wrong init_level (perhaps you have called finalize_gs2 &
791
          & without calling initialize_gs2, or without calling &
792
          & finalize_equations"
×
793
        stop 1
×
794
      end if
795

796
      call time_message(.false.,state%timers%total,' Total')
×
797

798
      call finish_gs2_init()
×
799

800
      if (proc0) call finish_file_utils
×
801

802
      call time_message(.false.,state%timers%finish,' Finished run')
×
803
      call time_message(.false.,state%timers%total,' Total')
×
804
      
805
      call debug_message(state%verb, 'gs2_main::finalize_gs2 calling print_times')
×
806

807
      if (state%print_times .and. .not. quiet_value) call print_times(state, state%timers)
×
808
      if (save_timer_statistics) call write_time_parallel_statistics(state%timers)
×
809
    end if
810

811
    if (state%init%opt_ov%is_initialised()) then
×
812
       if (state%init%opt_ov%override_nproc .and. &
×
813
            state%init%opt_ov%old_comm /= mp_comm_null) &
814
            call unsplit_all(state%init%opt_ov%old_comm)
×
815
    end if
816

817
    call barrier
×
818
    state%included = included
×
819

820
    call debug_message(state%verb, 'gs2_main::finalize_gs2 calling finish_mp')
×
821

822
    state%init%level = 0
×
823

824
    if (proc0 .and. (.not. quiet_value) ) write(*, '("Run finished at ",A)') date_iso8601()
×
825
  end subroutine finalize_gs2
×
826

827
  !> FIXME : Add documentation  
828
  subroutine prepare_optimisations_overrides(state)
×
829
    type(gs2_program_state_type), intent(inout) :: state
830
    if (.not. state%included) return
×
831
    call state%init%opt_ov%initialise()
×
832
  end subroutine prepare_optimisations_overrides
833

834
  !> FIXME : Add documentation  
835
  subroutine prepare_initial_values_overrides(state)
×
836
    use fields, only: force_maxwell_reinit
837
    use gs2_init, only: init_level_list
838
    use gs2_reinit, only: in_memory
839
    use gs2_layouts, only: g_lo
840
    use kt_grids, only: naky, ntheta0
841
    use theta_grid, only: ntgrid
842
    use dist_fn_arrays, only: gexp_3
843
    implicit none
844
    type(gs2_program_state_type), intent(inout) :: state
845
    if (.not. state%included) return
×
846
    ! Initialize to the level below so that overrides are triggered
847
    call state%init%init(init_level_list%override_initial_values-1)
×
848
    call state%init%initval_ov%initialise(ntgrid, ntheta0, naky, g_lo%llim_proc, &
849
         g_lo%ulim_alloc, force_maxwell_reinit=force_maxwell_reinit, &
850
         in_memory=in_memory, has_explicit_terms = allocated(gexp_3))
×
851
  end subroutine prepare_initial_values_overrides
852

853
  !> FIXME : Add documentation  
854
  subroutine set_initval_overrides_to_current_vals(initval_ov)
×
855
    use dist_fn_arrays, only: gnew, gexp_1, gexp_2, gexp_3
856
    use gs2_save, only: gs2_save_for_restart
857
    use mp, only: proc0, broadcast, mp_abort
858
    use collisions, only: vnmult
859
    use file_utils, only: error_unit
860
    use run_parameters, only: has_phi, has_apar, has_bpar
861
    use fields, only:  force_maxwell_reinit
862
    use fields_arrays, only: phinew, aparnew, bparnew
863
    use gs2_time, only: user_time, code_dt, code_dt_prev1, code_dt_prev2, code_dt_max
864
    use overrides, only: initial_values_overrides_type
865
    use antenna, only: dump_ant_amp
866
    use array_utils, only: copy
867
    implicit none
868
    type(initial_values_overrides_type), intent(inout) :: initval_ov
869

870
    if (.not.initval_ov%is_initialised()) &
×
871
      call mp_abort("Trying to set initial value overrides &
872
      & before they are initialized... have you called &
873
      & prepare_initial_values_overrides ? ", .true.)
×
874

875
    if(initval_ov%in_memory)then
×
876
      call copy(gnew, initval_ov%g)
×
877
      initval_ov%vnmult = vnmult
×
878
      if (allocated(initval_ov%gexp_1)) call copy(gexp_1, initval_ov%gexp_1)
×
879
      if (allocated(initval_ov%gexp_2)) call copy(gexp_2, initval_ov%gexp_2)
×
880
      if (allocated(initval_ov%gexp_3)) call copy(gexp_3, initval_ov%gexp_3)
×
881

882
      ! Do not use the value from [old_iface_]state%init%initval_ov%force_maxwell_reinit = initval_ov%force_maxwell_reinit as
883
      ! follows:
884
      !     if (.not. initval_ov%force_maxwell_reinit) then
885
      ! as was done previously. This is because this causes problems in gs2_init so we use the value from
886
      ! fields::force_maxwell_reinit directly (see comments in gs2_init for details). To use here the value from
887
      ! initval_ov%force_maxwell_reinit could result in inconsistent values being used in different parts of the code. Therefore, we
888
      ! now use the value from fields::force_maxwell_reinit directly here too.  Now that the reference to
889
      ! initval_ov%force_maxwell_reinit here has also been removed, this component is no longer referenced anywhere in the codebase.
890
      ! Therefore, the force_maxwell_reinit component has been completely removed from the initial_values_overrides_type derived
891
      ! type to avoid confusion in the future.
892
      if (.not. force_maxwell_reinit) then
×
893
         if(has_phi) call copy(phinew, initval_ov%phi)
×
894
         if(has_apar) call copy(aparnew, initval_ov%apar)
×
895
         if(has_bpar) call copy(bparnew, initval_ov%bpar)
×
896
      end if
897
    else ! if(.not.in_memory)then
898
      !Should really do this with in_memory=.true. as well but
899
      !not sure that we really need to as we never read in the dumped data.
900
      if (proc0) call dump_ant_amp
×
901

902
      call gs2_save_for_restart (gnew, user_time, vnmult, &
903
           has_phi, has_apar, has_bpar, code_dt, code_dt_prev1, code_dt_prev2, code_dt_max)
×
904
    endif
905

906
  end subroutine set_initval_overrides_to_current_vals
×
907

908
  !> FIXME : Add documentation  
909
  subroutine finalize_overrides(state)
×
910
    type(gs2_program_state_type), intent(inout) :: state
911
    if (state%init%initval_ov%is_initialised()) call state%init%initval_ov%finish()
×
912
  end subroutine finalize_overrides
×
913

914
  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
915
  !! Private subroutines
916
  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!
917

918
  !> Reset timers data to 0
919
  subroutine reset_timers(timers)
×
920
    use fft_work, only: time_fft
921
    use fields_arrays, only: time_field, time_field_mpi
922
    use fields_arrays, only: time_field_invert, time_field_invert_mpi
923
    use fields_arrays, only: time_dump_response, time_read_response
924
    use gs2_reinit, only: time_reinit
925
    use le_derivatives, only: time_vspace_derivatives, time_vspace_derivatives_mpi
926
    use nonlinear_terms, only: time_add_explicit_terms, time_add_explicit_terms_mpi
927
    use nonlinear_terms, only: time_add_explicit_terms_field
928
    use redistribute, only: reset_redist_times
929
    use mp, only: reset_mp_times
930
    type(gs2_timers_type), intent(inout) :: timers
931
    timers = gs2_timers_type()
×
932
    time_fft = 0. ; time_field = 0. ; time_field_mpi = 0. ; time_field_invert = 0.
×
933
    time_field_invert_mpi = 0. ; time_dump_response = 0. ; time_read_response = 0.
×
934
    time_reinit = 0. ; time_vspace_derivatives = 0. ; time_vspace_derivatives_mpi = 0.
×
935
    time_add_explicit_terms = 0. ; time_add_explicit_terms_mpi = 0.
×
936
    time_add_explicit_terms_field = 0.
×
937
    call reset_redist_times
×
938
    call reset_mp_times
×
939
  end subroutine reset_timers
×
940

941
  !> Gets statistics of passed real value across all processes.
942
  !> Intended for use with our timers.
943
  subroutine get_parallel_statistics(value_in, min_value, max_value,&
×
944
       & mean_value, proc0_value, iproc_min, iproc_max, values_out)
945
    use mp, only: nproc, iproc, sum_allreduce
946
    implicit none
947
    real, intent(in) :: value_in
948
    real, intent(out) :: min_value, max_value, mean_value, proc0_value
949
    integer, intent(out) :: iproc_min, iproc_max
950
    real, dimension(:), allocatable, intent(out), optional :: values_out
951
    real, dimension(:), allocatable :: values
×
952

953
    allocate(values(0:nproc-1))
×
954
    values = 0
×
955
    values(iproc) = value_in
×
956
    call sum_allreduce(values)
×
957
    if(present(values_out)) values_out = values
×
958

959
    min_value = minval(values)
×
960
    max_value = maxval(values)
×
961
    mean_value = sum(values)/nproc
×
962
    proc0_value = values(0)
×
963

964
    iproc_min = minloc(values, dim = 1) - 1
×
965
    iproc_max = maxloc(values, dim = 1) - 1
×
966
  end subroutine get_parallel_statistics
×
967

968
  !> Writes the timing information statistics to optional passed unit
969
  subroutine write_time_parallel_statistics(timers, report_unit)
×
970
    use file_utils, only: open_output_file, close_output_file
971
    use mp, only: proc0, get_mp_times
972
    use redistribute, only: get_redist_times
973
    use fft_work, only: time_fft
974
    use fields_arrays, only: time_field, time_field_mpi
975
    use fields_arrays, only: time_field_invert, time_field_invert_mpi
976
    use fields_arrays, only: time_dump_response, time_read_response
977
    use gs2_reinit, only: time_reinit
978
    use le_derivatives, only: time_vspace_derivatives, time_vspace_derivatives_mpi
979
    use nonlinear_terms, only: time_add_explicit_terms, time_add_explicit_terms_mpi
980
    use nonlinear_terms, only: time_add_explicit_terms_field
981
    implicit none
982
    !> Timing information
983
    type(gs2_timers_type), intent(in) :: timers
984
    integer, intent(in), optional :: report_unit
985
    integer :: unit
986
    real :: mp_total, mp_over, mp_coll, mp_ptp, mp_sync
987
    real :: redist_total, redist_mpi, redist_copy
988
    !> Helper type to hold timer data. There might be some
989
    !> utility in making this avaiable outside of this routine.
990
    type timer_data
991
       real :: time
992
       character(len=:), allocatable :: name
993
    end type timer_data
994
    type(timer_data), dimension(:), allocatable :: timer_dat
×
995
    integer :: i
996

997
    ! Make sure unit is set on proc0. Open an output file if required
998
    if (proc0) then
×
999
       if (present(report_unit)) then
×
1000
          unit = report_unit
×
1001
       else
1002
          call open_output_file(unit, '.timing_stats')
×
1003
       end if
1004
    end if
1005

1006
    call get_mp_times(mp_total, mp_over, mp_coll, mp_ptp, mp_sync)
×
1007
    call get_redist_times(redist_total, redist_mpi, redist_copy)
×
1008

1009
    allocate( timer_dat, source = [ &
×
1010
         timer_data(timers%init(1), "Initialization"), &
1011
         timer_data(time_field_invert(1), "field matrix invert"), &
1012
         timer_data(time_field_invert_mpi, "field matrix invert mpi"), &
1013
         timer_data(time_dump_response(1), "field matrix dump"), &
1014
         timer_data(time_read_response(1), "field matrix read"), &
1015
         timer_data(timers%advance(1), "Advance steps"), &
1016
#ifdef WITH_EIG
1017
         timer_data(timers%eigval(1), "Eigensolver"), &
1018
#endif
1019
         timer_data(time_field(1), "field solve"), &
1020
         timer_data(time_field_mpi, "field solve mpi"), &
1021
         timer_data(time_vspace_derivatives(1), "collisions"), &
1022
         timer_data(time_vspace_derivatives_mpi, "collisions mpi"), &
1023
         timer_data(time_add_explicit_terms(1), "explicit/nl"), &
1024
         timer_data(time_add_explicit_terms_mpi, "explicit/nl mpi"), &
1025
         timer_data(time_fft(1), "explicit/nl fft"), &
1026
         timer_data(time_add_explicit_terms_field(1), 'explicit/nl fields'), &
1027
         timer_data(timers%diagnostics(1), "diagnostics"), &
1028
         timer_data(time_reinit(1), "Re-initialize"), &
1029
         timer_data(redist_total, "Redistribute"), &
1030
         timer_data(redist_mpi, "redistribute mpi"), &
1031
         timer_data(redist_copy, "redistribute copy"), &
1032
         timer_data(timers%finish(1), "Finishing"), &
1033
         timer_data(mp_total, "MPI"), &
1034
         timer_data(mp_over, "Overheads"), &
1035
         timer_data(mp_coll, "Collectives"), &
1036
         timer_data(mp_ptp, "PTP"), &
1037
         timer_data(mp_sync, "Sync"), &
1038
         timer_data(timers%total(1), "Total") &
1039
         ])
×
1040

1041
    call write_parallel_statistics_header()
×
1042
    do i = 1, size(timer_dat)
×
1043
       call write_parallel_statistics(timer_dat(i)%time, timer_dat(i)%name)
×
1044
    end do
1045

1046
    ! If we opened it in this routine then close the opened output file
1047
    if (proc0 .and. .not. present(report_unit)) call close_output_file(unit)
×
1048

1049
  contains
1050
    subroutine write_parallel_statistics_header()
×
1051
      implicit none
1052
      if (proc0) then
×
1053
         write(unit, '(a,T25,4(a9," "),T70,a,T77,a)') "Region", &
×
1054
              "Min (s)", "Max (s)", "Mean (s)", "P0 (s)", &
×
1055
              "Ip min", "Ip max"
×
1056
         write(unit, '(83("-"))')
×
1057
      end if
1058
    end subroutine write_parallel_statistics_header
×
1059

1060
    subroutine write_parallel_statistics(time_value, name)
×
1061
      implicit none
1062
      real, intent(in) :: time_value
1063
      character(len=*), intent(in) :: name
1064
      real :: min_value, max_value, mean_value, proc0_value
1065
      integer :: iproc_min, iproc_max
1066

1067
      call get_parallel_statistics(time_value, &
1068
           min_value, max_value, mean_value, proc0_value, &
1069
           iproc_min, iproc_max)
×
1070

1071
      if (proc0) then
×
1072
         write(unit, '(a,T25,4(0pf9.3," "),T70,I0,T77,I0)') name, &
×
1073
           min_value, max_value, mean_value, proc0_value, &
×
1074
           iproc_min, iproc_max
×
1075
      end if
1076
    end subroutine write_parallel_statistics
×
1077
  end subroutine write_time_parallel_statistics
1078

1079
  !> Print timing information to standard output.
1080
  !>
1081
  !> Prints a full breakdown of timing information if `state%print_full_timers`
1082
  !> is true, otherwise just prints the total time.
1083
  subroutine print_times(state, timers)
×
1084
    use mp, only: proc0, min_reduce, max_reduce, sum_reduce, job
1085
    use mp, only: get_mp_times
1086
    use redistribute, only: get_redist_times
1087
    use fft_work, only: time_fft
1088
    use fields_arrays, only: time_field, time_field_mpi
1089
    use fields_arrays, only: time_field_invert, time_field_invert_mpi
1090
    use fields_arrays, only: time_dump_response, time_read_response
1091
    use gs2_reinit, only: time_reinit
1092
    use le_derivatives, only: time_vspace_derivatives, time_vspace_derivatives_mpi
1093
    use nonlinear_terms, only: time_add_explicit_terms, time_add_explicit_terms_mpi
1094
    use nonlinear_terms, only: time_add_explicit_terms_field
1095
#ifdef GS2_EXPERIMENTAL_ENABLE_MEMORY_USAGE
1096
    use memory_usage, only: print_memory_usage
1097
#endif
1098
    implicit none
1099
    !> Program state information, needed to print
1100
    type(gs2_program_state_type), intent(in) :: state
1101
    !> Timing information
1102
    type(gs2_timers_type), intent(in) :: timers
1103
    real :: mp_total, mp_over, mp_coll, mp_ptp, mp_sync
1104
    real :: redist_total, redist_mpi, redist_copy
1105

1106
    if (.not. proc0) return
×
1107

1108
    if (state%print_full_timers) then
×
1109
      call get_mp_times(mp_total, mp_over, mp_coll, mp_ptp, mp_sync)
×
1110
      call get_redist_times(redist_total, redist_mpi, redist_copy)
×
1111

1112
      !Blank line to force separation from other outputs
1113
      write(*, '("")')
×
1114
      write(*, '(" ", a)') formatted_time("Initialization", timers%init(1))
×
1115
      write(*, '("(", a, ")")') formatted_time("field matrix invert", time_field_invert(1))
×
1116
      write(*, '("(", a, ")")') formatted_time("field matrix invert mpi", time_field_invert_mpi)
×
1117
      write(*, '("(", a, ")")') formatted_time("field matrix dump", time_dump_response(1))
×
1118
      write(*, '("(", a, ")")') formatted_time("field matrix read", time_read_response(1))
×
1119
      write(*, '(" ", a)') formatted_time("Advance steps", timers%advance(1))
×
1120
#ifdef WITH_EIG
1121
      write(*, '(" ", a)') formatted_time("Eigensolver", timers%eigval(1))
1122
#endif
1123
      write(*, '("(", a, ")")') formatted_time("field solve", time_field(1))
×
1124
      write(*, '("(", a, ")")') formatted_time("field solve mpi", time_field_mpi)
×
1125
      write(*, '("(", a, ")")') formatted_time("collisions", time_vspace_derivatives(1))
×
1126
      write(*, '("(", a, ")")') formatted_time("collisions mpi", time_vspace_derivatives_mpi)
×
1127
      write(*, '("(", a, ")")') formatted_time("explicit/nl", time_add_explicit_terms(1))
×
1128
      write(*, '("(", a, ")")') formatted_time("explicit/nl mpi", time_add_explicit_terms_mpi)
×
1129
      write(*, '("(", a, ")")') formatted_time("explicit/nl fft", time_fft(1))
×
1130
      write(*, '("(", a, ")")') formatted_time("explicit/nl fields", time_add_explicit_terms_field(1))
×
1131
      write(*, '("(", a, ")")') formatted_time("diagnostics", timers%diagnostics(1))
×
1132
      write(*, '(" ", a)') formatted_time("Re-initialize", time_reinit(1))
×
1133
      write(*, '(" ", a)') formatted_time("Redistribute", redist_total)
×
1134
      write(*, '("(", a, ")")') formatted_time("redistribute mpi", redist_mpi)
×
1135
      write(*, '("(", a, ")")') formatted_time("redistribute copy", redist_copy)
×
1136
      write(*, '(" ", a)') formatted_time("Finishing", timers%finish(1))
×
1137
      write(*, '(" ", a)') formatted_time("MPI" ,mp_total)
×
1138
      write(*, '("(", a, ")")') formatted_time("Overheads", mp_over)
×
1139
      write(*, '("(", a, ")")') formatted_time("Collectives", mp_coll)
×
1140
      write(*, '("(", a, ")")') formatted_time("PTP", mp_ptp)
×
1141
      write(*, '("(", a, ")")') formatted_time("Sync", mp_sync)
×
1142
      write(*, '(" total from timer is:", 0pf9.2, " min", /)') timers%total(1) / 60.
×
1143
    else
1144
      if (state%external_job_id >= 0) then
×
1145
        write(*, '(a, i0, ", ")', advance="no") " External job ID: ", state%external_job_id
×
1146
      end if
1147
      if (state%list) then
×
1148
        write(*, '(a, i0, ", ")', advance="no") " Job ID: ", job
×
1149
      end if
1150

1151
      write(*, '("Total from timer is:", 0pf9.2," min")') state%timers%total(1)/60.
×
1152
    endif
1153

1154
#ifdef GS2_EXPERIMENTAL_ENABLE_MEMORY_USAGE
1155
    call print_memory_usage
1156
#endif
1157
  contains
1158
    !> Print a single formatted timer line
1159
    character(len=46) function formatted_time(name, timer)
×
1160
      !> Name of the timer
1161
      character(len=*), intent(in) :: name
1162
      !> Time in seconds
1163
      real, intent(in) :: timer
1164

1165
      write(formatted_time, "(a, T25, 0pf9.3, ' min', T40, 2pf5.1, ' %')") name, timer / 60., timer/timers%total(1)
×
1166
    end function formatted_time
×
1167
  end subroutine print_times
1168

1169
  !> The main entry point into GS2, runs a single GS2 simulation
1170
  !>
1171
  !> A complete, minimal use of this to run a single, complete
1172
  !> simulation is:
1173
  !>
1174
  !>     program gs2
1175
  !>       use mp, only: init_mp, mp_comm, finish_mp
1176
  !>       use gs2_main, only : run_gs2, gs2_program_state_type
1177
  !>       implicit none
1178
  !>       type(gs2_program_state_type) :: state
1179
  !>       call init_mp
1180
  !>       state%mp_comm = mp_comm
1181
  !>       call run_gs2(state)
1182
  !>       call finish_mp
1183
  !>     end program gs2
1184
  !>
1185
  !> This will initialise all the GS2 internals, evolve the equations
1186
  !> (or run the eigensolver), and then finalise the internals
1187
  !> (writing files to disk, deallocating memory, and so on).
1188
  !>
1189
  !> You can also not finalise the simulation, which can be useful if
1190
  !> you want read or modify the fields, for example. In this case,
1191
  !> you *must* call [[finish_gs2]] when you're done:
1192
  !>
1193
  !>     ! Optionally modify the state and input options
1194
  !>     call run_gs2(state, finalize=.false.)
1195
  !>     ! Do some interesting things
1196
  !>     call finish_gs2(state)
1197
  !>
1198
  !> This pattern is also useful if you want to run many GS2
1199
  !> simulations in the same process.
1200
  subroutine run_gs2(state, finalize, quiet)
×
1201
    use exit_codes, only: EXIT_NSTEP, EXIT_NOT_REQUESTED
1202
    use mp, only: proc0, init_mp
1203
    use optionals, only : get_option_with_default
1204
    implicit none
1205
    !> State of the GS2 simulation. Used to modify the behaviour of
1206
    !> GS2 and/or to programmatically get information about the
1207
    !> simulation on completion.
1208
    type(gs2_program_state_type), intent(inout) :: state
1209
    !> If `.true.` (default), then GS2 is finalised, end-of-simulation
1210
    !> diagnostics are computed, files are closed, arrays are
1211
    !> deallocated, and so on.
1212
    !>
1213
    !> If this is set to `.false.`, (for example, because you want to
1214
    !> read the state of the fields before the arrays are deallocated)
1215
    !> then you MUST pass in `state` and call [[finish_gs2]] with that
1216
    !> state object to ensure GS2 is finalised correctly.
1217
    logical, optional, intent(in) :: finalize
1218
    !> Optional passed through to intialize/finalize gs2 methods to suppress printing
1219
    logical, optional, intent(in) :: quiet
1220
    logical :: local_finalize
1221

1222
    local_finalize = get_option_with_default(finalize, .true.)
×
1223

1224
    call initialize_gs2(state, quiet = quiet)
×
1225
    call initialize_equations(state)
×
1226

1227
    ! Store a copy of the final configuration objects in our init structure
1228
    call state%init%config%get_configs()
×
1229
    call state%write_used_inputs_file()
×
1230

1231
    state%print_times = .false.
×
1232
    if (state%do_eigsolve) then
×
1233
      call run_eigensolver(state)
×
1234
    else
1235
      call evolve_equations(state, state%nstep)
×
1236
      if (state%exit_reason%is_identical(EXIT_NOT_REQUESTED)) state%exit_reason = EXIT_NSTEP
×
1237
    end if
1238
    if(proc0) call state%exit_reason%write_exit_file()
×
1239

1240
    if (local_finalize) then
×
1241
      state%print_times = .true.
×
1242
      call finish_gs2(state, quiet = quiet)
×
1243
    end if
1244
  end subroutine run_gs2
×
1245

1246
  !> Finish and cleanup a complete simulation
1247
  subroutine finish_gs2(state, quiet)
×
1248
    !> An existing, initialisation simulation state
1249
    type(gs2_program_state_type), intent(inout) :: state
1250
    logical, intent(in), optional :: quiet
1251
    call finalize_equations(state)
×
1252
    call finalize_gs2(state, quiet)
×
1253
  end subroutine finish_gs2
×
1254

1255
  !> Write an input file containing the current state of all input
1256
  !> parameters
1257
  subroutine write_used_inputs_file_bound(self)
×
1258
    class(gs2_program_state_type), intent(in) :: self
1259
    call write_used_inputs_file(self%init%config)
×
1260
  end subroutine write_used_inputs_file_bound
×
1261

1262
  !> Write an input file containing the current state of all input
1263
  !> parameters
1264
  subroutine write_used_inputs_file(config, header)
×
1265
    use mp, only: proc0
1266
    use file_utils, only: open_output_file, close_output_file, run_name
1267
    use config_collection, only: gs2_config_type
1268
    use standard_header, only: standard_header_type, get_default_header
1269
    type(gs2_config_type), intent(in), optional :: config
1270
    !> Header for files with build and run information
1271
    type(standard_header_type), intent(in), optional :: header
1272
    ! Actual value for optional `header` input
1273
    type(standard_header_type) :: local_header
×
1274
    ! Actual value for optional `config` input
1275
    type(gs2_config_type), allocatable :: local_config
×
1276
    ! File unit to write to
1277
    integer :: used_inputs_unit
1278

1279
    ! Only write this file on rank 0
1280
    if (.not. proc0) return
×
1281

1282
    local_header = get_default_header()
×
1283
    if (present(header)) local_header = header
×
1284

1285
    if (present(config)) then
×
1286
       local_config = config
×
1287
    else
1288
       allocate(local_config)
×
1289
       call local_config%get_configs()
×
1290
    end if
1291

1292
    call open_output_file(used_inputs_unit, ".used_inputs.in")
×
1293
    write(unit=used_inputs_unit, fmt='(a)') &
1294
         local_header%to_string( &
1295
         comment_character="! ", &
1296
         file_description="Input parameters as used by " // trim(run_name) &
1297
         )
×
1298

1299
    call local_config%write_to_unit(used_inputs_unit)
×
1300
    call close_output_file(used_inputs_unit)
×
1301
  end subroutine write_used_inputs_file
×
1302
end module gs2_main
×
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