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

gyrokinetics / gs2 / 2057264840

23 Sep 2025 12:41PM UTC coverage: 10.806%. Remained the same
2057264840

push

gitlab-ci

David Dickinson
Merged in bugfix/fix_change_in_nbset (pull request #1182)

5040 of 46640 relevant lines covered (10.81%)

119681.52 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, step_time, 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
    real, intent(in) :: step_time
182
    integer, intent(in), optional :: unit_in
183
    integer :: unit
184
    unit = get_option_with_default(unit_in, output_unit)
×
185
    write(unit,'("Iteration : ",I0," Number of internal steps : ",I0," Number of failed steps : ",I0," Number of RHS calls : ",I0," Wall time : ",0pf9.3," s")') &
186
         istep, nsuccessful_steps, nfailed_steps, nrhs_calls, step_time
×
187
  end subroutine report_step_statistics
×
188

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

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

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

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

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

251
    step_time = timer_local() - step_time
×
252
    if (proc0 .and. show_statistics) call report_step_statistics(istep, step_time)
×
253

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

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

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

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

293
    ! Initialise internal variables
294
    internal_time = 0.0
×
295
    counter = 1
×
296

297
    allocate(gnl_1(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc)) ; call zero_array(gnl_1)
×
298
    allocate(gnl_2(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc)) ; call zero_array(gnl_2)
×
299
    allocate(gnl_3(-ntgrid:ntgrid, 2, g_lo%llim_proc:g_lo%ulim_alloc)) ; call zero_array(gnl_3)
×
300

301
    ! Reset time step sizes to reflect fact we're restarting the explicit scheme
302
    code_dt_prev1 = dt_not_set
×
303
    code_dt_prev2 = dt_not_set
×
304

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

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

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

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

325
       ! Get the Adams-Bashforth coefficients for the current collection of time step sizes
326
       ab_coeffs = get_adams_bashforth_coefficients(target_dt = time_step)
×
327

328
       half_time = 0.5 * time_step
×
329

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

370
       ! Calculate the fields consistent with the new g
371
       call calculate_fields(fields_func, g_state, phinew, aparnew, bparnew)
×
372

373
       ! Increment internal state
374
       internal_time = internal_time + time_step
×
375
       counter = counter + 1
×
376
       nsuccessful_steps = nsuccessful_steps + 1
×
377

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

385
  end subroutine advance_nonlinear_term_ab3
×
386

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

416
    ! Initialise internal variables
417
    if (time_step_last < 0) time_step_last = dt
×
418
    internal_time = 0.0
×
419
    time_step = time_step_last
×
420

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

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

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

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

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

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

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

470
          ! Calculate the maximum absolute error and the maximum value of the previous solution
471

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

487
          ! Calculate an approximate relative error
488
          error = errors(1) / errors(2)
×
489

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

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

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

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

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

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

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

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

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

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

582
    end do
583

584
    ! Store the final time step size so we can start from this in the next callg
585
    time_step_last = time_step
×
586

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

589
  end subroutine advance_nonlinear_term_beuler
×
590

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

603
    call advance_nonlinear_term_rk_implementation( &
604
         g_state, phinew, aparnew, bparnew, dt, &
×
605
         fields_func, source_func, the_rk_scheme)
×
606
  end subroutine advance_nonlinear_term_rk
×
607

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

641
    ! Initialise internal variables
642
    if (time_step_last < 0) time_step_last = dt
×
643
    internal_time = 0.0
×
644
    counter = 1
×
645
    time_step = time_step_last
×
646

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

655
    ! Get the error coefficients
656
    allocate(error_coeffs, source = scheme%high_order_coeffs - scheme%lower_order_coeffs)
×
657

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

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

669
       do istage = 1, nstages
×
670
          call copy(g_cur, g_state)
×
671
          stage_coeffs = half_time * scheme%coeffs(:, istage)
×
672

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

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

692
          nrhs_calls = nrhs_calls + 1
×
693
          if (istage == 1) errors(3) = max_vel
×
694

695
       end do
696

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

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

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

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

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

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

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

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

782
          internal_time = internal_time + time_step
×
783
          nsuccessful_steps = nsuccessful_steps + 1
×
784
       end if
785

786
       !Now update the time step, capped to dt
787
       time_step = min(new_time_step, dt)
×
788

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

795
    end do
796

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

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

804
    time_step_last = time_step
×
805
  end subroutine advance_nonlinear_term_rk_implementation
×
806

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

835
    ! Initialise internal variables
836
    if (time_step_last < 0) time_step_last = dt
×
837
    internal_time = 0.0
×
838
    counter = 1
×
839
    time_step = time_step_last
×
840

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

849
       if(proc0.and.debug) print*,'Taking step with size',time_step,'at time',internal_time
850
       ipic = 1
×
851

852
       call calculate_fields(fields_func, g_state, phinew, aparnew, bparnew)
×
853

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

861
       errors(1) = 0.0
×
862
       errors(2) = gs2_max_abs(gnl_1) * half_time
×
863
       errors(3) = gs2_max_abs(g_start)
×
864
       errors(4) = max_vel
×
865
       call max_allreduce(errors)
×
866

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

879
       converged = picard_converged(errors)
×
880

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

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

896
          call calculate_fields(fields_func, g_state, phinew, aparnew, bparnew)
×
897

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

905
          errors(1) = errors(2)
×
906
          errors(2) = gs2_max_abs(gnl_1) * half_time
×
907
          errors(4) = max_vel
×
908
          call max_allreduce(errors)
×
909
          cfl_limit = 1.0 / errors(4)
×
910

911
          converged = picard_converged(errors)
×
912

913
          if(proc0.and.debug) print*,'ipic',ipic,converged,'|',errors
914

915
          if (time_step > cfl_limit .and. .not. converged) exit
×
916

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

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

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

944
       !Now update the time step, capped to dt
945
       time_step = min(time_step, dt)
×
946

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

953
    end do
954

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

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

973
  end subroutine advance_nonlinear_term_picard
974

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

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

1001
#include "split_nonlinear_terms_auto_gen.inc"
1002
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