• 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

4.21
/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 mp, only: mp_comm_null
43
  implicit none
44
  public :: run_gs2, finish_gs2, parse_command_line, gs2_program_state_type, reset_time_step
45
  public :: initialize_gs2, finalize_equations, finalize_gs2
46
  public :: initialize_equations, evolve_equations, run_eigensolver
47
  public :: prepare_optimisations_overrides, finalize_overrides, initialize_wall_clock_timer
48
  public :: prepare_initial_values_overrides, set_initval_overrides_to_current_vals
49

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

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

145
  private
146
 
147
contains
148

149
  !> Parse some basic command line arguments. Currently just 'version' and 'help'.
150
  !>
151
  !> This should be called before anything else, but especially before initialising MPI.
152
  subroutine parse_command_line()
4✔
153
    use git_version_mod, only: get_git_version
154
    use build_config, only : formatted_build_config
155
    use ingen_mod, only : run_ingen
156
    use mp, only: proc0, init_mp, finish_mp
157
    use file_utils, only: init_file_utils, finish_file_utils
158
    integer :: arg_count, arg_n, arg_length
159
    logical :: list
160
    character(len=:), allocatable :: argument
4✔
161
    character(len=*), parameter :: nl = new_line('a')
162
    character(len=*), parameter :: usage = &
163
         "gs2 [--version|-v] [--help|-h] [--build-config] [--check-input] [input file]" // nl // nl // &
164
         "GS2: A fast, flexible physicist's toolkit for gyrokinetics" // nl // &
165
         "For more help, see the documentation at https://gyrokinetics.gitlab.io/gs2/" // nl // &
166
         "or create an issue https://bitbucket.org/gyrokinetics/gs2/issues?status=open" // nl // &
167
         nl // &
168
         "  -h, --help           Print this message" // nl // &
169
         "  -v, --version        Print the GS2 version" // nl // &
170
         "  --build-config       Print the current build configuration" // nl // &
171
         "  --check-input FILE   Check input FILE for errors" // nl // &
172
         "  --parse-input FILE   Check we can parse the full input FILE"
173

174
    arg_count = command_argument_count()
4✔
175

176
    do arg_n = 0, arg_count
8✔
177
      call get_command_argument(arg_n, length=arg_length)
8✔
178
      if (allocated(argument)) deallocate(argument)
8✔
179
      allocate(character(len=arg_length)::argument)
8✔
180
      call get_command_argument(arg_n, argument)
8✔
181

182
      if ((argument == "--help") .or. (argument == "-h")) then
8✔
183
        write(*, '(a)') usage
×
184
        stop
×
185
      else if ((argument == "--version") .or. (argument == "-v")) then
8✔
186
        write(*, '("GS2 version ", a)') get_git_version()
2✔
187
        stop
2✔
188
      else if (argument == "--build-config") then
6✔
189
        write(*, '(a)') formatted_build_config()
2✔
190
        stop
2✔
191
      else if (argument == "--check-input") then
4✔
192
        ! Next argument should be the input file
193
        if (arg_n == arg_count) then
×
194
          error stop "Missing input file for '--check-input'" // nl // usage
×
195
        end if
196

197
        call get_command_argument(arg_n + 1, length=arg_length)
×
198
        deallocate(argument)
×
199
        allocate(character(len=arg_length)::argument)
×
200
        call get_command_argument(arg_n + 1, argument)
×
201

202
        call run_ingen(input_file=argument)
×
203
        stop
×
204
      else if (argument == "--parse-input") then
4✔
205
        ! Next argument should be the input file
206
        if (arg_n == arg_count) then
×
207
          error stop "Missing input file for '--parse-input'" // nl // usage
×
208
        end if
209

210
        call get_command_argument(arg_n + 1, length=arg_length)
×
211
        deallocate(argument)
×
212
        allocate(character(len=arg_length)::argument)
×
213
        call get_command_argument(arg_n + 1, argument)
×
214

215
        call init_mp
×
216
        call init_file_utils (list, name="template", input_file=argument)
×
217
        call early_abort_checks
×
218
        if (proc0) write(*, '(a)') "Input file '" // argument // "' parsed successfully."
×
219
        call finish_file_utils
×
220
        call finish_mp
×
221
        stop
×
222
      else if (argument == "--") then
4✔
223
        exit
×
224
      else if (argument(1:1) == "-") then
4✔
225
        write(*, '(a)') "Error: Unrecognised argument '" // argument // "'. Usage is:" // nl // nl // usage
×
226
        stop 2
×
227
      end if
228
    end do
229
  end subroutine parse_command_line
×
230

231
  !> Run whatever checks we can early in the initialisation process
232
  !> which might lead us to abort. Intended to help save compute resource
233
  !> by halting as early as we can.
234
  subroutine early_abort_checks
×
235
    use config_collection, only: gs2_config_type
236
    use gs2_diagnostics, only: check_restart_file_writeable
237
    use gs2_save, only: set_restart_file
238
    use init_g, only: add_restart_dir_to_file, set_restart_dir
239
    use file_utils, only: run_name
240
    type(gs2_config_type), allocatable :: configs !Allocatable to avoid stack size warning
×
241
    logical :: logic_dummy
242
    integer :: ind_slash
243
    ! Let us try populating a config collection from file so that
244
    ! we get an early abort if there is a problem with parsing the
245
    ! provided input file. It is important to note that the values
246
    ! stored here may not be correct due to inaccurate smart defaults
247
    ! at this stage.
248
    allocate(gs2_config_type::configs)
×
249
    call configs%populate_from_file
×
250

251
    ! Check we can write restart files etc. if needed
252
    logic_dummy = .false.
×
253

254
    associate(init_g => configs%init_g_config, diag => configs%diagnostics_config)
255
      init_g%restart_file = trim(run_name)//".nc"
×
256
      call add_restart_dir_to_file(init_g%restart_dir, init_g%restart_file)
×
257
      call set_restart_file(init_g%restart_file)
×
258
      ind_slash = index(init_g%restart_file, "/", .true.)
×
259
      if (ind_slash /= 0) init_g%restart_dir = init_g%restart_file(1:ind_slash)
×
260
      call set_restart_dir(init_g%restart_dir)
×
261
      ! Use logic_dummy for extra_files as we can't change save_distfn now and it won't
262
      ! lead to an abort anyway so suppress warning message.
263
      call check_restart_file_writeable(diag%file_safety_check, diag%save_for_restart, &
264
           logic_dummy, diag%make_restart_dir)
×
265
    end associate
266
  end subroutine early_abort_checks
×
267

268
  !> Starts the global wall clock timer used by check time. This is
269
  !> useful if you have multiple copies of gs2 running but you don't
270
  !> want to start them all at the same time, but you want them all to
271
  !> respect avail_cpu_time
272
  subroutine initialize_wall_clock_timer
×
273
    use job_manage, only: init_checktime
274
    call init_checktime
×
275
  end subroutine initialize_wall_clock_timer
×
276

277
  !> Initialise message passing, open the input file, split the
278
  !> communicator if running in list mode or if nensembles > 1,
279
  !> initialize the timers. After calling this function, gs2 reaches
280
  !> init\%level = basic. If it is desired to provide an external
281
  !> commuicator or set the input file name externally, these should
282
  !> be set before calling this function.
283
  subroutine initialize_gs2(state, header_in, quiet)
×
284
    use file_utils, only: init_file_utils, run_name, run_name_target
