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

gyrokinetics / gs2 / 1998640042

22 Aug 2025 01:50PM UTC coverage: 10.577% (-0.1%) from 10.718%
1998640042

push

gitlab-ci

David Dickinson
Merged in feature/dont_reset_configs_when_finishing_modules (pull request #1160)

4700 of 44434 relevant lines covered (10.58%)

125622.86 hits per line

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

0.0
/src/split_nonlinear_terms.fpp
1
!> A module to deal with advancing the nonlinear term
2
!> separately from the linear terms.
3
module split_nonlinear_terms
4
  use abstract_config, only: abstract_config_type, CONFIG_MAX_NAME_LEN
5
  use rk_schemes, only: rk_scheme_type
6
  implicit none
7
  private
8

9
  public :: init_split_nonlinear_terms, finish_split_nonlinear_terms, set_split_nonlinear_terms_config
10
  public :: advance_nonlinear_term, advance_nonadiabatic_dfn, strang_split
11
  public :: split_nonlinear_terms_config_type, get_split_nonlinear_terms_config
12

13
  logical :: initialized = .false.
14

15
  !> Statistics for the number of steps taken in the integrators
16
  integer :: nfailed_steps = 0, nrhs_calls = 0, nsuccessful_steps = 0
17

18
  !> Interface to describe the call signatures for routines to calculate the
19
  !> field from gnew (invert_field_func) and to calculate the source term used
20
  !> in the advance_nonlinear_term methods. Used to allow us to pass in these
21
  !> methods, giving us a way to test the integrators on different problems.
22
  interface
23
     subroutine invert_field_func (g_in, phi, apar, bpar, gf_lo, local_only)
24
       implicit none
25
       complex, dimension (:,:,:), intent(in) :: g_in
26
       complex, dimension (:,:,:), intent (out) :: phi, apar, bpar
27
       logical, intent(in), optional :: gf_lo, local_only
28
     end subroutine invert_field_func
29

30
     subroutine source_term_func(g_in, g1, phi, apar, bpar, max_vel_local, &
31
          need_to_adjust, calculate_cfl_limit)
32
       implicit none
33
       complex, dimension (:,:,:), intent (in) :: g_in
34
       complex, dimension (:,:,:), intent (out) :: g1
35
       complex, dimension (:,:,:), intent (in) :: phi, apar, bpar
36
       real, intent(out) :: max_vel_local
37
       logical, intent(in) :: need_to_adjust
38
       logical, intent(in), optional :: calculate_cfl_limit
39
     end subroutine source_term_func
40
  end interface
41

42
  ! Related to inputs
43
  integer :: split_method_switch
44
  integer, parameter :: split_method_ab3 = 1, split_method_backwards_euler = 2, &
45
       split_method_rk = 3, split_method_picard = 4
46
  type(rk_scheme_type) :: the_rk_scheme
47
  logical :: show_statistics, advance_nonadiabatic_dfn, strang_split
48
  real :: convergence_tolerance, time_step_safety_factor
49
  real :: relative_tolerance, absolute_tolerance
50

51
  !> Used to represent the input configuration of split_nonlinear_terms
52
  type, extends(abstract_config_type) :: split_nonlinear_terms_config_type
53
     ! namelist : split_nonlinear_terms_knobs
54
     ! indexed : false
55
     !> The absolute tolerance used in error controlled schemes. Attempt to adjust
56
     !> time step to keep error below this tolerance.
57
     real :: absolute_tolerance = 1.0e-3
58
     !> If true then nonlinear integrator advances the nonadiabatic dfn, h,
59
     !> rather than the modified distribution function, g.
60
     logical :: advance_nonadiabatic_dfn = .false.
61
     !> The tolerance used in convergence checks. Currently only used
62
     !> for halting the fixed-point iteration in the beuler method
63
     real :: convergence_tolerance = 1.0e-1
64
     !> The relative tolerance used in error controlled schemes. Attempt to adjust
65
     !> time step to keep error below this tolerance.
66
     real :: relative_tolerance = 1.0e-2
67
     !> Choose which specific RK scheme to use in the RK method.
68
     !> Generally if the tolerances are small a higher order scheme
69
     !> will be more effective than low order. At loose tolerances
70
     !> low order schemes are generally more efficient
71
     !> Valid options include:
72
     !>
73
     !>  - 'cashkarp' -- Cash-Karp scheme of order 4(5)
74
     !>  - 'default' -- Same as heun
75
     !>  - 'heun' -- Heun scheme of order 1(2)
76
     !>
77
     !> See [[rk_schemes]] for other options.
78
     character(len = 20) :: rk_method = 'default'
79
     !> If true then reports the number of right hand side (NL term) calculations,
80
     !> the number of failed internal steps and the number of successful steps at the
81
     !> end of each linear size step.
82
     logical :: show_statistics = .false.
83
     !> What algorithm do we use to advance the nonlinear term if
84
     !> split_nonlinear is true.
85
     !> Valid options include:
86
     !>
87
     !>  - 'AB3' -- Adams-Bashforth (up to) 3rd order. CLF controlled time step.
88
     !>  - 'beuler' -- Backwards Euler. Relative and absolute error controlled time step.
89
     !>            Newton iteration controlled by convergence_tolerance.
90
     !>  - 'default' -- The same as 'RK'.
91
     !>  - 'RK' -- RK scheme with embedded error estimate. Exact scheme can be switched out
92
     !>            using rk_method switch. Relative and absolute error controlled time step.
93
     !>  - 'picard' -- Use simple Picard iteration. Not generally recommended but available
94
     !>            for experimentation.
95
     !>
96
     character(len = 20) :: split_method = 'default'
97
     !> If true then indicates that we want to use a strang split approach where
98
     !> we advance the NL operator by a half step, linear by a full step and then
99
     !> NL by another half step. This _should_ be second order accurate whilst the
100
     !> regular split is only first order accurate.
101
     logical :: strang_split = .false.
102
     !> Multiplies the new time step calculated from either the error or
103
     !> cfl limits. Smaller values are more conservative but may help avoid
104
     !> repeated violation of the error/cfl limits and hence reduce the
105
     !> number of failed steps.
106
     real :: time_step_safety_factor = 0.9
107
#include "split_nonlinear_terms_overrides_and_bound_auto_gen.inc"
108
  end type split_nonlinear_terms_config_type
109

110
  type(split_nonlinear_terms_config_type) :: split_nonlinear_terms_config
111

112
contains
113

114
  !> Initialises the split_nonlinear_terms module. Primarily just reading input
115
  subroutine init_split_nonlinear_terms(split_nonlinear_terms_config_in)
×
116
    implicit none
117
    type(split_nonlinear_terms_config_type), intent(in), optional :: split_nonlinear_terms_config_in
118

119
    if (initialized) return
×
120
    initialized = .true.
×
121

122
    call read_parameters(split_nonlinear_terms_config_in)
×
123

124
  end subroutine init_split_nonlinear_terms
125

126
  !> Read the split_nonlinear_terms namelist
127
  subroutine read_parameters(split_nonlinear_terms_config_in)
×
128
    use file_utils, only: error_unit
129
    use text_options, only: text_option, get_option_value
130
    use rk_schemes, only: get_rk_schemes_as_text_options, get_rk_scheme_by_id
131
    implicit none
132
    type(split_nonlinear_terms_config_type), intent(in), optional :: split_nonlinear_terms_config_in
133
    type(text_option), dimension (*), parameter :: split_method_opts = &
134
         [ &
135
         text_option('default', split_method_rk), &
136
         text_option('AB3', split_method_ab3), &
137
         text_option('RK', split_method_rk), &
138
         text_option('beuler', split_method_backwards_euler),  &
139
         text_option('picard', split_method_picard)  &
140
         ]
141
    character(len = 20) :: rk_method, split_method
142
    integer :: ierr, rk_method_switch
143

144
    if (present(split_nonlinear_terms_config_in)) split_nonlinear_terms_config = split_nonlinear_terms_config_in
×
145

146
    call split_nonlinear_terms_config%init(name = 'split_nonlinear_terms_knobs', requires_index = .false.)
×
147

148
    ! Copy out internal values into module level parameters
149
    associate(self => split_nonlinear_terms_config)
150
#include "split_nonlinear_terms_copy_out_auto_gen.inc"
151
    end associate
152

153
    ierr = error_unit()
×
154

155
    call get_option_value &
156
         (split_method, split_method_opts, split_method_switch, &
157
         ierr, "split_method in split_nonlinear_terms_knobs",.true.)
×
158

159
    call get_option_value &
160
         (rk_method, get_rk_schemes_as_text_options(), rk_method_switch, &
161
         ierr, "rk_method in split_nonlinear_terms_knobs",.true.)
×
162
    the_rk_scheme = get_rk_scheme_by_id(rk_method_switch)
×
163
  end subroutine read_parameters
×
164

165
  !> Reset the module, freeing memory etc.
166
  subroutine finish_split_nonlinear_terms
×
167
    implicit none
168
    initialized = .false.
×
169
  end subroutine finish_split_nonlinear_terms
×
170

171
  !> Reset the step statistics
172
  subroutine reset_step_statistics
×
173
    nfailed_steps = 0 ; nrhs_calls = 0 ; nsuccessful_steps = 0
×
174
  end subroutine reset_step_statistics
×
175

176
  subroutine report_step_statistics(istep, unit_in)
×
177
    use iso_fortran_env, only: output_unit
178
    use optionals, only: get_option_with_default
179
    implicit none
180
    integer, intent(in) :: istep
181
    integer, intent(in), optional :: unit_in
182
    integer :: unit
183
    unit = get_option_with_default(unit_in, output_unit)
×
184
    write(unit,'("Iteration : ",I0," Number of internal steps : ",I0," Number of failed steps : ",I0," Number of RHS calls : ",I0)') &
185
         istep, nsuccessful_steps, nfailed_steps, nrhs_calls
×
186
  end subroutine report_step_statistics
×
187

188
  !> Advances dg/dt = NL(g,chi) from g_state, chi from t -> t+dt by calling
189
  !> specific requested method.
190
  !> On output g_state contains new g at next step, chi is left unchanged
191
  subroutine advance_nonlinear_term(g_state, istep, phi, apar, bpar, &
×
192
       dt, fields_func, source_func)
193
    use dist_fn_arrays, only: g_adjust, to_g_gs2, from_g_gs2
194
    use mp, only: mp_abort, get_mp_times, proc0
195
    use job_manage, only: time_message
196
    use nonlinear_terms, only: time_add_explicit_terms, time_add_explicit_terms_mpi
197
    use run_parameters, only: has_phi, has_apar, has_bpar
198
    use array_utils, only: copy
199
    implicit none
200
    integer, intent(in) :: istep
201
    complex, dimension (:,:,:), intent(in out) :: g_state
202
    complex, dimension (:,:,:), intent(in) :: phi, apar, bpar
203
    real, intent(in) :: dt
204
    complex, dimension (:,:,:), allocatable :: phinew, aparnew, bparnew
×
205
    real :: mp_total_after, mp_total
206
    procedure(invert_field_func) :: fields_func
207
    procedure(source_term_func) :: source_func
208

209
    call time_message(.false., time_add_explicit_terms, 'Explicit terms')
×
210
    call get_mp_times(total_time = mp_total)
×
211
    call reset_step_statistics
×
212

213
    ! Copy current fields to local copies
214
    allocate(phinew, mold = phi)
×
215
    allocate(aparnew, mold = apar)
×
216
    allocate(bparnew, mold = bpar)
×
217
    if (has_phi) call copy(phi, phinew)
×
218
    if (has_apar) call copy(apar, aparnew)
×
219
    if (has_bpar) call copy(bpar, bparnew)
×
220

221
    ! If we want to advance h rather than g then adjust
222
    ! here to get h. Note we rely on the call site also
223
    ! providing the correct fields_func to calculate fields
224
    ! from h rather than g. A different option would be
225
    ! to require the call site to always pass a way to calculate
226
    ! from g and a way from h and we then decide here which to use.
227
    if (advance_nonadiabatic_dfn) then
×
228
       call g_adjust(g_state, phinew, bparnew, direction = from_g_gs2)
×
229
    end if
230

231
    ! Call requested method for advancing nonlinear term
232
    select case(split_method_switch)
×
233
    case(split_method_ab3)
234
       call advance_nonlinear_term_ab3(g_state, phinew, aparnew, bparnew, dt, &
×
235
            fields_func, source_func)
×
236
    case(split_method_backwards_euler)
237
       call advance_nonlinear_term_beuler(g_state, phinew, aparnew, bparnew, dt, &
×
238
            fields_func, source_func)
×
239
    case(split_method_rk)
240
       call advance_nonlinear_term_rk(g_state, phinew, aparnew, bparnew, dt, &
×
241
            fields_func, source_func)
×
242
    case(split_method_picard)
243
       call advance_nonlinear_term_picard(g_state, phinew, aparnew, bparnew, dt, &
×
244
            fields_func, source_func)
×
245
    case default
246
       call mp_abort("Invalid split_method_switch", .true.)
×
247
    end select
248

249
    if (proc0 .and. show_statistics) call report_step_statistics(istep)
×
250

251
    ! If we advanced h then we need to reconstruct g from this
252
    if (advance_nonadiabatic_dfn) then
×
253
       call g_adjust(g_state, phi, bpar, direction = to_g_gs2)
×
254
    end if
255

256
    ! Now that we've advanced the explicit terms by dt and set the
257
    ! current g_state to this new result. Note that we do not update the
258
    ! fields, instead resetting them to their original values. The
259
    ! update to the fields is calculated as a part of the implicit
260
    ! field solve and including the NL contribution here leads to
261
    ! "double counting".
262

263
    call time_message(.false., time_add_explicit_terms, 'Explicit terms')
×
264
    call get_mp_times(total_time = mp_total_after)
×
265
    time_add_explicit_terms_mpi = time_add_explicit_terms_mpi + (mp_total_after - mp_total)
×
266
  end subroutine advance_nonlinear_term
×
267

268
  !> Advances dg/dt = NL(g,chi) from current g_state, chi from t -> t+dt by using
269
  !> AB scheme of orders up to 3rd.
270
  subroutine advance_nonlinear_term_ab3(g_state, phinew, aparnew, bparnew, dt, &
×
271
       fields_func, source_func)
272
    use theta_grid, only: ntgrid
273
    use gs2_time, only: get_adams_bashforth_coefficients
274
    use gs2_time, only: code_dt_min, dt_not_set, code_dt_prev1, code_dt_prev2
275
    use mp, only: mp_abort, max_allreduce
276
    use gs2_layouts, only: g_lo
277
    use array_utils, only: copy, zero_array
278
    implicit none
279
    complex, dimension (-ntgrid:, :, g_lo%llim_proc:), intent(in out) :: g_state
280
    complex, dimension (-ntgrid:,:,:), intent (in out) :: phinew, aparnew, bparnew
281
    !> Arrays to hold the nonlinear source history similar to gexp_1/2/3
282
    complex, dimension(:, :, :), allocatable :: gnl_1, gnl_2, gnl_3
×
283
    real, intent(in) :: dt
284
    real :: internal_time, time_step, max_vel, half_time
285
    real, dimension(:), allocatable :: ab_coeffs
×
286
    integer :: counter, iglo
287
    procedure(invert_field_func) :: fields_func
288
    procedure(source_term_func) :: source_func
289

290
    ! Initialise internal variables
291
    internal_time = 0.0
×
292
    counter = 1
×
293

294
    allocate(gnl_1(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc)) ; call zero_array(gnl_1)
×
295
    allocate(gnl_2(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc)) ; call zero_array(gnl_2)
×
296
    allocate(gnl_3(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc)) ; call zero_array(gnl_3)
×
297

298
    ! Reset time step sizes to reflect fact we're restarting the explicit scheme
299
    code_dt_prev1 = dt_not_set
×
300
    code_dt_prev2 = dt_not_set
×
301

302
    ! Keep taking explicit steps until we have advanced by dt
303
    do while (internal_time < dt)
×
304
       ! Get the current nonlinear source term and cfl limit
305
       call source_func(g_state, gnl_1, phinew, aparnew, bparnew, &
×
306
            max_vel, need_to_adjust = .not. advance_nonadiabatic_dfn, &
307
            calculate_cfl_limit = .true.)
×
308
       nrhs_calls = nrhs_calls + 1
×
309

310
       ! Get the maximum velocity across all processors
311
       ! and convert to time_step estimate.
312
       call max_allreduce(max_vel)
×
313
       time_step = 1.0 / max_vel
×
314
       time_step = time_step * time_step_safety_factor
×
315

316
       ! If the cfl time step is too small then abort
317
       if (time_step < code_dt_min) call mp_abort("Time step has become too small in advance_nonlinear_term.", .true.)
×
318

319
       ! Now make sure we're don't overshoot the target time by limiting time step.
320
       time_step = min(time_step, dt - internal_time)
×
321

322
       ! Get the Adams-Bashforth coefficients for the current collection of time step sizes
323
       ab_coeffs = get_adams_bashforth_coefficients(target_dt = time_step)
×
324

325
       half_time = 0.5 * time_step
×
326

327
       ! Advance solution by time_step
328
       select case(counter)
×
329
       case(1)
330
          !$OMP PARALLEL DO DEFAULT(none) &
331
          !$OMP PRIVATE(iglo) &
332
          !$OMP SHARED(g_lo, g_state, half_time, ab_coeffs, gnl_1) &
333
          !$OMP SCHEDULE(static)
334
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
335
             g_state(:, :, iglo) = g_state(:, :, iglo) + half_time *( &
×
336
                  ab_coeffs(1) * gnl_1(:, :, iglo)       &
×
337
                  )
×
338
          end do
339
          !$OMP END PARALLEL DO
340
       case(2)
341
          !$OMP PARALLEL DO DEFAULT(none) &
342
          !$OMP PRIVATE(iglo) &
343
          !$OMP SHARED(g_lo, g_state, half_time, ab_coeffs, gnl_1, gnl_2) &
344
          !$OMP SCHEDULE(static)
345
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
346
             g_state(:, :, iglo) = g_state(:, :, iglo) + half_time *( &
×
347
                  ab_coeffs(1) * gnl_1(:, :, iglo) +     &
×
348
                  ab_coeffs(2) * gnl_2(:, :, iglo)       &
×
349
                  )
×
350
          end do
351
          !$OMP END PARALLEL DO
352
       case default
353
          !$OMP PARALLEL DO DEFAULT(none) &
354
          !$OMP PRIVATE(iglo) &
355
          !$OMP SHARED(g_lo, g_state, half_time, ab_coeffs, gnl_1, gnl_2, gnl_3) &
356
          !$OMP SCHEDULE(static)
357
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
358
             g_state(:, :, iglo) = g_state(:, :, iglo) + half_time *( &
×
359
                  ab_coeffs(1) * gnl_1(:, :, iglo) +     &
×
360
                  ab_coeffs(2) * gnl_2(:, :, iglo) +     &
×
361
                  ab_coeffs(3) * gnl_3(:, :, iglo)       &
×
362
                  )
×
363
          end do
364
          !$OMP END PARALLEL DO
365
       end select
366

367
       ! Calculate the fields consistent with the new g
368
       call calculate_fields(fields_func, g_state, phinew, aparnew, bparnew)
×
369

370
       ! Increment internal state
371
       internal_time = internal_time + time_step
×
372
       counter = counter + 1
×
373
       nsuccessful_steps = nsuccessful_steps + 1
×
374

375
       ! Shift time history along one point
376
       code_dt_prev2 = code_dt_prev1
×
377
       code_dt_prev1 = time_step
×
378
       call copy(gnl_2, gnl_3)
×
379
       call copy(gnl_1, gnl_2)
×
380
    end do
381

382
  end subroutine advance_nonlinear_term_ab3
×
383

384
  !> Advances dg/dt = NL(g,chi) from current g_state, chi from t -> t+dt by using
385
  !> backwards Euler with fixed-point iteration.
386
  subroutine advance_nonlinear_term_beuler(g_state, phinew, aparnew, bparnew, dt, &
×
387
       fields_func, source_func)
388
    use theta_grid, only: ntgrid
389
    use gs2_time, only: code_dt_min
390
    use mp, only: mp_abort, max_allreduce, proc0
391
    use run_parameters, only: immediate_reset
392
    use gs2_layouts, only: g_lo
393
    use array_utils, only: copy, gs2_max_abs, zero_array
394
    use warning_helpers, only: exactly_equal
395
    implicit none
396
    complex, dimension (-ntgrid:, :, g_lo%llim_proc:), intent(in out) :: g_state
397
    complex, dimension (-ntgrid:,:,:), intent (in out) :: phinew, aparnew, bparnew
398
    complex, dimension(:, :, :), allocatable :: g_cur, g_local, gnl_1, gnl_2
×
399
    real, intent(in) :: dt
400
    real :: internal_time, time_step, max_vel
401
    integer :: counter, iglo
402
    integer, parameter :: iteration_limit = 20
403
    real, parameter :: time_adjust_factor = 2
404
    logical, parameter :: debug = .false.
405
    real :: inverse_error, error, actual_dt, half_time, cfl_time_step
406
    real, dimension(3) :: errors
407
    real, save :: time_step_last = -1
408
    procedure(invert_field_func) :: fields_func
409
    procedure(source_term_func) :: source_func
410
    logical :: reject_step, cfl_limited
411
    complex, dimension(:, :, :), allocatable :: error_array
×
412

413
    ! Initialise internal variables
414
    if (time_step_last < 0) time_step_last = dt
×
415
    internal_time = 0.0
×
416
    time_step = time_step_last
×
417

418
    allocate(error_array(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
419
    allocate(g_cur(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
420
    allocate(g_local(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
421
    allocate(gnl_1(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
422
    allocate(gnl_2(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
423
    call copy(g_state, g_cur)
×
424
    call zero_array(error_array) ; call zero_array(g_local)
×
425
    call zero_array(gnl_1); call zero_array(gnl_2)
×
426

427
    ! Keep on advancing until we have advanced by dt
428
    do while (internal_time < dt)
×
429
       ! Reset counter and error
430
       counter = 0
×
431
       error = 1.0
×
432
       errors = 0.0
×
433

434
       ! Limit the actual time step that we take to avoid overshooting (i.e.
435
       ! to keep internal_time <= dt).
436
       actual_dt = min(time_step, dt - internal_time)
×
437
       half_time = 0.5 * actual_dt
×
438

439
       ! Calculate the current NL source term, for use in error
440
       ! estimates later.
441
       call source_func(g_state, gnl_2, phinew, aparnew, bparnew, &
×
442
            max_vel, need_to_adjust = .not. advance_nonadiabatic_dfn, &
443
            calculate_cfl_limit = .false.)
×
444
       nrhs_calls = nrhs_calls + 1
×
445

446
       ! Try to take a step of size actual_dt using fixed point iteration with
447
       ! backwards Euler.
448
       do while (error > convergence_tolerance .and. counter < iteration_limit)
×
449

450
          ! Get the current nonlinear source term and cfl limit -- note we don't use the
451
          ! cfl limit here
452
          call source_func(g_state, gnl_1, phinew, aparnew, bparnew, &
×
453
               max_vel, need_to_adjust = .not. advance_nonadiabatic_dfn, &
454
               calculate_cfl_limit = .false.)
×
455
          nrhs_calls = nrhs_calls + 1
×
456

457
          ! Calculate the estimate of the new g
458
          !$OMP PARALLEL DO DEFAULT(none) &
459
          !$OMP PRIVATE(iglo) &
460
          !$OMP SHARED(g_lo, g_local, g_cur, half_time, gnl_1) &
461
          !$OMP SCHEDULE(static)
462
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
463
             g_local(:, :, iglo) = g_cur(:, :, iglo) + half_time * gnl_1(:, :, iglo)
×
464
          end do
465
          !$OMP END PARALLEL DO
466

467
          ! Calculate the maximum absolute error and the maximum value of the previous solution
468

469
          ! Note we _could_ merge the following loop witth the gs2_max_abs kernel
470
          ! so that we only loop over the error_array once (and actually don't
471
          ! need to explicitly store the full array)
472
          !$OMP PARALLEL DO DEFAULT(none) &
473
          !$OMP PRIVATE(iglo) &
474
          !$OMP SHARED(g_lo, error_array, g_state, g_local) &
475
          !$OMP SCHEDULE(static)
476
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
477
             error_array(:, :, iglo) = g_state(:, :, iglo) - g_local(:, :, iglo)
×
478
          end do
479
          !$OMP END PARALLEL DO
480
          errors(1) = gs2_max_abs(error_array)
×
481
          errors(2) = gs2_max_abs(g_local)
×
482
          call max_allreduce(errors)
×
483

484
          ! Calculate an approximate relative error
485
          error = errors(1) / errors(2)
×
486

487
          ! Update internals -- increment counter and update the 'previous' solution with the new one.
488
          counter = counter + 1
×
489
          call copy(g_local, g_state)
×
490

491
          ! Update the fields consistently with the current solution
492
          call fields_func(g_state, phinew, aparnew, bparnew, local_only = .true.)
×
493
       end do
494

495
       ! Now we need to decide if the last step was successful or not. There are two exit conditions, either the
496
       ! error was small enough (good step) or the iteration limit was exceeded (bad step).
497
       if (counter >= iteration_limit) then
×
498
          ! If it was a bad step then throw away these changes and reduce the time step
499
          if (proc0 .and. debug) print*,'Too many iterations, reducing step from',time_step,'to',time_step/time_adjust_factor,'with internal_time = ',internal_time
500

501
          ! Reduce the time step
502
          time_step = time_step / time_adjust_factor
×
503
          ! If the time step is now too small then abort
504
          if (time_step < code_dt_min) call mp_abort("Time step has become too small in advance_nonlinear_term.", .true.)
×
505

506
          ! If we've taken too many iterations then we want to drop the time step and try
507
          ! again. To try again we must ensure that gnew has been reset to g, and the fields
508
          ! are consistent with this.
509
          reject_step = .true.
×
510
       else
511
          ! If we have met the convergence condition then we should estimate the error
512
          ! on the solution and see if we need to reject the step or how we should adjust
513
          ! the step size.
514
          ! To estimate the error we compare the backward Euler update with an approximate
515
          ! Crank-Nicolson update.
516
          ! g_new_beuler = g + 0.5 * actual_dt * gnl_1(g_new_beuler)
517
          ! g_new_cn = g + 0.5 * actual_dt * (gnl_1(g_new_beuler) + gnl_1(g))/2
518
          ! abs_error  = |g_new_beuler - g_new_cn|
519
          !      = 0.5 * actual_dt * 0.5 * (gnl_1(g_new_beuler) - gnl_1(g)
520
          ! Where gnl_1(h) is the source func evaluated with gnew=h.
521

522
          ! Here we calculate gnl_1(g_new_beuler) exactly. We could probably
523
          ! rely on using the existing value of gnl_1(g_local) as, whilst this is
524
          ! strictly from the previous iteration of the fixed-point scheme, we know
525
          ! it is within the convergence tolerance of the true value.
526
          call source_func(g_state, gnl_1, phinew, aparnew, bparnew, &
×
527
               max_vel, need_to_adjust = .not. advance_nonadiabatic_dfn, &
528
               calculate_cfl_limit = .true.)
×
529
          nrhs_calls = nrhs_calls + 1
×
530

531
          ! Note we _could_ merge the following loop witth the gs2_max_abs kernel
532
          ! so that we only loop over the error_array once (and actually don't
533
          ! need to explicitly store the full array)
534
          !$OMP PARALLEL DO DEFAULT(none) &
535
          !$OMP PRIVATE(iglo) &
536
          !$OMP SHARED(g_lo, error_array, gnl_1, gnl_2) &
537
          !$OMP SCHEDULE(static)
538
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
539
             error_array(:, :, iglo) = gnl_1(:, :, iglo) - gnl_2(:, :, iglo)
×
540
          end do
541
          !$OMP END PARALLEL DO
542
          errors(1) = gs2_max_abs(error_array) * (0.5 * half_time)
×
543
          errors(3) = max_vel
×
544
          call max_allreduce(errors)
×
545
          inverse_error = get_inverse_error(errors)
×
546
          cfl_time_step = 1.0 / errors(3)
×
547

548
          !Calculate new time step based on error
549
          time_step = min(actual_dt * sqrt(inverse_error), cfl_time_step)
×
550
          cfl_limited = time_step < actual_dt .and. exactly_equal(time_step, cfl_time_step)
×
551
          time_step = time_step * time_step_safety_factor
×
552

553
          ! If error is too large reject the step
554
          if ( inverse_error < 1.0 .or. (cfl_limited .and. immediate_reset)) then
×
555
             if (proc0 .and. debug) print*,'Attempted beuler step failed due to error or cfl, adapting time step'
556
             ! Reset as we're retrying the step.
557
             reject_step = .true.
×
558
          else
559
             reject_step = .false.
×
560
          end if
561
       end if
562

563
       if (reject_step) then
×
564
          ! If the time step is now too small then abort
565
          if (time_step < code_dt_min) call mp_abort("Time step has become too small in advance_nonlinear_term.", .true.)
×
566
          call copy(g_cur, g_state)
×
567
          ! If we store the initial field then we could perhaps just copy here instead.
568
          ! This could be faster as it avoids communications involved in the velocity integration.
569
          call calculate_fields(fields_func, g_state, phinew, aparnew, bparnew)
×
570
          nfailed_steps = nfailed_steps + 1
×
571
       else
572
          ! If we have met the error condition and not taken too many steps
573
          ! then g_state represents our new solution so make sure we update g to reflect this
574
          internal_time = internal_time + actual_dt
×
575
          call copy(g_state, g_cur)
×
576
          nsuccessful_steps = nsuccessful_steps + 1
×
577
       end if
578

579
    end do
580

581
    ! Store the final time step size so we can start from this in the next callg
582
    time_step_last = time_step
×
583

584
    if(proc0.and.debug) print*,'Explicit done in ',counter,'steps with final error',inverse_error,'and step',time_step,'final time',internal_time
585

586
  end subroutine advance_nonlinear_term_beuler
×
587

588
  !> Advances dg/dt = NL(g,chi) from current g_state, chi from t -> t+dt by using
589
  !> an Runge-Kutta scheme with embedded error estimate for error control. This method
590
  !> is a wrapper to the true generic RK implementation.
591
  subroutine advance_nonlinear_term_rk(g_state, phinew, aparnew, bparnew, dt, &
×
592
       fields_func, source_func)
593
    implicit none
594
    complex, dimension (:,:,:), intent(in out) :: g_state
595
    complex, dimension (:,:,:), intent (in out) :: phinew, aparnew, bparnew
596
    real, intent(in) :: dt
597
    procedure(invert_field_func) :: fields_func
598
    procedure(source_term_func) :: source_func
599

600
    call advance_nonlinear_term_rk_implementation( &
601
         g_state, phinew, aparnew, bparnew, dt, &
×
602
         fields_func, source_func, the_rk_scheme)
×
603
  end subroutine advance_nonlinear_term_rk
×
604

605
  !> Advances dg/dt = NL(g,chi) from current g_state, chi from t -> t+dt by using
606
  !> an Runge-Kutta scheme with embedded error estimate for error control
607
  subroutine advance_nonlinear_term_rk_implementation(g_state, phinew, &
×
608
       aparnew, bparnew, dt, fields_func, source_func, scheme)
×
609
    use theta_grid, only: ntgrid
610
    use gs2_time, only: code_dt_min
611
    use mp, only: mp_abort, proc0, max_allreduce
612
    use gs2_layouts, only: g_lo
613
    use rk_schemes, only: rk_scheme_type
614
    use run_parameters, only: immediate_reset
615
    use array_utils, only: copy, gs2_max_abs, zero_array
616
    use warning_helpers, only: exactly_equal
617
    implicit none
618
    complex, dimension (-ntgrid:, :, g_lo%llim_proc:), intent(in out) :: g_state
619
    complex, dimension (-ntgrid:,:,:), intent (in out) :: phinew, aparnew, bparnew
620
    complex, dimension(:, :, :), allocatable :: g_cur, gnl_1
×
621
    real, intent(in) :: dt
622
    type(rk_scheme_type), intent(in) :: scheme
623
    complex, dimension (:, :, :, :), allocatable :: stages
×
624
    real :: internal_time, time_step, max_vel, inverse_error
625
    real :: new_time_step, cfl_time_step
626
    integer :: counter, nstages
627
    logical, parameter :: debug = .false.
628
    integer :: istage, istage_sub, iglo
629
    real, dimension(:), allocatable :: solution_coeffs, error_coeffs
×
630
    real, dimension(3) :: errors
631
    real, save :: time_step_last = -1
632
    procedure(invert_field_func) :: fields_func
633
    procedure(source_term_func) :: source_func
634
    logical :: cfl_limited
635
    real :: half_time
636
    real, dimension(:), allocatable :: stage_coeffs
×
637

638
    ! Initialise internal variables
639
    if (time_step_last < 0) time_step_last = dt
×
640
    internal_time = 0.0
×
641
    counter = 1
×
642
    time_step = time_step_last
×
643

644
    ! Copy the relevant coefficients for forming the solution to reduce
645
    ! later duplication.
646
    if (scheme%follow_high_order) then
×
647
       allocate(solution_coeffs, source = scheme%high_order_coeffs)
×
648
    else
649
       allocate(solution_coeffs, source = scheme%lower_order_coeffs)
×
650
    end if
651

652
    ! Get the error coefficients
653
    allocate(error_coeffs, source = scheme%high_order_coeffs - scheme%lower_order_coeffs)
×
654

655
    nstages = scheme%number_of_stages
×
656
    allocate(stages(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc, nstages))
×
657
    allocate(gnl_1(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
658
    allocate(g_cur(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
659
    call copy(g_state, g_cur) ; call zero_array(stages) ; call zero_array(gnl_1)
×
660

661
    ! Keep taking explicit steps until we have advanced by dt
662
    do while (internal_time < dt)
×
663
       if(proc0.and.debug) print*,'Taking step with size',time_step,'at time',internal_time
664
       half_time = 0.5 * time_step
×
665

666
       do istage = 1, nstages
×
667
          call copy(g_cur, g_state)
×
668
          stage_coeffs = half_time * scheme%coeffs(:, istage)
×
669

670
          !$OMP PARALLEL DO DEFAULT(none) &
671
          !$OMP PRIVATE(istage_sub, iglo) &
672
          !$OMP SHARED(g_lo, g_state, half_time, scheme, stages, istage, stage_coeffs) &
673
          !$OMP COLLAPSE(2) &
674
          !$OMP SCHEDULE(static)
675
          do istage_sub = 1, istage-1
×
676
             do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
677
                g_state(:, :, iglo) = g_state(:, :, iglo) + stage_coeffs(istage_sub) * stages(:, :, iglo, istage_sub)
×
678
             end do
679
          end do
680
          !$OMP END PARALLEL DO
681
          call calculate_fields(fields_func, g_state, phinew, aparnew, bparnew)
×
682

683
          ! Get the current nonlinear source term
684
          call source_func(g_state,  stages(:, :, :, istage), &
×
685
               phinew, aparnew, bparnew, &
×
686
               max_vel, need_to_adjust = .not. advance_nonadiabatic_dfn, &
687
               calculate_cfl_limit = (istage == 1))
×
688

689
          nrhs_calls = nrhs_calls + 1
×
690
          if (istage == 1) errors(3) = max_vel
×
691

692
       end do
693

694
       ! One can directly form the error by simply forming error =
695
       ! time_step * 0.5 * sum(stages_i * (high_order_coeffs_i -
696
       ! low_order_coeffs_i)). Here we store this in gnl_1
697
       ! without the time_step * 0.5 factor (to avoid extra
698
       ! array operations). We multiply the final error by
699
       ! time_step/2 to ensure full consistency.
700
       ! Could we merge this OpenMP parallel region with the
701
       ! other loop directly below to avoid some overhead?
702
       !$OMP PARALLEL DO DEFAULT(none) &
703
       !$OMP PRIVATE(iglo) &
704
       !$OMP SHARED(g_lo, gnl_1, error_coeffs, stages) &
705
       !$OMP SCHEDULE(static)
706
       do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
707
          gnl_1(:, :, iglo) = error_coeffs(1) * stages(:, :, iglo, 1)
×
708
       end do
709
       !$OMP END PARALLEL DO
710

711
       !$OMP PARALLEL DO DEFAULT(none) &
712
       !$OMP PRIVATE(iglo, istage) &
713
       !$OMP SHARED(g_lo, gnl_1, error_coeffs, nstages, stages) &
714
       !$OMP COLLAPSE(2) &
715
       !$OMP SCHEDULE(static)
716
       do istage = 2, nstages
×
717
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
718
             gnl_1(:, :, iglo) = gnl_1(:, :, iglo) + error_coeffs(istage) * stages(:, :, iglo, istage)
×
719
          end do
720
       end do
721
       !$OMP END PARALLEL DO
722

723
       ! Store the absolute error
724
       errors(1) = gs2_max_abs(gnl_1) * half_time
×
725
       ! Estimate the absolution size of the solution using
726
       ! the old solution
727
       errors(2) = gs2_max_abs(g_cur)
×
728
       call max_allreduce(errors)
×
729
       inverse_error = get_inverse_error(errors)
×
730
       cfl_time_step = 1.0 / errors(3)
×
731

732
       !Calculate the new_time_step
733
       new_time_step = min(time_step * (inverse_error)**(1.0/scheme%order), cfl_time_step)
×
734
       cfl_limited = new_time_step < time_step .and. exactly_equal(new_time_step, cfl_time_step)
×
735
       new_time_step = new_time_step * time_step_safety_factor
×
736

737
       if(proc0 .and. debug) print*,'Inverse error is ',inverse_error,'at internal_time', &
738
            internal_time,'with step',time_step,'new time step is',new_time_step, &
739
            'counter=',counter
740

741
       ! If the cfl time step is too small then abort
742
       if (new_time_step < code_dt_min) &
×
743
            call mp_abort("Time step has become too small in advance_nonlinear_term.", .true.)
×
744

745
       ! If the error is too large we need to retry with a smaller step, so don't
746
       ! update anything
747
       if (inverse_error < 1.0 .or. (cfl_limited .and. immediate_reset)) then
×
748
          if(proc0.and.debug) print*,'Time step with size',time_step, &
749
               'failed at internal_time',internal_time,'and counter',counter, &
750
               'retrying with step',new_time_step
751
          nfailed_steps = nfailed_steps + 1
×
752
       else
753
          stage_coeffs = solution_coeffs * half_time
×
754
          !Update the solution. Note we could probably merge the two
755
          !OpenMP loops into a single OpenMP parallel region and then
756
          !just add OMP DO to each loop. This would save a bit of overhead.
757
          !$OMP PARALLEL DO DEFAULT(none) &
758
          !$OMP PRIVATE(iglo) &
759
          !$OMP SHARED(g_lo, g_cur, solution_coeffs, stage_coeffs, stages) &
760
          !$OMP SCHEDULE(static)
761
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
762
             g_cur(:, :, iglo) = g_cur(:, :, iglo) + stage_coeffs(1) * stages(:, :, iglo, 1)
×
763
          end do
764
          !$OMP END PARALLEL DO
765

766
          !$OMP PARALLEL DO DEFAULT(none) &
767
          !$OMP PRIVATE(istage, iglo) &
768
          !$OMP SHARED(g_lo, g_cur, solution_coeffs, nstages, half_time, &
769
          !$OMP stages, stage_coeffs) &
770
          !$OMP COLLAPSE(2) &
771
          !$OMP SCHEDULE(static)
772
          do istage = 2, nstages
×
773
             do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
774
                g_cur(:, :, iglo) = g_cur(:, :, iglo) + stage_coeffs(istage) * stages(:, :, iglo, istage)
×
775
             end do
776
          end do
777
          !$OMP END PARALLEL DO
778

779
          internal_time = internal_time + time_step
×
780
          nsuccessful_steps = nsuccessful_steps + 1
×
781
       end if
782

783
       !Now update the time step, capped to dt
784
       time_step = min(new_time_step, dt)
×
785

786
       ! Make sure we don't overshoot the target time by limiting time step.
787
       if(internal_time < dt) then
×
788
          time_step = min(time_step, dt - internal_time)
×
789
          counter = counter + 1
×
790
       end if
791

792
    end do
793

794
    if(proc0.and.debug) print*,'Completed rk step in',counter,'steps to',internal_time
795

796
    ! We may be able to avoid this copy and field solve on exit if we restructure the main
797
    ! loop slightly so g_state represents the new solution. This may require use of g_work
798
    ! or similar to hold intermediate values.
799
    call copy(g_cur, g_state)
×
800

801
    time_step_last = time_step
×
802
  end subroutine advance_nonlinear_term_rk_implementation
×
803

804
  !> Advances dg/dt = NL(g,chi) from current g_state, chi from t -> t+dt by using
805
  !> a simple Picard iteration scheme
806
  subroutine advance_nonlinear_term_picard(g_state, phinew, &
×
807
       aparnew, bparnew, dt, fields_func, source_func)
×
808
    use theta_grid, only: ntgrid
809
    use gs2_time, only: code_dt_min
810
    use mp, only: mp_abort, proc0, max_allreduce
811
    use gs2_layouts, only: g_lo
812
    use array_utils, only: copy, gs2_max_abs, zero_array
813
    implicit none
814
    complex, dimension (-ntgrid:, :, g_lo%llim_proc:), intent(in out) :: g_state
815
    complex, dimension (-ntgrid:,:,:), intent (in out) :: phinew, aparnew, bparnew
816
    complex, dimension(:, :, :), allocatable :: gnl_1
×
817
    real, intent(in) :: dt
818
    real :: internal_time, time_step, max_vel, cfl_limit
819
    integer :: counter, ipic, iglo
820
    logical, parameter :: debug = .false.
821
    real, dimension(4) :: errors
822
    real, save :: time_step_last = -1
823
    procedure(invert_field_func) :: fields_func
824
    procedure(source_term_func) :: source_func
825
    complex, dimension(:, :, :), allocatable :: g_start
×
826
    integer, parameter :: npic_limit = 15, npic_low_limit = 3
827
    real, parameter :: time_step_factor = 2.0
828
    logical, parameter :: check_cfl = .true.
829
    logical :: converged
830
    real :: half_time
831

832
    ! Initialise internal variables
833
    if (time_step_last < 0) time_step_last = dt
×
834
    internal_time = 0.0
×
835
    counter = 1
×
836
    time_step = time_step_last
×
837

838
    allocate(g_start(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
839
    allocate(gnl_1(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc))
×
840
    call zero_array(g_start) ; call zero_array(gnl_1)
×
841
    ! Keep taking explicit steps until we have advanced by dt
842
    do while (internal_time < dt)
×
843
       call copy(g_state, g_start)
×
844
       half_time = 0.5 * time_step
×
845

846
       if(proc0.and.debug) print*,'Taking step with size',time_step,'at time',internal_time
847
       ipic = 1
×
848

849
       call calculate_fields(fields_func, g_state, phinew, aparnew, bparnew)
×
850

851
       ! Get the current nonlinear source term
852
       call source_func(g_state, gnl_1, &
×
853
            phinew, aparnew, bparnew, &
×
854
            max_vel, need_to_adjust = .not. advance_nonadiabatic_dfn, &
855
            calculate_cfl_limit = check_cfl)
×
856
       nrhs_calls = nrhs_calls + 1
×
857

858
       errors(1) = 0.0
×
859
       errors(2) = gs2_max_abs(gnl_1) * half_time
×
860
       errors(3) = gs2_max_abs(g_start)
×
861
       errors(4) = max_vel
×
862
       call max_allreduce(errors)
×
863

864
       ! Check for CFL limit - we can simply rescale the change in g and carry on
865
       ! so here we simply rescale the effective time step,
866
       cfl_limit = 1.0 / errors(4)
×
867
       if (time_step > cfl_limit .and. check_cfl) then
×
868
          ! Drop the effective time step a little from the limit
869
          cfl_limit = 0.9 * cfl_limit
×
870
          if(proc0.and.debug) print*,'Dropping time step due to cfl from',time_step,'to',cfl_limit
871
          errors(2) = errors(2) * cfl_limit / time_step
×
872
          time_step = cfl_limit
×
873
          half_time = time_step * 0.5
×
874
       end if
875

876
       converged = picard_converged(errors)
×
877

878
       !$OMP PARALLEL DO DEFAULT(none) &
879
       !$OMP PRIVATE(iglo) &
880
       !$OMP SHARED(g_state, g_start, gnl_1, half_time, g_lo)&
881
       !$OMP SCHEDULE(static)
882
       do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
883
          g_state(:, :, iglo) = g_start(:, :, iglo) + gnl_1(:, :, iglo) * half_time
×
884
       end do
885
       !$OMP END PARALLEL DO
886

887
       do while(.not. converged)
×
888
          ! Note the first step (i.e. call before this loop) is included in
889
          ! ipic here (i.e. it counts towards our approach towards npic_limit).
890
          ipic = ipic + 1
×
891
          if (ipic > npic_limit) exit
×
892

893
          call calculate_fields(fields_func, g_state, phinew, aparnew, bparnew)
×
894

895
          ! Get the current nonlinear source term
896
          call source_func(g_state, gnl_1, &
×
897
               phinew, aparnew, bparnew, &
×
898
               max_vel, need_to_adjust = .not. advance_nonadiabatic_dfn, &
899
               calculate_cfl_limit = check_cfl)
×
900
          nrhs_calls = nrhs_calls + 1
×
901

902
          errors(1) = errors(2)
×
903
          errors(2) = gs2_max_abs(gnl_1) * half_time
×
904
          errors(4) = max_vel
×
905
          call max_allreduce(errors)
×
906
          cfl_limit = 1.0 / errors(4)
×
907

908
          converged = picard_converged(errors)
×
909

910
          if(proc0.and.debug) print*,'ipic',ipic,converged,'|',errors
911

912
          if (time_step > cfl_limit .and. .not. converged) exit
×
913

914
          !$OMP PARALLEL DO DEFAULT(none) &
915
          !$OMP PRIVATE(iglo) &
916
          !$OMP SHARED(g_state, g_start, gnl_1, half_time, g_lo)&
917
          !$OMP SCHEDULE(static)
918
          do iglo = g_lo%llim_proc, g_lo%ulim_proc
×
919
             g_state(:, :, iglo) = g_start(:, :, iglo) + gnl_1(:, :, iglo) * half_time
×
920
          end do
921
          !$OMP END PARALLEL DO
922
       end do
923

924
       if (.not. converged) then
×
925
          ! If we didn't converge in the limit then reset state
926
          ! to the start of the step and reduce the time step.
927
          call copy(g_start, g_state)
×
928
          time_step = time_step / time_step_factor
×
929
          nfailed_steps = nfailed_steps + 1
×
930

931
          ! If the time step is too small then abort
932
          if (time_step < code_dt_min) &
×
933
               call mp_abort("Time step has become too small in advance_nonlinear_term.", .true.)
×
934
       else
935
          internal_time = internal_time + time_step
×
936
          nsuccessful_steps = nsuccessful_steps + 1
×
937
          ! If we converged quickly then increase the time step
938
          if (ipic <= npic_low_limit) time_step = time_step * time_step_factor
×
939
       end if
940

941
       !Now update the time step, capped to dt
942
       time_step = min(time_step, dt)
×
943

944
       ! Make sure we don't overshoot the target time by limiting time step.
945
       if(internal_time < dt) then
×
946
          time_step = min(time_step, dt - internal_time)
×
947
          counter = counter + 1
×
948
       end if
949

950
    end do
951

952
    if(proc0.and.debug) print*,'Completed Picard step in',counter,'steps to',internal_time,'last time step',time_step
953

954
    time_step_last = time_step
×
955
  contains
956
    pure logical function picard_converged(errors) result(converged)
×
957
      implicit none
958
      real, dimension(4), intent(in) :: errors
959
      converged = &
960
           !Change in solution less than abs tol
961
           (errors(2) < absolute_tolerance) .or.  &
962
           ! Change in the change, less than abs tol
963
           (abs(errors(2) - errors(1)) < absolute_tolerance) .or. &
964
           ! Change is less than the relative tolerance
965
           (errors(2) < relative_tolerance * errors(3)) .or. &
966
           ! Change in the change less than the relative tolerance
967
           (abs(errors(2) - errors(1)) < relative_tolerance * errors(3))
×
968
    end function picard_converged
×
969

970
  end subroutine advance_nonlinear_term_picard
971

972
  !> Returns the normalised inverse error estimate. In other words
973
  !> the error tolerance, rtol*errors(2) + atol, divided by the error
974
  !> estimate (plus a small number to avoid divide by zero).
975
  !>
976
  !> Assumes that errors contains the global magnitude of the error
977
  !> estimate in the first element and the global maximum of the solution
978
  !> in the second element.
979
  real pure function get_inverse_error(errors) result(inverse_error)
×
980
    implicit none
981
    real, dimension(:), intent(in) :: errors
982
    inverse_error = (relative_tolerance * errors(2) + absolute_tolerance) / &
×
983
         (errors(1) + epsilon(errors(1)))
×
984
  end function get_inverse_error
×
985

986
  !> Calculates the fields consistent with the passed distribution function
987
  subroutine calculate_fields(fields_func, g_in, phi_out, apar_out, bpar_out)
×
988
    use nonlinear_terms, only: time_add_explicit_terms_field
989
    use job_manage, only: time_message
990
    procedure(invert_field_func) :: fields_func
991
    complex, dimension(:, :, :), intent(in) :: g_in
992
    complex, dimension (:,:,:), intent (out) :: phi_out, apar_out, bpar_out
993
    call time_message(.false., time_add_explicit_terms_field, 'Explicit terms - field')
×
994
    call fields_func(g_in, phi_out, apar_out, bpar_out, local_only = .true.)
×
995
    call time_message(.false., time_add_explicit_terms_field, 'Explicit terms - field')
×
996
  end subroutine calculate_fields
×
997

998
#include "split_nonlinear_terms_auto_gen.inc"
999
end module split_nonlinear_terms
×
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