285
    use gs2_init, only: init_gs2_init
286
    use job_manage, only: time_message, job_fork
287
    use job_manage, only: init_checktime
288
    use mp, only: init_mp, broadcast, job, nproc, proc0, iproc, get_processor_name
289
    use mp, only: use_nproc, included, mp_comm, mp_comm_null
290
    use redistribute, only: using_measure_scatter
291
    use unit_tests, only: debug_message, set_job_id
292
    use runtime_tests, only: verbosity
293
    use standard_header, only: standard_header_type, get_default_header, set_default_header
294
    use optionals, only: get_option_with_default
295
#ifdef OPENMP
296
    use omp_lib, only: omp_get_num_threads
297
#endif
298
    implicit none
299
    type(gs2_program_state_type), intent(inout) :: state
300
    !> Header for files with build and run information
301
    type(standard_header_type), intent(in), optional :: header_in
302
    !> If true, don't print start-up messages/header
303
    logical, intent(in), optional :: quiet
304
    ! Actual value for optional `header` input
305
    type(standard_header_type) :: local_header
×
306
    ! Internal value for optional `quiet` input
307
    logical :: quiet_value
308
#ifdef OPENMP
309
    integer :: nthread
310
#endif
311

312
    if (state%init%level >= init_level_list%basic) then
×
313
       error stop "ERROR: Called initialize_gs2 twice &
314
        & without calling finalize_gs2? state%init%level on entry too high."
×
315
    end if
316
    !Ensure the job id reported in debug messages is set to something before we call debug message. Note
317
    !that this may get set to a different value later in the Initialisation.
318
    call set_job_id(0)
×
319
    call debug_message(4, 'gs2_main::initialize_gs2 starting initialization')
×
320

321
    call init_mp(state%mp_comm)
×
322
    call debug_message(state%verb, 'gs2_main::initialize_gs2 initialized mp')
×
323

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

326
    if (present(header_in)) call set_default_header(header_in)
×
327
    local_header = get_default_header()
×
328

329
    quiet_value = get_option_with_default(quiet, .false.)
×
330

331
    call initialize_wall_clock_timer
×
332

333
    ! If optimisations say to use a subset of available processors
334
    ! create the communicator for this here.
335
    if (state%init%opt_ov%is_initialised()) then
×
336
       if (state%init%opt_ov%override_nproc .and. state%init%opt_ov%nproc /= nproc) then
×
337
          state%init%opt_ov%old_comm = mp_comm
×
338
          call use_nproc(state%init%opt_ov%nproc)
×
339
       end if
340
    else
341
      state%init%opt_ov%old_comm = mp_comm_null
×
342
    end if
343
    state%included = included
×
344
    state%nproc_actual = nproc
×
345
    if (.not. state%included) return
×
346

347
    if (state%is_external_job) then 
×
348
      call broadcast(state%external_job_id)
×
349
      call set_job_id(state%external_job_id)
×
350
    end if
351

352
    call reset_timers(state%timers)
×
353
  
354
    if (proc0) then
×
355
      ! Report number of processors being used
356
      if (.not. quiet_value) then
×
357
         write(*, '(a)') local_header%to_string(comment_character=" ")
×
358
         if (state%external_job_id >= 0) then
×
359
            write(*, '(a, i0, a)', advance="no") "External job ", state%external_job_id, " "
×
360
         end if
361
         write(*, '(a, i0, a)', advance="no") "Running on ", nproc, " processor"
×
362
         ! Pluralise processor
363
         if (nproc > 1) write(*, '(a)', advance="no") "s"
×
364
#ifdef OPENMP
365
         !$OMP PARALLEL
366
         nthread = omp_get_num_threads()
367
         !$OMP END PARALLEL
368
         write(*, '(A, I0, A)',advance="no") " with ", nthread, " thread"
369
         ! Pluralise thread
370
         if (nthread > 1) write(*, '(a)', advance="no") "s"
371
#endif
372
         ! Make sure we still get a blank line
373
         write(*,*) new_line('a')
×
374
      end if
375

376
      ! Call init_file_utils, ie. initialize the run_name, checking
377
      !  whether we are doing a list of runs.
378
      ! Until the logic of init_file_utils is fixed we set trin_run
379
      ! when an external file name has been provided... this prevents
380
      ! it overriding the name from the command line.
381
      call init_file_utils (state%list, trin_run = state%run_name_external, &
382
           name = state%run_name, n_ensembles = state%nensembles)
×
383
      call debug_message(state%verb, 'gs2_main::initialize_gs2 initialized file_utils')
×
384
    end if
385
    
386
    call broadcast (state%list)
×
387
    call debug_message(state%verb, 'gs2_main::initialize_gs2 broadcasted list')
×
388

389
    if (state%list) then
×
390
       call job_fork
×
391
       call set_job_id(job)
×
392
       call debug_message(state%verb, 'gs2_main::initialize_gs2 called job fork')
×
393
    else if (state%nensembles > 1) then 
×
394
       call job_fork (n_ensembles=state%nensembles)
×
395
       call debug_message(state%verb, &
396
         'gs2_main::initialize_gs2 called job fork (nensembles>1)')
×
397
    end if
398

399
    call time_message(.false.,state%timers%total,' Total')
×
400

401
    ! Pass run name to other procs
402
    if (proc0) run_name_target = trim(run_name)
×
403
    call broadcast (run_name_target)
×
404
    if (.not. proc0) run_name => run_name_target
×
405
    call debug_message(state%verb, 'gs2_main::initialize_gs2 run_name = '//trim(run_name))
×
406

407
    ! Check for early aborts
408
    call early_abort_checks
×
409

410
    !Set using_measure_scatter to indicate we want to use in "gather/scatter" timings
411
    using_measure_scatter = .false.
×
412

413
    ! Initialize the gs2 initialization system
414
    call init_gs2_init()
×
415

416
    state%init%level = init_level_list%basic
×
417

418
    call time_message(.false.,state%timers%total,' Total')
×
419

420
    call debug_message(state%verb, 'gs2_main::initialize_gs2 finished')
×
421

422
  end subroutine initialize_gs2
×
423

424
  !> Initialize all the modules which are used to evolve the
425
  !> equations. After calling this function, gs2 reaches `init%level = full`.
426
  subroutine initialize_equations(state)
×
427
    use job_manage, only: time_message
428
    use run_parameters, only: nstep, do_eigsolve
429
    use unit_tests, only: debug_message
430
    implicit none
431
    type(gs2_program_state_type), intent(inout) :: state
432

433
    if (.not. state%included) return
×
434
    call debug_message(state%verb, 'gs2_main::initialize_equations starting')
×
435
    call time_message(.false.,state%timers%total,' Total')
×
436
    call time_message(.false., state%timers%init,' Initialization')
×
437

438
    ! This triggers initializing of all the grids, all the physics parameters
439
    ! and all the modules which solve the equations and the diagnostics
440
    call state%init%init(init_level_list%full)
×
441

442
    call time_message(.false.,state%timers%init,' Initialization')
×
443

444
    ! Set defaults. These are typically only important
445
    ! for the standalone gs2 program
446
    state%nstep = nstep
×
447
    state%do_eigsolve = do_eigsolve
×
448

449
    call debug_message(state%verb, 'gs2_main::initialize_equations finished')
×
450
    call time_message(.false.,state%timers%total,' Total')
×
451
  end subroutine initialize_equations
452

453
  !> Run the initial value solver. nstep_run must
454
  !> be less than or equal to `state%nstep`, which is
455
  !> set from the input file. The cumulative number of
456
  !> steps that can be run cannot exceed `state%nstep`,
457
  !> Examples:
458
  !>
459
  !>      call evolve_equations(state, state%nstep) ! Basic run
460
  !>
461
  !> Note that these two calls:
462
  !>
463
  !>      call evolve_equations(state, state%nstep/2)
464
  !>      call evolve_equations(state, state%nstep/2)
465
  !>
466
  !> will in general have the identical effect to the single call above.
467
  !> There are circumstances when this is not true,
468
  !> for example, if the first of the two calls to evolve_equations
469
  !> exits without running nstep/2 steps (perhaps because the
470
  !> growth rate has converged).
471
  !>
472
  !> This example will cause an error because the total number
473
  !> of steps exceeds `state%nstep`:
474
  !>
475
  !>      call evolve_equations(state, state%nstep/2)
476
  !>      call evolve_equations(state, state%nstep/2)
477
  !>      call evolve_equations(state, state%nstep/2)
478
  subroutine evolve_equations(state, nstep_run, header)
×
479
    use collisions, only: vnmult
480
    use dist_fn_arrays, only: gnew
481
    use fields, only: advance
482
    use gs2_diagnostics, only: nsave, loop_diagnostics
483
    use gs2_diagnostics_new, only: run_diagnostics, gnostics
484
    use gs2_reinit, only: check_time_step
485
    use gs2_save, only: gs2_save_for_restart
486
    use gs2_time, only: user_time, update_time, write_dt, user_dt
487
    use gs2_time, only: code_dt, code_dt_prev1, code_dt_prev2, code_dt_max
488
    use job_manage, only: time_message, checkstop, checktime
489
    use mp, only: proc0, scope, subprocs, broadcast
490
    use run_parameters, only: reset, has_phi, has_apar, has_bpar, nstep, max_sim_time
491
    use run_parameters, only: avail_cpu_time, margin_cpu_time, use_old_diagnostics
492
    use run_parameters, only: progress_frequency, ncheck_stop, save_timer_statistics
493
    use unit_tests, only: debug_message
494
    use standard_header, only: standard_header_type, get_default_header
495
    use exit_codes, only: EXIT_MAX_SIM_TIME
496
    use file_utils, only: open_output_file, close_output_file
497
    type(gs2_program_state_type), intent(inout) :: state
498
    type(standard_header_type), optional, intent(in) :: header
499
    integer :: istep, progress_unit
500
    integer, intent(in) :: nstep_run
501
    logical :: temp_initval_override_store, should_save_restart, show_progress
502
    integer :: istep_loop_start, istep_loop_max, istep_offset, nsteps_left
503
    real, dimension(2) :: progress_time
504
    real :: time_per_step
505
    character(len = 256) :: progress_message
506
    ! Actual value for optional `header` input
507
    type(standard_header_type) :: local_header
×
508

509
    if (.not. state%included) return
×
510

511
    local_header = get_default_header()
×
512
    if (present(header)) local_header = header
×
513

514
    call debug_message(state%verb, &
515
        'gs2_main::evolve_equations starting')
×
516

517
    temp_initval_override_store = state%init%initval_ov%override
×
518

519
    call time_message(.false.,state%timers%total,' Total')
×
520
    
521
    if (state%nensembles > 1) call scope (subprocs)
×
522

523
    call time_message(.false.,state%timers%main_loop,' Main Loop')
×
524

525
    ! Make sure exit is false before entering timestep loop
526
    state%exit = .false.
×
527

528
    call debug_message(state%verb, 'gs2_main::evolve_equations starting loop')
×
529

530
    progress_time = 0
×
531
    show_progress = proc0 .and. (progress_frequency > 0)
×
532
    if (show_progress .and. proc0) call open_output_file(progress_unit, '.progress')
×
533

534
    ! We run for nstep_run iterations, starting from whatever istep we got
535
    ! to in previous calls to this function. Note that calling
536
    ! finalize_equations resets state%istep_end
537
    istep_loop_start = state%istep_end + 1
×
538
    istep_loop_max = state%istep_end + nstep_run
×
539
    do istep = istep_loop_start, istep_loop_max
×
540
       if (istep > nstep) then
×
541
         if (proc0) write (*,*) 'Reached maximum number of steps allowed &
×
542
              & (set by nstep) without restarting diagnostics.'
×
543
         ! Should we set an exit_reason here?
544
         exit
×
545
       end if
546

547
       call time_message(.false.,state%timers%advance,' Advance time step')
×
548
       call time_message(.false.,progress_time,' Progress time')
×
549
       call debug_message(state%verb+1, 'gs2_main::evolve_equations calling advance')
×
550
       call time_message(.false.,state%timers%timestep,' Timestep')
×
551
       ! Try to take a time step
552
       call advance (istep)
×
553
       call time_message(.false.,state%timers%timestep,' Timestep')
×
554
       call debug_message(state%verb+1,'gs2_main::evolve_equations called advance')
×
555

556
       if(state%dont_change_timestep) reset = .false.
×
557

558
       !If the advance call has triggered a reset then change the timestep.
559
       !Currently this is triggered if immediate_reset is true and the nonlinear
560
       !cfl limit is exceeded.
561
       if (reset) then
×
562
         call prepare_initial_values_overrides(state)
×
563
         call debug_message(state%verb+1, 'gs2_main::evolve_equations resetting timestep')
×
564
         call set_initval_overrides_to_current_vals(state%init%initval_ov)
×
565
         state%init%initval_ov%override = .true.
×
566
         call reset_time_step (state%init, istep, state%exit, state%external_job_id)
×
567

568
         ! Now we've reset set the flag back to .false.
569
         reset = .false.
×
570

571
         ! If we've changed the timestep and have not decided to exit then
572
         ! we need to call advance to actually complete this timestep.
573
         if (.not. state%exit) call advance(istep)
×
574
       end if
575

576
       if (state%exit) exit
×
577

578
       call debug_message(state%verb+1, &
579
            'gs2_main::evolve_equations calling gs2_save_for_restart')
×
580

581
       should_save_restart = .false.
×
582
       if (use_old_diagnostics) then
×
583
          should_save_restart = (nsave > 0 .and. mod(istep, nsave) == 0)
×
584
       else
585
          should_save_restart = (gnostics%nsave > 0 .and. mod(istep, gnostics%nsave) == 0)
×
586
       end if
587
       if (should_save_restart) call gs2_save_for_restart (gnew, user_time, vnmult, &
×
588
            has_phi, has_apar, has_bpar, code_dt, code_dt_prev1, &
589
            code_dt_prev2, code_dt_max, header=local_header)
×
590

591
       call update_time
×
592
       call time_message(.false.,state%timers%diagnostics,' Diagnostics')
×
593

594
       call debug_message(state%verb+1, 'gs2_main::evolve_equations calling diagnostics')
×
595
       if (.not. state%skip_diagnostics) then 
×
596
         if (use_old_diagnostics) then 
×
597
           call loop_diagnostics (istep, state%exit)
×
598
         else 
599
           call run_diagnostics (istep, state%exit)
×
600
         end if
601
       end if
602

603
       if (state%exit) state%converged = .true.
×
604
       if (state%exit) call debug_message(state%verb+1, &
×
605
         'gs2_main::evolve_equations exit true after diagnostics')
×
606

607
       call time_message(.false.,state%timers%diagnostics,' Diagnostics')
×
608
       call time_message(.false.,state%timers%advance,' Advance time step')
×
609

610
       if (.not. state%exit) then
×
611
         call debug_message(state%verb+1, &
612
              'gs2_main::evolve_equations checking time step')
×
613

614
         !Note this should only trigger a reset for timesteps too small
615
         !as timesteps too large are already handled when immediate_reset is
616
         !.true. If immediate_reset is .false. then this is where we handle
617
         !all checking of the time step.
618
         call check_time_step(reset,state%exit)
×
619
         call debug_message(state%verb+1, &
620
              'gs2_main::evolve_equations checked time step')
×
621

622
         !If something has triggered a reset then reset here
623
         if (state%dont_change_timestep) reset = .false.
×
624
         if (reset) then
×
625
            call prepare_initial_values_overrides(state)
×
626
            call set_initval_overrides_to_current_vals(state%init%initval_ov)
×
627
            state%init%initval_ov%override = .true.
×
628
            call reset_time_step (state%init, istep, state%exit, state%external_job_id)
×
629

630
            ! Switch off the reset flag now, otherwise it can still be active
631
            ! on the next iteration.
632
            reset = .false.
×
633
         end if
634

635
         if ((mod(istep, ncheck_stop) == 0) .and. (.not.state%exit)) &
×
636
              call checkstop(state%exit,state%exit_reason)
×
637
         if (state%exit) call debug_message(state%verb+1, &
×
638
              'gs2_main::evolve_equations exit true after checkstop')
×
639
         if (.not.state%exit) call checktime(avail_cpu_time,state%exit,margin_cpu_time)
×
640
         if (state%exit) call debug_message(state%verb+1, &
×
641
              'gs2_main::evolve_equations exit true after checktime')
×
642
       end if
643
       call debug_message(state%verb+1, &
644
        'gs2_main::evolve_equations after reset and checks')
×
645

646
       state%istep_end = istep
×
647

648
       ! Check if the next step would exceed the maximum requested simulation time,
649
       ! and if so flag that we wish to exit. Only check this if we're not already exiting.
650
       if ((.not. state%exit) .and. user_time + user_dt > max_sim_time) then
×
651
          state%exit_reason = EXIT_MAX_SIM_TIME
×
652
          state%exit = .true.
×
653
       end if
654

655
       if (show_progress) then
×
656
          ! Have to split this from previous logic as we shouldn't call mod if
657
          ! progress_frequency is zero and we can't rely on short circuit logic
658
          if (mod(istep - istep_loop_start + 1, progress_frequency) == 0) then
×
659
             call time_message(.false.,progress_time,' Progress time')
×
660
             time_per_step = progress_time(1)/progress_frequency
×
661
             nsteps_left = min((istep_loop_max - istep), int((max_sim_time - user_time) / user_dt))
×
662
             write(progress_message, &
663
                  '("Done step ",I0," of ",I0," : Time/step ",G10.3," s ETA ",G10.3," s")') &
664
                  istep - istep_loop_start + 1, istep_loop_max - istep_loop_start + 1, &
×
665
                  time_per_step, nsteps_left * time_per_step
×
666
             write(6, '(A)') trim(progress_message)
×
667
             rewind(progress_unit)
×
668
             write(progress_unit, '(A)') trim(progress_message)
×
669
             ! Reset progress timer
670
             progress_time = 0
×
671
          end if
672
       end if
673

674
       if (state%exit) then
×
675
           call debug_message(state%verb, 'gs2_main::evolve_equations exiting loop')
×
676
          exit
×
677
       end if
678
    end do
679

680
    if (proc0 .and. show_progress) then
×
681
       write(progress_unit, '("Finished.")')
×
682
       call close_output_file(progress_unit)
×
683
    end if
684

685
    ! Try to ensure that we write the time dependent diagnostics at the end of the simulation
686
    ! even in cases where nstep does not have nwrite as a factor.
687
    if (.not. state%skip_diagnostics) then
×
688
       ! Note when we have completed all our iterations we pass istep - 1 as we assume istep has been 
689
       ! incremented once from the last step actually taken. In cases where we explicitly exit the loop
690
       ! we need to pass istep instead.
691
       istep_offset = 1
×
692
       if (state%exit) istep_offset = 0
×
693
       if (use_old_diagnostics) then
×
694
          call loop_diagnostics (istep - istep_offset, state%exit, force = .true.)
×
695
       else
696
          call run_diagnostics (istep - istep_offset, state%exit, force = .true.)
×
697
       end if
698
    end if
699

700
    call time_message(.false.,state%timers%main_loop,' Main Loop')
×
701
    if (proc0 .and. .not. state%is_external_job) call write_dt
×
702

703
    call time_message(.false.,state%timers%total,' Total')
×
704
    if (state%print_times) call print_times(state, state%timers)
×
705
    if (save_timer_statistics) call write_time_parallel_statistics(state%timers)
×
706

707
    ! We also restore the value of the override switch to what it
708
    ! was when this function was called.
709
    state%init%initval_ov%override = temp_initval_override_store
×
710
    call debug_message(state%verb,'gs2_main::evolve_equations finished')
×
711
  end subroutine evolve_equations
×
712

713
  subroutine reset_time_step(current_init, istep, my_exit, job_id)
×
714
    use gs2_reinit, only: prepare_reset_time_step, do_reset_time_step, time_reinit
715
    use gs2_init, only: init_type, init, init_level_list
716
    use run_parameters, only: reset
717
    use job_manage, only: time_message
718
    implicit none
719
    type(init_type), intent(inout) :: current_init
720
    integer, intent(in) :: istep
721
    logical, intent(in out) :: my_exit
722
    integer, intent (in), optional :: job_id
723
    logical :: reset_in
724
    call time_message(.false., time_reinit, ' Re-initialize')
×
725
    call prepare_reset_time_step(istep, my_exit)
×
726
    if (my_exit) return
×
727

728
    !First disable the reset flag so we can call
729
    !routines needed in reinit
730
    reset_in = reset
×
731
    reset = .false.
×
732

733
    call init(current_init, init_level_list%change_timestep)
×
734
    call do_reset_time_step(istep, my_exit, job_id)
×
735

736
    if (my_exit) then
×
737
       reset = reset_in
×
738
       return
×
739
    end if
740

741
    call init(current_init, init_level_list%full)
×
742
    call time_message(.false., time_reinit, ' Re-initialize')
×
743

744
    reset = reset_in
×
745
  end subroutine reset_time_step
746

747
  !> Employ the eigenvalue solver to seek eigenmodes using SLEPc
748
  subroutine run_eigensolver(state)
×
749
#ifdef WITH_EIG
750
#ifdef FIELDS_EIG
751
    use fields_eigval, only: init_eigval, finish_eigval, BasicSolve
752
#else
753
    use eigval, only: init_eigval, finish_eigval, BasicSolve
754
#endif
755
#endif 
756
    use job_manage, only: time_message
757
    use mp, only: mp_abort
758
    type(gs2_program_state_type), intent(inout) :: state
759
    if (.not. state%included) return
×
760
#ifdef WITH_EIG
761
   call time_message(.false.,state%timers%total,' Total')
762

763
   !Start timer
764
   call time_message(.false.,state%timers%eigval,' Eigensolver')
765

766
   !Initialise slepc and the default/input eigensolver parameters
767
   call init_eigval
768

769
   !Create a solver based on input paramters, use it to solve and
770
   !then destroy it.
771
   call BasicSolve
772

773
   !Tidy up
774
   call finish_eigval
775

776
   !Stop timer
777
   call time_message(.false.,state%timers%eigval,' Eigensolver')
778
#else
779
   call mp_abort("Eigensolver requires GS2 to be built with slepc/petsc", .true.)
×
780
#endif
781
   call time_message(.false.,state%timers%total,' Total')
×
782

783
  end subroutine run_eigensolver
784

785
  !> FIXME : Add documentation  
786
  subroutine finalize_equations(state)
×
787
    use job_manage, only: time_message
788
    use unit_tests, only: debug_message
789
    implicit none
790
    type(gs2_program_state_type), intent(inout) :: state
791

792
    if (.not. state%included) return
×
793

794
    call time_message(.false.,state%timers%finish,' Finished run')
×
795
    call time_message(.false.,state%timers%total,' Total')
×
796

797
    call debug_message(state%verb, 'gs2_main::finalize_equations starting')
×
798
    call state%init%init(init_level_list%basic)
×
799
    state%istep_end = 0
×
800
    call time_message(.false.,state%timers%finish,' Finished run')
×
801
    call time_message(.false.,state%timers%total,' Total')
×
802
  end subroutine finalize_equations
803

804
  !> FIXME : Add documentation  
805
  subroutine finalize_gs2(state, quiet)
×
806
    use file_utils, only: finish_file_utils
807
    use gs2_init, only: finish_gs2_init
808
    use job_manage, only: time_message
809
    use mp, only: finish_mp, proc0, barrier, unsplit_all, included, mp_comm_null
810
    use unit_tests, only: debug_message
811
    use standard_header, only: date_iso8601
812
    use optionals, only: get_option_with_default
813
    use run_parameters, only: save_timer_statistics
814
    implicit none
815
    type(gs2_program_state_type), intent(inout) :: state
816
    !> If true, don't print start-up messages/header
817
    logical, intent(in), optional :: quiet
818

819
    ! Internal value for optional `quiet` input
820
    logical :: quiet_value
821

822
    quiet_value = get_option_with_default(quiet, .false.)
×
823

824
    if (state%included) then
×
825
      if (state%init%level /= init_level_list%basic) then
×
826
        write  (*,*) "ERROR: Called finalize_gs2 at the &
827
          & wrong init_level (perhaps you have called finalize_gs2 &
828
          & without calling initialize_gs2, or without calling &
829
          & finalize_equations"
×
830
        stop 1
×
831
      end if
832

833
      call time_message(.false.,state%timers%total,' Total')
×
834

835
      call finish_gs2_init()
×
836

837
      if (proc0) call finish_file_utils
×
838

839
      call time_message(.false.,state%timers%finish,' Finished run')
×
840
      call time_message(.false.,state%timers%total,' Total')
×
841
      
842
      call debug_message(state%verb, 'gs2_main::finalize_gs2 calling print_times')
×
843

844
      if (state%print_times .and. .not. quiet_value) call print_times(state, state%timers)
×
845
      if (save_timer_statistics) call write_time_parallel_statistics(state%timers)
×
846
    end if
847

848
    if (state%init%opt_ov%is_initialised()) then
×
849
       if (state%init%opt_ov%override_nproc .and. &
×
850
            state%init%opt_ov%old_comm /= mp_comm_null) &
851
            call unsplit_all(state%init%opt_ov%old_comm)
×
852
    end if
853

854
    call barrier
×
855
    state%included = included
×
856

857
    call debug_message(state%verb, 'gs2_main::finalize_gs2 calling finish_mp')
×
858

859
    state%init%level = 0
×
860

861
    if (proc0 .and. (.not. quiet_value) ) write(*, '("Run finished at ",A)') date_iso8601()
×
862
  end subroutine finalize_gs2
×
863

864
  !> FIXME : Add documentation  
865
  subroutine prepare_optimisations_overrides(state)
×
866
    type(gs2_program_state_type), intent(inout) :: state
867
    if (.not. state%included) return
×
868
    call state%init%opt_ov%initialise()
×
869
  end subroutine prepare_optimisations_overrides
870

871
  !> FIXME : Add documentation  
872
  subroutine prepare_initial_values_overrides(state)
×
873
    use fields, only: force_maxwell_reinit
874
    use gs2_init, only: init_level_list
875
    use gs2_reinit, only: in_memory
876
    use gs2_layouts, only: g_lo
877
    use kt_grids, only: naky, ntheta0
878
    use theta_grid, only: ntgrid
879
    use dist_fn_arrays, only: gexp_3
880
    implicit none
881
    type(gs2_program_state_type), intent(inout) :: state
882
    if (.not. state%included) return
×
883
    ! Initialize to the level below so that overrides are triggered
884
    call state%init%init(init_level_list%override_initial_values-1)
×
885
    call state%init%initval_ov%initialise(ntgrid, ntheta0, naky, g_lo%llim_proc, &
886
         g_lo%ulim_alloc, force_maxwell_reinit=force_maxwell_reinit, &
887
         in_memory=in_memory, has_explicit_terms = allocated(gexp_3))
×
888
  end subroutine prepare_initial_values_overrides
889

890
  !> FIXME : Add documentation  
891
  subroutine set_initval_overrides_to_current_vals(initval_ov)
×
892
    use dist_fn_arrays, only: gnew, gexp_1, gexp_2, gexp_3
893
    use gs2_save, only: gs2_save_for_restart
894
    use mp, only: proc0, broadcast, mp_abort
895
    use collisions, only: vnmult
896
    use file_utils, only: error_unit
897
    use run_parameters, only: has_phi, has_apar, has_bpar
898
    use fields, only:  force_maxwell_reinit
899
    use fields_arrays, only: phinew, aparnew, bparnew
900
    use gs2_time, only: user_time, code_dt, code_dt_prev1, code_dt_prev2, code_dt_max
901
    use overrides, only: initial_values_overrides_type
902
    use antenna, only: dump_ant_amp
903
    use array_utils, only: copy
904
    implicit none
905
    type(initial_values_overrides_type), intent(inout) :: initval_ov
906

907
    if (.not.initval_ov%is_initialised()) &
×
908
      call mp_abort("Trying to set initial value overrides &
909
      & before they are initialized... have you called &
910
      & prepare_initial_values_overrides ? ", .true.)
×
911

912
    if(initval_ov%in_memory)then
×
913
      call copy(gnew, initval_ov%g)
×
914
      initval_ov%vnmult = vnmult
×
915
      if (allocated(initval_ov%gexp_1)) call copy(gexp_1, initval_ov%gexp_1)
×
916
      if (allocated(initval_ov%gexp_2)) call copy(gexp_2, initval_ov%gexp_2)
×
917
      if (allocated(initval_ov%gexp_3)) call copy(gexp_3, initval_ov%gexp_3)
×
918

919
      ! Do not use the value from [old_iface_]state%init%initval_ov%force_maxwell_reinit = initval_ov%force_maxwell_reinit as
920
      ! follows:
921
      !     if (.not. initval_ov%force_maxwell_reinit) then
922
      ! as was done previously. This is because this causes problems in gs2_init so we use the value from
923
      ! fields::force_maxwell_reinit directly (see comments in gs2_init for details). To use here the value from
924
      ! initval_ov%force_maxwell_reinit could result in inconsistent values being used in different parts of the code. Therefore, we
925
      ! now use the value from fields::force_maxwell_reinit directly here too.  Now that the reference to
926
      ! initval_ov%force_maxwell_reinit here has also been removed, this component is no longer referenced anywhere in the codebase.
927
      ! Therefore, the force_maxwell_reinit component has been completely removed from the initial_values_overrides_type derived
928
      ! type to avoid confusion in the future.
929
      if (.not. force_maxwell_reinit) then
×
930
         if(has_phi) call copy(phinew, initval_ov%phi)
×
931
         if(has_apar) call copy(aparnew, initval_ov%apar)
×
932
         if(has_bpar) call copy(bparnew, initval_ov%bpar)
×
933
      end if
934
    else ! if(.not.in_memory)then
935
      !Should really do this with in_memory=.true. as well but
936
      !not sure that we really need to as we never read in the dumped data.
937
      if (proc0) call dump_ant_amp
×
938

939
      call gs2_save_for_restart (gnew, user_time, vnmult, &
940
           has_phi, has_apar, has_bpar, code_dt, code_dt_prev1, code_dt_prev2, code_dt_max)
×
941
    endif
942

943
  end subroutine set_initval_overrides_to_current_vals
×
944

945
  !> FIXME : Add documentation  
946
  subroutine finalize_overrides(state)
×
947
    type(gs2_program_state_type), intent(inout) :: state
948
    if (state%init%initval_ov%is_initialised()) call state%init%initval_ov%finish()
×
949
  end subroutine finalize_overrides
×
950

951
  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
952
  !! Private subroutines
953
  !!!!!!!!!!!!!!!!!!!!!!!!!!!!!
954

955
  !> Reset timers data to 0
956
  subroutine reset_timers(timers)
×
957
    use fft_work, only: time_fft
958
    use fields_arrays, only: time_field, time_field_mpi
959
    use fields_arrays, only: time_field_invert, time_field_invert_mpi
960
    use fields_arrays, only: time_dump_response, time_read_response
961
    use gs2_reinit, only: time_reinit
962
    use le_derivatives, only: time_vspace_derivatives, time_vspace_derivatives_mpi
963
    use nonlinear_terms, only: time_add_explicit_terms, time_add_explicit_terms_mpi
964
    use nonlinear_terms, only: time_add_explicit_terms_field
965
    use redistribute, only: reset_redist_times
966
    use mp, only: reset_mp_times
967
    type(gs2_timers_type), intent(inout) :: timers
968
    timers = gs2_timers_type()
×
969
    time_fft = 0. ; time_field = 0. ; time_field_mpi = 0. ; time_field_invert = 0.
×
970
    time_field_invert_mpi = 0. ; time_dump_response = 0. ; time_read_response = 0.
×
971
    time_reinit = 0. ; time_vspace_derivatives = 0. ; time_vspace_derivatives_mpi = 0.
×
972
    time_add_explicit_terms = 0. ; time_add_explicit_terms_mpi = 0.
×
973
    time_add_explicit_terms_field = 0.
×
974
    call reset_redist_times
×
975
    call reset_mp_times
×
976
  end subroutine reset_timers
×
977

978
  !> Gets statistics of passed real value across all processes.
979
  !> Intended for use with our timers.
980
  subroutine get_parallel_statistics(value_in, min_value, max_value,&
×
981
       & mean_value, proc0_value, iproc_min, iproc_max, values_out)
982
    use mp, only: nproc, iproc, sum_allreduce
983
    implicit none
984
    real, intent(in) :: value_in
985
    real, intent(out) :: min_value, max_value, mean_value, proc0_value
986
    integer, intent(out) :: iproc_min, iproc_max
987
    real, dimension(:), allocatable, intent(out), optional :: values_out
988
    real, dimension(:), allocatable :: values
×
989

990
    allocate(values(0:nproc-1))
×
991
    values = 0
×
992
    values(iproc) = value_in
×
993
    call sum_allreduce(values)
×
994
    if(present(values_out)) values_out = values
×
995

996
    min_value = minval(values)
×
997
    max_value = maxval(values)
×
998
    mean_value = sum(values)/nproc
×
999
    proc0_value = values(0)
×
1000

1001
    iproc_min = minloc(values, dim = 1) - 1
×
1002
    iproc_max = maxloc(values, dim = 1) - 1
×
1003
  end subroutine get_parallel_statistics
×
1004

1005
  !> Writes the timing information statistics to optional passed unit
1006
  subroutine write_time_parallel_statistics(timers, report_unit)
×
1007
    use file_utils, only: open_output_file, close_output_file
1008
    use mp, only: proc0, get_mp_times
1009
    use redistribute, only: get_redist_times
1010
    use fft_work, only: time_fft
1011
    use fields_arrays, only: time_field, time_field_mpi
1012
    use fields_arrays, only: time_field_invert, time_field_invert_mpi
1013
    use fields_arrays, only: time_dump_response, time_read_response
1014
    use gs2_reinit, only: time_reinit
1015
    use le_derivatives, only: time_vspace_derivatives, time_vspace_derivatives_mpi
1016
    use nonlinear_terms, only: time_add_explicit_terms, time_add_explicit_terms_mpi
1017
    use nonlinear_terms, only: time_add_explicit_terms_field
1018
    implicit none
1019
    !> Timing information
1020
    type(gs2_timers_type), intent(in) :: timers
1021
    integer, intent(in), optional :: report_unit
1022
    integer :: unit
1023
    real :: mp_total, mp_over, mp_coll, mp_ptp, mp_sync
1024
    real :: redist_total, redist_mpi, redist_copy
1025
    !> Helper type to hold timer data. There might be some
1026
    !> utility in making this avaiable outside of this routine.
1027
    type timer_data
1028
       real :: time
1029
       character(len=:), allocatable :: name
1030
    end type timer_data
1031
    type(timer_data), dimension(:), allocatable :: timer_dat
×
1032
    integer :: i
1033

1034
    ! Make sure unit is set on proc0. Open an output file if required
1035
    if (proc0) then
×
1036
       if (present(report_unit)) then
×
1037
          unit = report_unit
×
1038
       else
1039
          call open_output_file(unit, '.timing_stats')
×
1040
       end if
1041
    end if
1042

1043
    call get_mp_times(mp_total, mp_over, mp_coll, mp_ptp, mp_sync)
×
1044
    call get_redist_times(redist_total, redist_mpi, redist_copy)
×
1045

1046
    allocate( timer_dat, source = [ &
×
1047
         timer_data(timers%init(1), "Initialization"), &
1048
         timer_data(time_field_invert(1), "field matrix invert"), &
1049
         timer_data(time_field_invert_mpi, "field matrix invert mpi"), &
1050
         timer_data(time_dump_response(1), "field matrix dump"), &
1051
         timer_data(time_read_response(1), "field matrix read"), &
1052
         timer_data(timers%advance(1), "Advance steps"), &
1053
#ifdef WITH_EIG
1054
         timer_data(timers%eigval(1), "Eigensolver"), &
1055
#endif
1056
         timer_data(time_field(1), "field solve"), &
1057
         timer_data(time_field_mpi, "field solve mpi"), &
1058
         timer_data(time_vspace_derivatives(1), "collisions"), &
1059
         timer_data(time_vspace_derivatives_mpi, "collisions mpi"), &
1060
         timer_data(time_add_explicit_terms(1), "explicit/nl"), &
1061
         timer_data(time_add_explicit_terms_mpi, "explicit/nl mpi"), &
1062
         timer_data(time_fft(1), "explicit/nl fft"), &
1063
         timer_data(time_add_explicit_terms_field(1), 'explicit/nl fields'), &
1064
         timer_data(timers%diagnostics(1), "diagnostics"), &
1065
         timer_data(time_reinit(1), "Re-initialize"), &
1066
         timer_data(redist_total, "Redistribute"), &
1067
         timer_data(redist_mpi, "redistribute mpi"), &
1068
         timer_data(redist_copy, "redistribute copy"), &
1069
         timer_data(timers%finish(1), "Finishing"), &
1070
         timer_data(mp_total, "MPI"), &
1071
         timer_data(mp_over, "Overheads"), &
1072
         timer_data(mp_coll, "Collectives"), &
1073
         timer_data(mp_ptp, "PTP"), &
1074
         timer_data(mp_sync, "Sync"), &
1075
         timer_data(timers%total(1), "Total") &
1076
         ])
×
1077

1078
    call write_parallel_statistics_header()
×
1079
    do i = 1, size(timer_dat)
×
1080
       call write_parallel_statistics(timer_dat(i)%time, timer_dat(i)%name)
×
1081
    end do
1082

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

1086
  contains
1087
    subroutine write_parallel_statistics_header()
×
1088
      implicit none
1089
      if (proc0) then
×
1090
         write(unit, '(a,T25,4(a9," "),T70,a,T77,a)') "Region", &
×
1091
              "Min (s)", "Max (s)", "Mean (s)", "P0 (s)", &
×
1092
              "Ip min", "Ip max"
×
1093
         write(unit, '(83("-"))')
×
1094
      end if
1095
    end subroutine write_parallel_statistics_header
×
1096

1097
    subroutine write_parallel_statistics(time_value, name)
×
1098
      implicit none
1099
      real, intent(in) :: time_value
1100
      character(len=*), intent(in) :: name
1101
      real :: min_value, max_value, mean_value, proc0_value
1102
      integer :: iproc_min, iproc_max
1103

1104
      call get_parallel_statistics(time_value, &
1105
           min_value, max_value, mean_value, proc0_value, &
1106
           iproc_min, iproc_max)
×
1107

1108
      if (proc0) then
×
1109
         write(unit, '(a,T25,4(0pf9.3," "),T70,I0,T77,I0)') name, &
×
1110
           min_value, max_value, mean_value, proc0_value, &
×
1111
           iproc_min, iproc_max
×
1112
      end if
1113
    end subroutine write_parallel_statistics
×
1114
  end subroutine write_time_parallel_statistics
1115

1116
  !> Print timing information to standard output.
1117
  !>
1118
  !> Prints a full breakdown of timing information if `state%print_full_timers`
1119
  !> is true, otherwise just prints the total time.
1120
  subroutine print_times(state, timers)
×
1121
    use mp, only: proc0, min_reduce, max_reduce, sum_reduce, job
1122
    use mp, only: get_mp_times
1123
    use redistribute, only: get_redist_times
1124
    use fft_work, only: time_fft
1125
    use fields_arrays, only: time_field, time_field_mpi
1126
    use fields_arrays, only: time_field_invert, time_field_invert_mpi
1127
    use fields_arrays, only: time_dump_response, time_read_response
1128
    use gs2_reinit, only: time_reinit
1129
    use le_derivatives, only: time_vspace_derivatives, time_vspace_derivatives_mpi
1130
    use nonlinear_terms, only: time_add_explicit_terms, time_add_explicit_terms_mpi
1131
    use nonlinear_terms, only: time_add_explicit_terms_field
1132
#ifdef GS2_EXPERIMENTAL_ENABLE_MEMORY_USAGE
1133
    use memory_usage, only: print_memory_usage
1134
#endif
1135
    implicit none
1136
    !> Program state information, needed to print
1137
    type(gs2_program_state_type), intent(in) :: state
1138
    !> Timing information
1139
    type(gs2_timers_type), intent(in) :: timers
1140
    real :: mp_total, mp_over, mp_coll, mp_ptp, mp_sync
1141
    real :: redist_total, redist_mpi, redist_copy
1142

1143
    if (.not. proc0) return
×
1144

1145
    if (state%print_full_timers) then
×
1146
      call get_mp_times(mp_total, mp_over, mp_coll, mp_ptp, mp_sync)
×
1147
      call get_redist_times(redist_total, redist_mpi, redist_copy)
×
1148

1149
      !Blank line to force separation from other outputs
1150
      write(*, '("")')
×
1151
      write(*, '(" ", a)') formatted_time("Initialization", timers%init(1))
×
1152
      write(*, '("(", a, ")")') formatted_time("field matrix invert", time_field_invert(1))
×
1153
      write(*, '("(", a, ")")') formatted_time("field matrix invert mpi", time_field_invert_mpi)
×
1154
      write(*, '("(", a, ")")') formatted_time("field matrix dump", time_dump_response(1))
×
1155
      write(*, '("(", a, ")")') formatted_time("field matrix read", time_read_response(1))
×
1156
      write(*, '(" ", a)') formatted_time("Advance steps", timers%advance(1))
×
1157
#ifdef WITH_EIG
1158
      write(*, '(" ", a)') formatted_time("Eigensolver", timers%eigval(1))
1159
#endif
1160
      write(*, '("(", a, ")")') formatted_time("field solve", time_field(1))
×
1161
      write(*, '("(", a, ")")') formatted_time("field solve mpi", time_field_mpi)
×
1162
      write(*, '("(", a, ")")') formatted_time("collisions", time_vspace_derivatives(1))
×
1163
      write(*, '("(", a, ")")') formatted_time("collisions mpi", time_vspace_derivatives_mpi)
×
1164
      write(*, '("(", a, ")")') formatted_time("explicit/nl", time_add_explicit_terms(1))
×
1165
      write(*, '("(", a, ")")') formatted_time("explicit/nl mpi", time_add_explicit_terms_mpi)
×
1166
      write(*, '("(", a, ")")') formatted_time("explicit/nl fft", time_fft(1))
×
1167
      write(*, '("(", a, ")")') formatted_time("explicit/nl fields", time_add_explicit_terms_field(1))
×
1168
      write(*, '("(", a, ")")') formatted_time("diagnostics", timers%diagnostics(1))
×
1169
      write(*, '(" ", a)') formatted_time("Re-initialize", time_reinit(1))
×
1170
      write(*, '(" ", a)') formatted_time("Redistribute", redist_total)
×
1171
      write(*, '("(", a, ")")') formatted_time("redistribute mpi", redist_mpi)
×
1172
      write(*, '("(", a, ")")') formatted_time("redistribute copy", redist_copy)
×
1173
      write(*, '(" ", a)') formatted_time("Finishing", timers%finish(1))
×
1174
      write(*, '(" ", a)') formatted_time("MPI" ,mp_total)
×
1175
      write(*, '("(", a, ")")') formatted_time("Overheads", mp_over)
×
1176
      write(*, '("(", a, ")")') formatted_time("Collectives", mp_coll)
×
1177
      write(*, '("(", a, ")")') formatted_time("PTP", mp_ptp)
×
1178
      write(*, '("(", a, ")")') formatted_time("Sync", mp_sync)
×
1179
      write(*, '(" total from timer is:", 0pf9.2, " min", /)') timers%total(1) / 60.
×
1180
    else
1181
      if (state%external_job_id >= 0) then
×
1182
        write(*, '(a, i0, ", ")', advance="no") " External job ID: ", state%external_job_id
×
1183
      end if
1184
      if (state%list) then
×
1185
        write(*, '(a, i0, ", ")', advance="no") " Job ID: ", job
×
1186
      end if
1187

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

1191
#ifdef GS2_EXPERIMENTAL_ENABLE_MEMORY_USAGE
1192
    call print_memory_usage
1193
#endif
1194
  contains
1195
    !> Print a single formatted timer line
1196
    character(len=46) function formatted_time(name, timer)
×
1197
      !> Name of the timer
1198
      character(len=*), intent(in) :: name
1199
      !> Time in seconds
1200
      real, intent(in) :: timer
1201

1202
      write(formatted_time, "(a, T25, 0pf9.3, ' min', T40, 2pf5.1, ' %')") name, timer / 60., timer/timers%total(1)
×
1203
    end function formatted_time
×
1204
  end subroutine print_times
1205

1206
  !> The main entry point into GS2, runs a single GS2 simulation
1207
  !>
1208
  !> A complete, minimal use of this to run a single, complete
1209
  !> simulation is:
1210
  !>
1211
  !>     program gs2
1212
  !>       use mp, only: init_mp, mp_comm, finish_mp
1213
  !>       use gs2_main, only : run_gs2, gs2_program_state_type
1214
  !>       implicit none
1215
  !>       type(gs2_program_state_type) :: state
1216
  !>       call init_mp
1217
  !>       state%mp_comm = mp_comm
1218
  !>       call run_gs2(state)
1219
  !>       call finish_mp
1220
  !>     end program gs2
1221
  !>
1222
  !> This will initialise all the GS2 internals, evolve the equations
1223
  !> (or run the eigensolver), and then finalise the internals
1224
  !> (writing files to disk, deallocating memory, and so on).
1225
  !>
1226
  !> You can also not finalise the simulation, which can be useful if
1227
  !> you want read or modify the fields, for example. In this case,
1228
  !> you *must* call [[finish_gs2]] when you're done:
1229
  !>
1230
  !>     ! Optionally modify the state and input options
1231
  !>     call run_gs2(state, finalize=.false.)
1232
  !>     ! Do some interesting things
1233
  !>     call finish_gs2(state)
1234
  !>
1235
  !> This pattern is also useful if you want to run many GS2
1236
  !> simulations in the same process.
1237
  subroutine run_gs2(state, finalize, quiet)
×
1238
    use exit_codes, only: EXIT_NSTEP, EXIT_NOT_REQUESTED
1239
    use mp, only: proc0, init_mp
1240
    use optionals, only : get_option_with_default
1241
    implicit none
1242
    !> State of the GS2 simulation. Used to modify the behaviour of
1243
    !> GS2 and/or to programmatically get information about the
1244
    !> simulation on completion.
1245
    type(gs2_program_state_type), intent(inout) :: state
1246
    !> If `.true.` (default), then GS2 is finalised, end-of-simulation
1247
    !> diagnostics are computed, files are closed, arrays are
1248
    !> deallocated, and so on.
1249
    !>
1250
    !> If this is set to `.false.`, (for example, because you want to
1251
    !> read the state of the fields before the arrays are deallocated)
1252
    !> then you MUST pass in `state` and call [[finish_gs2]] with that
1253
    !> state object to ensure GS2 is finalised correctly.
1254
    logical, optional, intent(in) :: finalize
1255
    !> Optional passed through to intialize/finalize gs2 methods to suppress printing
1256
    logical, optional, intent(in) :: quiet
1257
    logical :: local_finalize
1258

1259
    local_finalize = get_option_with_default(finalize, .true.)
×
1260

1261
    call initialize_gs2(state, quiet = quiet)
×
1262
    call initialize_equations(state)
×
1263

1264
    ! Store a copy of the final configuration objects in our init structure
1265
    call state%init%config%get_configs()
×
1266
    call state%write_used_inputs_file()
×
1267

1268
    state%print_times = .false.
×
1269
    if (state%do_eigsolve) then
×
1270
      call run_eigensolver(state)
×
1271
    else
1272
      call evolve_equations(state, state%nstep)
×
1273
      if (state%exit_reason%is_identical(EXIT_NOT_REQUESTED)) state%exit_reason = EXIT_NSTEP
×
1274
    end if
1275
    if(proc0) call state%exit_reason%write_exit_file()
×
1276

1277
    if (local_finalize) then
×
1278
      state%print_times = .true.
×
1279
      call finish_gs2(state, quiet = quiet)
×
1280
    end if
1281
  end subroutine run_gs2
×
1282

1283
  !> Finish and cleanup a complete simulation
1284
  subroutine finish_gs2(state, quiet)
×
1285
    !> An existing, initialisation simulation state
1286
    type(gs2_program_state_type), intent(inout) :: state
1287
    logical, intent(in), optional :: quiet
1288
    call finalize_equations(state)
×
1289
    call finalize_gs2(state, quiet)
×
1290
  end subroutine finish_gs2
×
1291

1292
  !> Write an input file containing the current state of all input
1293
  !> parameters
1294
  subroutine write_used_inputs_file_bound(self)
×
1295
    class(gs2_program_state_type), intent(in) :: self
1296
    call write_used_inputs_file(self%init%config)
×
1297
  end subroutine write_used_inputs_file_bound
×
1298

1299
  !> Write an input file containing the current state of all input
1300
  !> parameters
1301
  subroutine write_used_inputs_file(config, header)
×
1302
    use mp, only: proc0
1303
    use file_utils, only: open_output_file, close_output_file, run_name
1304
    use config_collection, only: gs2_config_type
1305
    use standard_header, only: standard_header_type, get_default_header
1306
    type(gs2_config_type), intent(in), optional :: config
1307
    !> Header for files with build and run information
1308
    type(standard_header_type), intent(in), optional :: header
1309
    ! Actual value for optional `header` input
1310
    type(standard_header_type) :: local_header
×
1311
    ! Actual value for optional `config` input
1312
    type(gs2_config_type), allocatable :: local_config
×
1313
    ! File unit to write to
1314
    integer :: used_inputs_unit
1315

1316
    ! Only write this file on rank 0
1317
    if (.not. proc0) return
×
1318

1319
    local_header = get_default_header()
×
1320
    if (present(header)) local_header = header
×
1321

1322
    if (present(config)) then
×
1323
       local_config = config
×
1324
    else
1325
       allocate(local_config)
×
1326
       call local_config%get_configs()
×
1327
    end if
1328

1329
    call open_output_file(used_inputs_unit, ".used_inputs.in")
×
1330
    write(unit=used_inputs_unit, fmt='(a)') &
1331
         local_header%to_string( &
1332
         comment_character="! ", &
1333
         file_description="Input parameters as used by " // trim(run_name) &
1334
         )
×
1335

1336
    call local_config%write_to_unit(used_inputs_unit)
×
1337
    call close_output_file(used_inputs_unit)
×
1338
  end subroutine write_used_inputs_file
×
1339
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