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

gyrokinetics / gs2 / 2021218321

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

push

gitlab-ci

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

4710 of 44407 relevant lines covered (10.61%)

125698.1 hits per line

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

0.0
/src/gs2_diagnostics.fpp
1
#include "unused_dummy.inc"
2
!> A module for calculating and writing the main GS2 outputs.
3
module gs2_diagnostics
4
  use gs2_heating, only: heating_diagnostics
5
  use gs2_save, only: save_many
6
  use diagnostics_configuration, only: diagnostics_config_type
7
  use gs2_io, only: get_netcdf_file_id
8

9
  implicit none
10

11
  private
12

13
  public :: read_parameters, init_gs2_diagnostics, finish_gs2_diagnostics
14
  public :: check_gs2_diagnostics, wnml_gs2_diagnostics, check_restart_file_writeable
15
  public :: loop_diagnostics, omegaavg, calculate_instantaneous_omega
16
  public :: diffusivity, calculate_simple_quasilinear_flux_metric_by_k
17
  public :: save_restart_dist_fn, do_write_fyx, do_write_f, do_write_parity
18
  public :: do_write_heating, do_write_nl_flux_dist, do_write_geom, heating
19
  public :: save_distfn, save_glo_info_and_grids, save_velocities, save_for_restart
20
  public :: omegatol, nwrite, nmovie, navg, nsave, make_movie, exit_when_converged
21
  public :: do_write_correlation_extend, do_write_correlation, do_write_symmetry
22
  public :: do_final_gs2_diagnostics
23

24
  real :: omegatinst, omegatol, damped_threshold, omega_checks_start
25
  logical :: print_line, print_flux_line, write_line, write_flux_line
26
  logical :: write_omega, write_omavg, write_ascii, write_gs, write_ql_metric
27
  logical :: write_g, write_gyx, write_eigenfunc, write_fields, write_final_fields
28
  logical :: write_final_antot, write_final_moments, write_avg_moments, write_parity
29
  logical :: write_moments, ob_midplane, write_final_db
30
  logical :: write_cross_phase, write_final_epar, write_kpar, write_heating, write_lorentzian
31
  logical :: write_fluxes, write_fluxes_by_mode, write_kinetic_energy_transfer, write_verr
32
  logical :: write_cerr, write_max_verr, exit_when_converged, use_nonlin_convergence
33
  logical :: save_for_restart, save_distfn, save_glo_info_and_grids, save_velocities
34
  logical :: write_symmetry, write_correlation_extend, write_correlation, make_movie
35
  logical :: write_nl_flux_dist, file_safety_check, append_old, make_restart_dir
36
  logical :: write_phi_over_time, write_apar_over_time, write_bpar_over_time, write_jext
37
  integer :: nwrite, nmovie, navg, nsave, igomega, nwrite_mult, nc_sync_freq
38

39
  ! internal. `write_any` differs from new diagnostics input `write_any`. The
40
  ! latter can be used to turn off all output, whereas here, it's used to
41
  ! _check_ if any outputs are enabled
42
  logical :: write_any, write_any_fluxes
43
  logical, private :: initialized = .false.
44
  complex, allocatable, dimension (:,:,:) :: domega
45

46
  !> Complex frequency, and time-averaged complex frequency
47
  complex, dimension (:, :), allocatable :: omega, omegaavg
48

49
  integer :: out_unit, heat_unit, heat_unit2, lpc_unit
50
  integer :: jext_unit, phase_unit, dist_unit, yxdist_unit
51
  integer :: res_unit, res_unit2, parity_unit, cres_unit
52
  integer :: conv_nstep_av, conv_min_step, conv_max_step
53
  integer :: conv_nsteps_converged
54

55
  !> Frequency time history, size `(navg, ntheta0, naky)`
56
  complex, dimension (:,:,:), allocatable :: omegahist
57

58
  !> Heating diagnostics summed over space at the current timestep
59
  type (heating_diagnostics) :: h
60
  !> Heating diagnostics summed over space over the last [[gs2_diagnostics_knobs:navg]] timesteps
61
  type (heating_diagnostics), dimension(:), save, allocatable :: h_hist
62
  !> Heating diagnostics as a function of \((\theta, k_y)\) at the current timestep
63
  type (heating_diagnostics), dimension(:,:), save, allocatable :: hk
64
  !> Heating diagnostics as a function of \((\theta, k_y)\) over the last [[gs2_diagnostics_knobs:navg]] timesteps
65
  type (heating_diagnostics), dimension(:,:,:), save, allocatable :: hk_hist
66
  !GGH J_external
67
  real, dimension(:,:,:), allocatable ::  j_ext_hist
68

69
  real, dimension (:,:,:), allocatable ::  pflux_tormom
70

71
  real, dimension (:), allocatable :: pflux_avg, qflux_avg, heat_avg, vflux_avg
72
  real :: conv_test_multiplier
73

74
  integer :: nout = 1
75
  integer :: nout_movie = 1
76
  integer :: nout_big = 1
77
  complex :: wtmp_old = 0.
78

79
contains
80

81
  !> Write the diagnostics namelist to file
82
  subroutine wnml_gs2_diagnostics(unit)
×
83
    use diagnostics_configuration, only: diagnostics_config
84
    implicit none
85
    !> Unit of an open file to write to
86
    integer, intent(in) :: unit
87
    call diagnostics_config%write(unit)
×
88
  end subroutine wnml_gs2_diagnostics
×
89

90
  !> Perform some basic checking of the diagnostic input parameters, and write the results to file
91
  subroutine check_gs2_diagnostics(report_unit)
×
92
    use file_utils, only: run_name
93
    use nonlinear_terms, only: nonlin
94
    use dist_fn, only : def_parity, even 
95
    use kt_grids, only : is_box
96
    use init_g, only : restart_file
97
    use gs2_save, only: restart_writable
98
    implicit none
99
    !> Unit of an open file to write to
100
    integer, intent(in) :: report_unit
101
    logical :: writable
102
    write (report_unit, *) 
×
103
    write (report_unit, fmt="('------------------------------------------------------------')")
×
104
    write (report_unit, *) 
×
105
    write (report_unit, fmt="('Diagnostic control section.')")
×
106

107
    if (print_line) then
×
108
       write (report_unit, fmt="('print_line = T:            Estimated frequencies &
109
            & output to the screen every ',i4,' steps.')") nwrite
×
110
    else
111
       ! nothing
112
    end if
113

114
    if (write_line) then
×
115
       if (write_ascii) then
×
116
          write (report_unit, fmt="('write_line = T:            Estimated frequencies output to ',a,' every ',i4,' steps.')") &
117
               & trim(run_name)//'.out',  nwrite
×
118
       end if
119
       write (report_unit, fmt="('write_line = T:            Estimated frequencies output to ',a,' every ',i4,' steps.')") &
120
            & trim(run_name)//'.out.nc',  nwrite
×
121
    else
122
       ! nothing
123
    end if
124

125
    if (print_flux_line) then
×
126
       write (report_unit, fmt="('print_flux_line = T:       Instantaneous fluxes output to screen every ', &
127
            & i4,' steps.')") nwrite
×
128
    else
129
       ! nothing
130
    end if
131

132
    if (write_flux_line) then
×
133
       if (write_ascii) then
×
134
          write (report_unit, fmt="('write_flux_line = T:       Instantaneous fluxes output to ',a,' every ',i4,' steps.')") &
135
               & trim(run_name)//'.out',  nwrite
×
136
       end if
137
       write (report_unit, fmt="('write_flux_line = T:       Instantaneous fluxes output to ',a,' every ',i4,' steps.')") &
138
            & trim(run_name)//'.out.nc',  nwrite
×
139
    else
140
       ! nothing
141
    end if
142

143
    if (write_omega) then
×
144
       if (write_ascii) then
×
145
          write (report_unit, fmt="('write_omega = T:           Instantaneous frequencies written to ',a)") trim(run_name)//'.out'
×
146
       else
147
          write (report_unit, fmt="('write_omega = T:           No effect.')")
×
148
       end if
149
       write (report_unit, fmt="('                           Frequencies calculated at igomega = ',i4)") igomega
×
150
       if (def_parity .and. .not. even) then
×
151
          write (report_unit, fmt="('################# WARNING #######################')")
×
152
          write (report_unit, fmt="('   You probably want igomega /= 0 for odd parity modes.')") 
×
153
          write (report_unit, fmt="('################# WARNING #######################')")
×
154
          write (report_unit, *) 
×
155
       end if
156
    end if
157

158
    if (write_omavg) then
×
159
       if (write_ascii) then
×
160
          write (report_unit, fmt="('write_omavg = T:           Time-averaged frequencies written to ',a)") trim(run_name)//'.out'
×
161
          write (report_unit, fmt="('                           Averages taken over ',i4,' timesteps.')") navg
×
162
       else
163
          write (report_unit, fmt="('write_omavg = T:           No effect.')")
×
164
       end if
165
    end if
166

167
    if (write_ascii) then
×
168
       write (report_unit, fmt="('write_ascii = T:           Write some data to ',a)") trim(run_name)//'.out'
×
169
    end if
170

171
    if (write_eigenfunc) then
×
172
       if (write_ascii) then
×
173
          write (report_unit, fmt="('write_eigenfunc = T:       Normalized Phi(theta) written to ',a)") trim(run_name)//'.eigenfunc'
×
174
       end if
175
       write (report_unit, fmt="('write_eigenfunc = T:       Normalized Phi(theta) written to ',a)") trim(run_name)//'.out.nc'
×
176
    end if
177

178
    if (write_final_fields) then
×
179
       if (write_ascii) then
×
180
          write (report_unit, fmt="('write_final_fields = T:    Phi(theta), etc. written to ',a)") trim(run_name)//'.fields'
×
181
       end if
182
       write (report_unit, fmt="('write_final_fields = T:    Phi(theta), etc. written to ',a)") trim(run_name)//'.out.nc'
×
183
    end if
184

185
    if (write_final_antot) then
×
186
       if (write_ascii) then
×
187
          write (report_unit, fmt="('write_final_antot = T:          Sources for Maxwell eqns. written to ',a)") &
188
               & trim(run_name)//'.antot'
×
189
       end if
190
       write (report_unit, fmt="('write_final_antot = T:          Sources for Maxwell eqns. written to ',a)") &
191
            & trim(run_name)//'.out.nc'
×
192
    end if
193

194
    if (write_final_moments) then
×
195
       if (write_ascii) then
×
196
          write (report_unit, fmt="('write_final_moments = T:   Low-order moments of g written to ',a)") &
197
               & trim(run_name)//'.moments'
×
198
          write (report_unit, fmt="('write_final_moments = T:   int dl/B average of low-order moments of g written to ',a)") &
199
               & trim(run_name)//'.amoments'
×
200
       end if
201
       write (report_unit, fmt="('write_final_moments = T:   Low-order moments of g written to ',a)") &
202
            & trim(run_name)//'.out.nc'
×
203
       write (report_unit, fmt="('write_final_moments = T:   int dl/B average of low-order moments of g written to ',a)") &
204
            & trim(run_name)//'.out.nc'
×
205
    end if
206

207
    if (write_avg_moments) then
×
208
       if (.not. is_box) then
×
209
          write (report_unit, *) 
×
210
          write (report_unit, fmt="('################# WARNING #######################')")
×
211
          write (report_unit, fmt="('write_avg_moments = T:          Ignored unless grid_option=box')")
×
212
          write (report_unit, fmt="('################# WARNING #######################')")
×
213
          write (report_unit, *) 
×
214
       else
215
          if (write_ascii) then
×
216
             write (report_unit, fmt="('write_avg_moments = T:     Flux surface averaged low-order moments of g written to ',a)") &
217
                  & trim(run_name)//'.moments'
×
218
          end if
219
          write (report_unit, fmt="('write_avg_moments = T:     Flux surface averaged low-order moments of g written to ',a)") &
220
               & trim(run_name)//'.out.nc'
×
221
       end if
222
    end if
223

224
    if (write_final_epar) then
×
225
       if (write_ascii) then
×
226
          write (report_unit, fmt="('write_final_epar = T:      E_parallel(theta) written to ',a)") trim(run_name)//'.epar'
×
227
       end if
228
       write (report_unit, fmt="('write_final_epar = T:      E_parallel(theta) written to ',a)") trim(run_name)//'.out.nc'
×
229
    end if
230

231
    if (write_fluxes) then
×
232
       if (write_ascii) then
×
233
          write (report_unit, fmt="('write_fluxes = T:         Phi**2(kx, ky) written to ',a)") trim(run_name)//'.out'
×
234
       end if
235
    else
236
       write (report_unit, fmt="('write_fluxes = F:         Phi**2(kx, ky) NOT written to ',a)") trim(run_name)//'.out'
×
237
    end if
238

239
    if (save_for_restart) then
×
240
       write (report_unit, fmt="('save_for_restart = T:      Restart files written to ',a)") trim(restart_file)//'.(PE)'
×
241
    else
242
       if (nonlin) then
×
243
          write (report_unit, *) 
×
244
          write (report_unit, fmt="('################# WARNING #######################')")
×
245
          write (report_unit, fmt="('save_for_restart = F:              This run cannot be continued.')")
×
246
          write (report_unit, fmt="('THIS IS PROBABLY AN ERROR.')") 
×
247
          write (report_unit, fmt="('################# WARNING #######################')")
×
248
          write (report_unit, *) 
×
249
       end if
250
    end if
251

252
    !Verify restart file can be written
253
    if((save_for_restart.or.save_distfn).and.(file_safety_check))then
×
254
       !Can we write file?
255
       writable=restart_writable()
×
256

257
       !If we can't write the restart file then we should probably quit
258
       if((.not.writable))then
×
259
          if(save_for_restart)then 
×
260
             write (report_unit, *) 
×
261
             write (report_unit, fmt="('################# WARNING #######################')")
×
262
             write (report_unit, fmt="('save_for_restart = T:   But we cannot write to a test file like ',A,'.')") trim(restart_file)
×
263
             write (report_unit, fmt="('THIS IS PROBABLY AN ERROR --> Check restart_dir.')") 
×
264
             write (report_unit, fmt="('################# WARNING #######################')")
×
265
             write (report_unit, *) 
×
266
          endif
267
          if(save_distfn)then 
×
268
             write (report_unit, *) 
×
269
             write (report_unit, fmt="('################# WARNING #######################')")
×
270
             write (report_unit, fmt="('save_distfn = T:   But we cannot write to a test file like ',A,'.')") trim(restart_file)
×
271
             write (report_unit, fmt="('THIS IS PROBABLY AN ERROR --> Check restart_dir.')") 
×
272
             write (report_unit, fmt="('################# WARNING #######################')")
×
273
             write (report_unit, *) 
×
274
          endif
275
       endif
276
    endif
277

278
  end subroutine check_gs2_diagnostics
×
279

280
  !> Initialise this module and all its dependencies, including defining NetCDF
281
  !> vars, call real_init, which calls read_parameters; broadcast all the
282
  !> different write flags.
283
  subroutine init_gs2_diagnostics (gs2_diagnostics_config_in, header)
×
284
    use kt_grids, only: ntheta0, naky
285
    use species, only: nspec
286
    use gs2_io, only: init_gs2_io
287
    use gs2_heating, only: init_htype
288
    use collisions, only: collision_model_switch, init_lorentz_error
289
    use collisions, only: collision_model_lorentz, collision_model_lorentz_test
290
    use mp, only: broadcast, mp_abort
291
    use diagnostics_final_routines, only: init_par_filter
292
    use diagnostics_velocity_space, only: init_weights, setup_legendre_transform
293
    use standard_header, only: standard_header_type
294
    implicit none
295
    !> Input parameters for this module
296
    type(diagnostics_config_type), intent(in), optional :: gs2_diagnostics_config_in
297
    !> Header for files with build and run information
298
    type(standard_header_type), intent(in), optional :: header
299
    ! Actual value for optional `header` input
300
    type(standard_header_type) :: local_header
×
301

302
    if (present(header)) then
×
303
      local_header = header
×
304
    else
305
      local_header = standard_header_type()
×
306
    end if
307

308
    if (initialized) return
×
309
    initialized = .true.
×
310

311
    call real_init (gs2_diagnostics_config_in, header=local_header)
×
312

313
    ! initialize weights for less accurate integrals used
314
    ! to provide an error estimate for v-space integrals (energy and untrapped)
315
    if (write_verr) then
×
316
       call init_weights
×
317
       call setup_legendre_transform
×
318
    end if
319

320
    ! allocate heating diagnostic data structures
321
    if (write_heating) then
×
322
       allocate (h_hist(0:navg-1))
×
323
       call init_htype (h_hist,  nspec)
×
324

325
       allocate (hk_hist(ntheta0,naky,0:navg-1))
×
326
       call init_htype (hk_hist, nspec)
×
327

328
       call init_htype (h,  nspec)
×
329

330
       allocate (hk(ntheta0, naky))
×
331
       call init_htype (hk, nspec)
×
332
    else
333
       allocate (h_hist(0))
×
334
       allocate (hk(1,1))
×
335
       allocate (hk_hist(1,1,0))
×
336
    end if
337

338
    !GGH Allocate density and velocity perturbation diagnostic structures
339
    if (write_jext) then
×
340
       allocate (j_ext_hist(ntheta0, naky,0:navg-1))
×
341
       j_ext_hist = 0
×
342
    end if
343

344
    call init_gs2_io (append_old, make_movie, write_correlation_extend, &
345
         write_phi_over_time, write_apar_over_time, write_bpar_over_time, &
346
         nout, header=local_header)
×
347

348
    call broadcast (nout)
×
349

350
    if (write_cerr) then
×
351
       if (collision_model_switch == collision_model_lorentz .or. &
×
352
            collision_model_switch == collision_model_lorentz_test) then
353
          call init_lorentz_error
×
354
       else
355
          write_cerr = .false.
×
356
       end if
357
    end if
358

359
    if(.not. allocated(pflux_avg)) then
×
360
       allocate (pflux_avg(nspec), qflux_avg(nspec), heat_avg(nspec), vflux_avg(nspec))
×
361
       pflux_avg = 0.0 ; qflux_avg = 0.0 ; heat_avg = 0.0 ; vflux_avg = 0.0
×
362
    endif
363

364
    call check_restart_file_writeable(file_safety_check, save_for_restart, save_distfn, &
365
         make_restart_dir)
×
366

367
    !Setup the parallel fft if we're writing/using the parallel spectrum
368
    if (write_kpar .or. write_gs) call init_par_filter
×
369
  end subroutine init_gs2_diagnostics
×
370

371
  !> Check if we can write the restart files
372
  !>
373
  !> If restart files aren't writable, aborts if `need_restart` is
374
  !> true, or sets `extra_files` to false. Also prints a warning in
375
  !> the second case.
376
  subroutine check_restart_file_writeable(check_writable, need_restart, extra_files, &
×
377
       create_restart_dir)
378
    use init_g, only: get_restart_dir
379
    use gs2_save, only: restart_writable
380
    use mp, only: proc0, mp_abort, broadcast
381
    implicit none
382
    !> Has the user requested this check
383
    logical, intent(in) :: check_writable
384
    !> Has the user requested restart files
385
    logical, intent(in) :: need_restart
386
    !> Has the user requested distribution function to be written
387
    logical, intent(inout) :: extra_files
388
    !> Do we want to try to create the restart dir if initial writes fail?
389
    logical, intent(inout) :: create_restart_dir
390

391
    ! Error message from trying to open restart file
392
    character(len=:), allocatable :: error_message
×
393
    ! GS2 error message to show user
394
    character(len=:), allocatable :: abort_message
×
395

396
    ! Assume everything's fine if we're not checking, or if it's not needed
397
    if (.not. check_writable) return
×
398
    if (.not. (need_restart .or. extra_files)) return
×
399

400
    ! If we can write the restart files, we're done
401
    if (restart_writable(error_message=error_message)) return
×
402

403
    if (create_restart_dir) then
×
404
       if (proc0) then
×
405
          write(*, '(A," (",A,") ",A)') "Initial attempt to write to restart_dir", trim(get_restart_dir()),"failed, attempting to create it."
×
406
          call execute_command_line('mkdir -p ' // trim(get_restart_dir()))
×
407
       end if
408

409
       ! If we can now write the restart files, we're done
410
       if (restart_writable(error_message=error_message)) return
×
411
    end if
412

413
    abort_message = " Cannot write restart files! Error message was:" // new_line('a') &
414
         // "    " // error_message // new_line('a') &
415
         // " Please check that `init_g_knobs::restart_dir = " // trim(get_restart_dir()) &
416
         // "` exists and has the correct permissions."
×
417

418
    ! User has requested restart files, but we can't write them => abort
419
    if (need_restart) then
×
420
      abort_message = abort_message // new_line('a') // "    --> Aborting"
×
421
      call mp_abort(trim(abort_message), to_screen=.true.)
×
422
    end if
423

424
    ! If it's just a case of save_distfn, then we can carry on but
425
    ! disable `save_distfn` and print a useful mesasge
426
    if (extra_files) then
×
427
      if(proc0) write(*, '(a, a, a)') abort_message, new_line('a'), "    --> Setting `save_distfn = F`"
×
428
      extra_files = .false.
×
429
    endif
430
  end subroutine check_restart_file_writeable
×
431

432
  !> Read the input parameters; open the various text output files according to
433
  !> the relevant input flags; allocate and zero the module-level flux arrays,
434
  !> [[gs2_diagnostics_knobs:omega]] and [[gs2_diagnostics_knobs:omegaavg]]
435
  subroutine real_init(gs2_diagnostics_config_in, header)
×
436
    use run_parameters, only: has_apar
437
    use file_utils, only: open_output_file, get_unused_unit
438
    use kt_grids, only: naky, ntheta0
439
    use mp, only: proc0
440
    use standard_header, only: standard_header_type
441
    use diagnostics_fluxes, only: init_diagnostics_fluxes
442
    use diagnostics_kinetic_energy_transfer, only: init_diagnostics_kinetic_energy_transfer
443
    use diagnostics_nonlinear_convergence, only: init_nonlinear_convergence
444
    implicit none
445
    !> Input parameters for this module
446
    type(diagnostics_config_type), intent(in), optional :: gs2_diagnostics_config_in
447
    !> Header for files with build and run information
448
    type(standard_header_type), intent(in), optional :: header
449
    ! Actual value for optional `header` input
450
    type(standard_header_type) :: local_header
×
451

452
    if (present(header)) then
×
453
      local_header = header
×
454
    else
455
      local_header = standard_header_type()
×
456
    end if
457

458
    call read_parameters(gs2_diagnostics_config_in)
×
459

460
    if (proc0) then
×
461
       if (write_ascii) then
×
462
          call open_output_file (out_unit, ".out")          
×
463
       end if
464

465
       if (write_cross_phase .and. write_ascii) then
×
466
          call open_output_file (phase_unit, ".phase")
×
467
       end if
468

469
       if (write_heating .and. write_ascii) then
×
470
          call open_output_file (heat_unit, ".heat")
×
471
          call open_output_file (heat_unit2, ".heat2")
×
472
       end if
473

474
       if (write_verr .and. write_ascii) then
×
475
          call open_output_file (res_unit, ".vres")
×
476
          call open_output_file (lpc_unit, ".lpc")
×
477
          if (write_max_verr) call open_output_file (res_unit2, ".vres2")
×
478
       end if
479

480
       if (write_cerr .and. write_ascii) then
×
481
          call open_output_file (cres_unit, ".cres")
×
482
       end if
483

484
       if (write_parity .and. write_ascii) then
×
485
          call open_output_file (parity_unit, ".parity")
×
486
       end if
487

488
       if (write_g .and. write_ascii) then
×
489
          call open_output_file(dist_unit, ".dist")
×
490
       end if
491

492
       if (write_gyx .and. write_ascii) then
×
493
          call open_output_file(yxdist_unit, ".yxdist")
×
494
       end if
495

496
       !GGH J_external, only if A_parallel is being calculated.
497
       if (write_jext .and. has_apar) then
×
498
          if (write_ascii) then
×
499
             call open_output_file (jext_unit, ".jext")
×
500
          end if
501
       else
502
          write_jext = .false.
×
503
       end if
504

505
       if (write_ascii) then
×
506
          write (unit=out_unit, fmt='(a)') local_header%to_string(file_description="GS2 output file")
×
507
       end if
508

509
       allocate (omegahist(0:navg-1,ntheta0,naky))
×
510
       omegahist = 0.0
×
511
       if (use_nonlin_convergence) call init_nonlinear_convergence(conv_nstep_av, nwrite)
×
512

513
    end if
514

515
    ! Needed to allow us to use common_calculate_fluxes later
516
    call init_diagnostics_fluxes()
×
517

518
    if (write_kinetic_energy_transfer) call init_diagnostics_kinetic_energy_transfer
×
519
    if (.not. allocated(omega)) then
×
520
       allocate(omega(ntheta0, naky))
×
521
       allocate(omegaavg(ntheta0, naky))
×
522
       omega=0
×
523
       omegaavg=0
×
524
    end if
525

526
  end subroutine real_init
×
527

528
  !> Read the input parameters for the diagnostics module
529
  subroutine read_parameters (gs2_diagnostics_config_in, warn_nonfunctional)
×
530
    use diagnostics_configuration, only: warn_about_nonfunctional_selection, diagnostics_config
531
    use run_parameters, only: has_phi
532
    use antenna, only: no_driver
533
    use nonlinear_terms, only: nonlin
534
    use collisions, only: heating, use_le_layout, set_heating
535
    use mp, only: proc0
536
    use optionals, only: get_option_with_default
537
    implicit none
538
    !> Configuration for this module, can be used to set new default values or
539
    !> avoid reading the input file
540
    type(diagnostics_config_type), intent(in), optional :: gs2_diagnostics_config_in
541
    logical, intent(in), optional :: warn_nonfunctional
542
    logical :: write_zonal_transfer, write_upar_over_time, write_tperp_over_time
543
    logical :: write_ntot_over_time, write_density_over_time, write_collisional
544

545
    if (present(gs2_diagnostics_config_in)) diagnostics_config = gs2_diagnostics_config_in
×
546

547
    call diagnostics_config%init(name = 'gs2_diagnostics_knobs', requires_index = .false.)
×
548

549
    ! Print some health warnings if switches are not their default
550
    ! values and are not available in this diagnostics module
551
    if (get_option_with_default(warn_nonfunctional, .true.)) then
×
552
       call warn_about_nonfunctional_selection(.not. diagnostics_config%write_any, "write_any")
×
553
       call warn_about_nonfunctional_selection(diagnostics_config%write_collisional, "write_collisional")
×
554
       call warn_about_nonfunctional_selection(diagnostics_config%write_density_over_time, "write_density_over_time")
×
555
       call warn_about_nonfunctional_selection(diagnostics_config%write_ntot_over_time, "write_ntot_over_time")
×
556
       call warn_about_nonfunctional_selection(diagnostics_config%write_tperp_over_time, "write_tperp_over_time")
×
557
       call warn_about_nonfunctional_selection(diagnostics_config%write_upar_over_time, "write_upar_over_time")
×
558
       call warn_about_nonfunctional_selection(diagnostics_config%write_zonal_transfer, "write_zonal_transfer")
×
559
    end if
560

561
    ! Copy out internal values into module level parameters
562
    associate(self => diagnostics_config)
563
#include "diagnostics_copy_out_auto_gen.inc"
564
    end associate
565

566
    !Override flags
567
    if (write_max_verr) write_verr = .true.
×
568

569
    ! The collision_error method assumes we have setup the lz layout.
570
    if (use_le_layout) write_cerr = .false.
×
571
    if (.not. nonlin) use_nonlin_convergence = .false.
×
572

573
    if (no_driver .and. write_lorentzian) then
×
574
      write(*, "(a)") "WARNING: 'write_lorentzian = .true.' but antenna not enabled. Turning off 'write_lorentzian'"
×
575
      write_lorentzian = .false.
×
576
    end if
577

578
    !These don't store any data if we don't have phi so don't bother
579
    !calculating it.
580
    if(.not. has_phi) write_symmetry = .false.
×
581
    if(.not. has_phi) write_nl_flux_dist = .false.
×
582
    if(.not. has_phi) write_correlation = .false.
×
583
    if(.not. has_phi) write_correlation_extend = .false.
×
584

585
    if (.not. save_for_restart) nsave = -1
×
586

587
    if (write_heating .and. .not. heating) then
×
588
       if (proc0) write(*,'("Warning: Disabling write_heating as collisions:heating is false.")')
×
589
       write_heating = .false.
×
590
    else if (heating .and. .not. write_heating) then
×
591
       call set_heating(.false.)
×
592
    end if
593

594
    write_any = write_line .or. write_omega     .or. write_omavg &
595
         .or. write_flux_line .or. write_fluxes .or. write_fluxes_by_mode  &
596
         .or. write_kpar   .or. write_heating     .or. write_lorentzian  .or. write_gs
×
597
    write_any_fluxes = write_flux_line .or. print_flux_line .or. write_fluxes .or. write_fluxes_by_mode
×
598
  end subroutine read_parameters
×
599

600
  subroutine do_final_gs2_diagnostics
×
601
    use mp, only: proc0
602
    use fields_arrays, only: phinew, bparnew
603
    use antenna, only: dump_ant_amp
604
    use gs2_time, only: user_time
605
    use unit_tests, only: debug_message
606
    use diagnostics_final_routines, only: do_write_final_fields, do_write_kpar
607
    use diagnostics_final_routines, only: do_write_final_epar, do_write_final_db
608
    use diagnostics_final_routines, only: do_write_final_antot, do_write_final_moments
609
    use diagnostics_final_routines, only: do_write_gs
610
    use diagnostics_velocity_space, only: collision_error
611
    use diagnostics_fields, only: get_phi0
612
    implicit none
613

614
    call debug_message(3, 'gs2_diagnostics::final_gs2_diagnostics &
615
         & starting')
×
616

617
    if (write_gyx) call do_write_fyx (yxdist_unit, phinew, bparnew)
×
618
    if (write_g) call do_write_f (dist_unit)
×
619
    if (write_cerr) call collision_error (cres_unit, phinew, bparnew)
×
620

621
    if (proc0) then
×
622
       if (write_eigenfunc) call do_write_eigenfunc(get_netcdf_file_id(), write_ascii)
×
623
       if (write_final_fields) call do_write_final_fields(write_ascii, &
×
624
            file_id=get_netcdf_file_id())
×
625
       if (write_kpar) call do_write_kpar(write_ascii)
×
626
       if (write_final_epar) call do_write_final_epar(write_ascii, &
×
627
            file_id=get_netcdf_file_id())
×
628

629
       ! definition here assumes we are not using wstar_units
630
       if (write_final_db) call do_write_final_db(write_ascii)
×
631
    end if
632

633
    !Note pass in phase factor phi0 which may not be initialised
634
    !this is ok as phi0 will be set in routine if not already set
635
    if (write_final_moments) call do_write_final_moments(get_phi0(), &
×
636
         use_normalisation=write_eigenfunc, write_text=write_ascii, &
637
         file_id=get_netcdf_file_id())
×
638

639
    if (write_final_antot) call do_write_final_antot(write_ascii, &
×
640
         file_id=get_netcdf_file_id())
×
641

642
    call save_restart_dist_fn(save_for_restart, save_distfn, &
643
                              save_glo_info_and_grids=save_glo_info_and_grids, &
644
                              save_velocities=save_velocities, &
645
                              user_time=user_time)
×
646

647
    if (proc0) call dump_ant_amp
×
648

649
    if (write_gs) call do_write_gs(write_ascii)
×
650

651
    if (proc0) call do_write_geom
×
652
  end subroutine do_final_gs2_diagnostics
×
653

654
  !> Finalise the diagnostics module, writing final timestep diagnostics and
655
  !> closing any open files
656
  subroutine finish_gs2_diagnostics
×
657
    use gs2_io, only: nc_finish
658
    use diagnostics_velocity_space, only: finish_legendre_transform, finish_weights
659
    if (.not. initialized) return
×
660
    ! Close some of the open ascii output files
661
    call close_files
×
662
    !Finalise the netcdf file
663
    call nc_finish
×
664
    !Now tidy up
665
    call deallocate_arrays
×
666
    if (write_verr) then
×
667
       call finish_weights
×
668
       call finish_legendre_transform
×
669
    end if
670
    wtmp_old = 0. ; nout = 1 ; nout_movie = 1 ; nout_big = 1
×
671
    initialized = .false.
×
672
  end subroutine finish_gs2_diagnostics
673

674
  !> Save some extra information in final restart files
675
  subroutine save_restart_dist_fn(save_for_restart, save_distfn, &
×
676
                                  save_glo_info_and_grids, &
677
                                  save_velocities, user_time, fileopt_base)
678
    use run_parameters, only: has_phi, has_apar, has_bpar
679
    use collisions, only: vnmult
680
    use gs2_save, only: gs2_save_for_restart
681
    use gs2_time, only: code_dt, code_dt_prev1, code_dt_prev2, code_dt_max
682
    use fields_arrays, only: phinew, bparnew
683
    use dist_fn_arrays, only: gnew, g_adjust, to_g_gs2, from_g_gs2
684
    use optionals, only: get_option_with_default
685
    !> See [[gs2_diagnostics_knobs:save_for_restart]]
686
    logical, intent(in) :: save_for_restart
687
    !> See [[gs2_diagnostics_knobs:save_distfn]]
688
    logical, intent(in) :: save_distfn
689
    !> See [[gs2_diagnostics_knobs:save_glo_info_and_grids]]
690
    logical, intent(in) :: save_glo_info_and_grids
691
    !> See [[gs2_diagnostics_knobs:save_velocities]]
692
    logical, intent(in) :: save_velocities
693
    !> Current simulation time
694
    real, intent(in) :: user_time
695
    !> Optional string to add to file name
696
    character(len=*), intent(in), optional :: fileopt_base
697
    character(len=:), allocatable :: fileopt
×
698

699
    fileopt = get_option_with_default(fileopt_base, "")
×
700

701
    if (save_for_restart) then
×
702
       call gs2_save_for_restart(gnew, user_time, vnmult, &
703
            has_phi, has_apar, has_bpar, &
704
            code_dt, code_dt_prev1, code_dt_prev2, code_dt_max, &
705
            save_glo_info_and_grids=save_glo_info_and_grids, &
706
            save_velocities=save_velocities, &
707
            fileopt = fileopt)
×
708
    end if
709

710
    if (save_distfn) then
×
711
       !Convert h to distribution function
712
       call g_adjust(gnew, phinew, bparnew, direction = from_g_gs2)
×
713

714
       !Save dfn, fields and velocity grids to file
715
       call gs2_save_for_restart(gnew, user_time, vnmult, &
716
            has_phi, has_apar, has_bpar, &
717
            code_dt, code_dt_prev1, code_dt_prev2, code_dt_max, &
718
            fileopt= fileopt//".dfn", &
719
            save_glo_info_and_grids=save_glo_info_and_grids, &
720
            save_velocities=save_velocities)
×
721

722
       !Convert distribution function back to h
723
       call g_adjust(gnew, phinew, bparnew, direction = to_g_gs2)
×
724
    end if
725
  end subroutine save_restart_dist_fn
×
726

727
  !> Deallocate the [[gs2_diagnostics]] module-level arrays
728
  subroutine deallocate_arrays
×
729
    use mp, only: proc0
730
    use gs2_heating, only: del_htype
731
    use diagnostics_fluxes, only: finish_diagnostics_fluxes
732
    use diagnostics_kinetic_energy_transfer, only: finish_diagnostics_kinetic_energy_transfer
733
    use diagnostics_nonlinear_convergence, only: finish_nonlinear_convergence
734
    implicit none
735

736
    if (write_heating) then
×
737
       call del_htype (h)
×
738
       call del_htype (h_hist)
×
739
       call del_htype (hk_hist)
×
740
       call del_htype (hk)
×
741
    end if
742

743
    call finish_diagnostics_fluxes()
×
744
    call finish_diagnostics_kinetic_energy_transfer()
×
745
    if (allocated(h_hist)) deallocate (h_hist, hk_hist, hk)
×
746
    if (allocated(j_ext_hist)) deallocate (j_ext_hist)
×
747
    if (proc0 .and. allocated(omegahist)) deallocate (omegahist)
×
748
    if (allocated(pflux_tormom)) deallocate (pflux_tormom) 
×
749

750
    if (allocated(pflux_avg)) deallocate (pflux_avg, qflux_avg, heat_avg, vflux_avg)
×
751
    if (allocated(omega)) deallocate(omega, omegaavg)
×
752
    if (use_nonlin_convergence) call finish_nonlinear_convergence
×
753

754
    if (proc0 .and. allocated(domega)) deallocate(domega)
×
755
  end subroutine deallocate_arrays
×
756

757
  !> Close various text output files
758
  subroutine close_files
×
759
    use file_utils, only: close_output_file
760
    use mp, only: proc0
761
    implicit none
762

763
    if(.not.proc0) return
×
764
    if (write_ascii .and. write_parity) call close_output_file (parity_unit)
×
765
    if (write_ascii .and. write_verr) then
×
766
       call close_output_file (res_unit)
×
767
       call close_output_file (lpc_unit)
×
768
       if (write_max_verr) call close_output_file (res_unit2)
×
769
    end if
770
    if (write_ascii .and. write_cerr) call close_output_file(cres_unit)
×
771
    if (write_ascii .and. write_g) call close_output_file(dist_unit)
×
772
    if (write_ascii .and. write_gyx) call close_output_file(yxdist_unit)
×
773
    if (write_ascii) call close_output_file (out_unit)
×
774
    if (write_ascii .and. write_cross_phase) call close_output_file (phase_unit)
×
775
    if (write_ascii .and. write_heating) call close_output_file (heat_unit)
×
776
    if (write_ascii .and. write_heating) call close_output_file (heat_unit2)
×
777
    if (write_ascii .and. write_jext) call close_output_file (jext_unit)
×
778
  end subroutine close_files
779

780
  !> Calculate and write the various diagnostic quantities.
781
  !>
782
  !> This is the main routine for the "old" diagnostics.
783
  subroutine loop_diagnostics (istep, exit, debopt, force)
×
784
    use, intrinsic :: iso_fortran_env, only: output_unit
785
    use species, only: nspec, spec, has_electron_species
786
    use kt_grids, only: naky, ntheta0
787
    use run_parameters, only: nstep, has_phi, has_apar, has_bpar
788
    use fields_arrays, only: phinew, bparnew
789
    use collisions, only: ncheck, vary_vnew
790
    use mp, only: proc0, broadcast
791
    use gs2_time, only: user_time
792
    use gs2_io, only: nc_qflux, nc_vflux, nc_pflux, nc_pflux_tormom, nc_exchange, nc_final_fields, nc_sync, get_netcdf_movie_file_id
793
    use antenna, only: antenna_w
794
    use optionals, only: get_option_with_default
795
    use diagnostics_printout, only: write_phi_fluxes_to_unit, write_fluxes_to_unit
796
    use diagnostics_fluxes, only: common_calculate_fluxes, qheat, qmheat, qbheat, &
797
         pflux, vflux, vflux_par, vflux_perp, pflux_tormom, vflux0, vflux1, pmflux, vmflux, &
798
         pbflux, vbflux, exchange
799
    use diagnostics_velocity_space, only: collision_error
800
    use optionals, only: get_option_with_default
801
    use warning_helpers, only: is_not_zero, not_exactly_equal
802
    use volume_averages, only: average_all, average_ky
803
    implicit none
804
    !> Current timestep
805
    integer, intent (in) :: istep
806
    !> If true, simulation should stop (for example, because it has converged)
807
    logical, intent (out) :: exit
808
    !> If true, turn on some debug prints
809
    logical, intent (in), optional:: debopt
810
    logical, intent(in), optional :: force
811
    real, dimension (ntheta0, naky) :: phitot
×
812
    real :: phi2, apar2, bpar2
813
    real :: t
814
    integer :: ik, it, write_mod
815
    complex, save :: wtmp_new !This shouldn't need to be given the save property
816
    real, dimension (ntheta0, nspec) :: x_qmflux
×
817
    real, dimension (nspec) ::  heat_fluxes,  part_fluxes, mom_fluxes, parmom_fluxes, perpmom_fluxes, part_tormom_fluxes
×
818
    real, dimension (nspec) :: mheat_fluxes, mpart_fluxes, mmom_fluxes
×
819
    real, dimension (nspec) :: bheat_fluxes, bpart_fluxes, bmom_fluxes
×
820
    real, dimension (nspec) :: energy_exchange
×
821
    real, dimension (nspec) ::  heat_par,  heat_perp
×
822
    real, dimension (nspec) :: mheat_par, mheat_perp
×
823
    real, dimension (nspec) :: bheat_par, bheat_perp
×
824
    real :: hflux_tot, zflux_tot, vflux_tot
825
    logical :: do_force, debug
826
    real, save :: t_old = 0.
827
    integer, save :: istep_last = -1
828
    debug = get_option_with_default(debopt, .false.)
×
829

830
    !Set the current time
831
    t = user_time
×
832
    !Always skip if we've already done this step
833
    if (istep == istep_last) return
×
834

835
    do_force = get_option_with_default(force, .false.)
×
836

837
    exit = .false.
×
838

839
    call do_get_omega(istep,debug,exit)
×
840

841
    if (write_heating) call heating (istep, navg, h, hk, h_hist, hk_hist)
×
842

843
    if (make_movie .and. mod(istep,nmovie) == 0) call do_write_movie(t)
×
844

845
    if (write_gyx .and. mod(istep,nmovie) == 0) call do_write_fyx (yxdist_unit, phinew, bparnew)
×
846

847
    if (vary_vnew) then
×
848
       write_mod = mod(istep,ncheck)
×
849
    else
850
       write_mod = mod(istep,nwrite)
×
851
    end if
852

853
    if (write_verr .and. write_mod == 0) call do_write_verr
×
854

855
    if (debug) write(6,*) "loop_diagnostics: call update_time"
×
856

857
    !########################################################
858
    !The rest of the routine only happens every nwrite steps
859
    !########################################################
860
    if (mod(istep,nwrite) /= 0 .and. .not. exit .and. .not. do_force) return
×
861

862
    ! If we get here then we're doing a full set of diagnostics
863
    ! so store the step
864
    istep_last = istep
×
865

866
    if (write_g) call do_write_f (dist_unit)
×
867

868
    ! Note this also returns phi2, apar2, bpar2 and phitot for other diagnostics
869
    if (proc0) call do_write_ncloop(t, istep, phi2, apar2, bpar2, phitot)
×
870

871
    if (print_line) call do_print_line(phitot)
×
872

873
    if (write_moments) call do_write_moments
×
874

875
    if (write_cross_phase .and. has_electron_species(spec) .and. write_ascii) call do_write_crossphase(t)
×
876

877
    !###########################
878
    ! The following large section could do with being moved to separate routines but
879
    !     at the moment its all quite interlinked which makes this hard.
880
    !###########################
881

882
    !Zero various arrays which may or may not get filled
883
    part_fluxes = 0.0 ; mpart_fluxes = 0.0 ; bpart_fluxes = 0.0
×
884
    heat_fluxes = 0.0 ; mheat_fluxes = 0.0 ; bheat_fluxes = 0.0
×
885
    mom_fluxes = 0.0 ; mmom_fluxes = 0.0 ; bmom_fluxes = 0.0  
×
886
    part_tormom_fluxes = 0.0
×
887
    energy_exchange = 0.0
×
888

889
    if (debug) write(6,*) "loop_diagnostics: -1"
×
890

891
    if (write_any_fluxes) then
×
892
       call common_calculate_fluxes()
×
893
       if (proc0) then
×
894
          if (has_phi) then
×
895
             call average_all(qheat(:, :, :, 1), heat_fluxes)
×
896
             call average_all(qheat(:, :, :, 2), heat_par)
×
897
             call average_all(qheat(:, :, :, 3), heat_perp)
×
898
             call average_all(pflux, part_fluxes)
×
899
             call average_all(pflux_tormom, part_tormom_fluxes)
×
900
             call average_all(vflux, mom_fluxes)
×
901
             call average_all(vflux_par, parmom_fluxes)
×
902
             call average_all(vflux_perp, perpmom_fluxes)
×
903
             call average_all(exchange, energy_exchange)
×
904
          end if
905
          if (has_apar) then
×
906
             call average_all(qmheat(:, :, :, 1), mheat_fluxes)
×
907
             call average_all(qmheat(:, :, :, 2), mheat_par)
×
908
             call average_all(qmheat(:, :, :, 3), mheat_perp)
×
909
             call average_all(pmflux, mpart_fluxes)
×
910
             call average_all(vmflux, mmom_fluxes)
×
911
             call average_ky(qmheat(:, :, :, 1), x_qmflux)
×
912
          end if
913
          if (has_bpar) then
×
914
             call average_all(qbheat(:, :, :, 1), bheat_fluxes)
×
915
             call average_all(qbheat(:, :, :, 2), bheat_par)
×
916
             call average_all(qbheat(:, :, :, 3), bheat_perp)
×
917
             call average_all(pbflux, bpart_fluxes)
×
918
             call average_all(vbflux, bmom_fluxes)
×
919
          end if
920
          pflux_avg = pflux_avg + (part_fluxes + mpart_fluxes + bpart_fluxes)*(t-t_old)
×
921
          qflux_avg = qflux_avg + (heat_fluxes + mheat_fluxes + bheat_fluxes)*(t-t_old)
×
922
          vflux_avg = vflux_avg + (mom_fluxes + mmom_fluxes + bmom_fluxes)*(t-t_old)
×
923
          if (write_heating) heat_avg = heat_avg + h%imp_colls*(t-t_old)
×
924
          !          t_old = t
925
       end if
926
    end if
927

928
    if (proc0 .and. print_flux_line) then
×
929
      if (has_phi) then
×
930
        call write_phi_fluxes_to_unit(output_unit, t, phi2, heat_fluxes, energy_exchange)
×
931
      end if
932
      if (has_apar) then
×
933
        call write_fluxes_to_unit(output_unit, t, apar2, "apar", mheat_fluxes)
×
934
      end if
935
      if (has_bpar) then
×
936
        call write_fluxes_to_unit(output_unit, t, bpar2, "bpar", bheat_fluxes)
×
937
      end if
938
    end if
939

940
    ! Check for convergence
941
    if (use_nonlin_convergence) call check_nonlin_convergence(istep, heat_fluxes(1), exit)
×
942
    if (debug) write(6,*) "loop_diagnostics: -1"
×
943

944
    if (.not. write_any) then
×
945
       ! We have to increment the number of outputs written to file
946
       ! before leaving. Usually we do this at the end of the routine
947
       ! so we must make sure we do this here before leaving early.
948
       nout = nout + 1
×
949
       return
×
950
    end if
951

952
    if (debug) write(output_unit, *) "loop_diagnostics: -2"
×
953

954
    if (proc0 .and. write_any) then
×
955
       if (write_ascii) then
×
956
         write (unit=out_unit, fmt=*) 'time=', t
×
957
         if (write_heating) call do_write_heating(t, heat_unit, heat_unit2, h)
×
958
         if (write_jext) call do_write_jext(t,istep)
×
959
       end if
960

961
       hflux_tot = 0.
×
962
       zflux_tot = 0.
×
963
       vflux_tot = 0.
×
964
       if (has_phi) then
×
965
         hflux_tot = sum(heat_fluxes)
×
966
         vflux_tot = sum(mom_fluxes)
×
967
         zflux_tot = sum(part_fluxes*spec%z)
×
968
       end if
969
       if (has_apar) then
×
970
         hflux_tot = hflux_tot + sum(mheat_fluxes)
×
971
         vflux_tot = vflux_tot + sum(mmom_fluxes)
×
972
         zflux_tot = zflux_tot + sum(mpart_fluxes*spec%z)
×
973
       end if
974
       if (has_bpar) then
×
975
         hflux_tot = hflux_tot + sum(bheat_fluxes)
×
976
         vflux_tot = vflux_tot + sum(bmom_fluxes)
×
977
         zflux_tot = zflux_tot + sum(bpart_fluxes*spec%z)
×
978
       end if
979

980
       if (write_flux_line .and. write_ascii) then
×
981
         if (has_phi) then
×
982
           call write_phi_fluxes_to_unit(out_unit, t, phi2, &
983
                heat_fluxes, energy_exchange, part_fluxes, mom_fluxes)
×
984
         end if
985
         if (write_lorentzian) then
×
986
           wtmp_new = antenna_w()
×
987
           if (is_not_zero(real(wtmp_old)) .and. not_exactly_equal(wtmp_new, wtmp_old)) &
×
988
                write (unit=out_unit, fmt="('w= ',e17.10, ' amp= ',e17.10)") real(wtmp_new), sqrt(2.*apar2)
×
989
           wtmp_old = wtmp_new
×
990
         end if
991
         if (has_apar) then
×
992
           call write_fluxes_to_unit(out_unit, t, apar2, "apar", mheat_fluxes, mpart_fluxes)
×
993
         end if
994
         if (has_bpar) then
×
995
           call write_fluxes_to_unit(out_unit, t, bpar2, "bpar", bheat_fluxes, bpart_fluxes)
×
996
         end if
997
         write (unit=out_unit, fmt="('t= ',e17.10,' h_tot= ',e11.4, ' z_tot= ',e11.4)") t, hflux_tot, zflux_tot
×
998
       end if
999

1000
       if (write_fluxes) then
×
1001
         call nc_qflux (get_netcdf_file_id(), nout, qheat(:,:,:,1), qmheat(:,:,:,1), qbheat(:,:,:,1), &
×
1002
              heat_par, mheat_par, bheat_par, &
×
1003
              heat_perp, mheat_perp, bheat_perp, &
×
1004
              heat_fluxes, mheat_fluxes, bheat_fluxes, x_qmflux, hflux_tot)
×
1005
         call nc_exchange (get_netcdf_file_id(), nout, exchange, energy_exchange)
×
1006
         call nc_vflux (get_netcdf_file_id(), nout, vflux, vmflux, vbflux, &
1007
              mom_fluxes, mmom_fluxes, bmom_fluxes, vflux_tot, &
×
1008
              vflux_par, vflux_perp, vflux0, vflux1)
×
1009
         call nc_pflux (get_netcdf_file_id(), nout, pflux, pmflux, pbflux, &
1010
              part_fluxes, mpart_fluxes, bpart_fluxes, zflux_tot)
×
1011
       end if
1012

1013
       if (write_ascii) then
×
1014
          do ik = 1, naky
×
1015
             do it = 1, ntheta0
×
1016
                if (write_line) call do_write_line(t,it,ik,phitot(it,ik))
×
1017
                if (write_omega) call do_write_omega(it,ik)
×
1018
                if (write_omavg) call do_write_omavg(it,ik)
×
1019
             end do
1020
          enddo
1021
       end if
1022
    endif
1023

1024
    if (write_cerr) call collision_error(cres_unit, phinew, bparnew)
×
1025

1026
    if (write_nl_flux_dist) call do_write_nl_flux_dist(get_netcdf_file_id(), nout)
×
1027

1028
    if (write_kinetic_energy_transfer) call do_write_kinetic_energy_transfer(get_netcdf_file_id(), nout)
×
1029

1030
    if (write_symmetry) call do_write_symmetry(get_netcdf_file_id(), nout)
×
1031

1032
    if (write_correlation) call do_write_correlation(get_netcdf_file_id(), nout)
×
1033

1034
    if (write_correlation_extend .and. istep > nstep/4 .and. mod(istep,nwrite_mult*nwrite)==0) &
×
1035
         call do_write_correlation_extend(get_netcdf_file_id(), t, t_old)
×
1036

1037
    if (write_parity) call do_write_parity(t, parity_unit, write_ascii)
×
1038

1039
    if (write_avg_moments) call do_write_avg_moments
×
1040

1041
    !Now sync the data to file (note doesn't actually sync every call)
1042
    if (proc0) call nc_sync(get_netcdf_file_id(), nout, get_netcdf_movie_file_id(), nout_movie, nc_sync_freq)
×
1043

1044
    !Increment loop counter
1045
    nout = nout + 1
×
1046

1047
    if (write_ascii .and. mod(nout, 10) == 0 .and. proc0) call flush_files
×
1048

1049
    !Update time
1050
    t_old = t
×
1051

1052
    if (debug) write(6,*) "loop_diagnostics: done"
×
1053
  end subroutine loop_diagnostics
1054

1055
  !> Calculate [[gs2_diagnostics_knobs:omegaavg]] for linear simulations or if
1056
  !> [[run_parameters_knobs:eqzip]] is on; otherwise set
1057
  !> [[gs2_diagnostics_knobs:omega]] and [[gs2_diagnostics_knobs:omegaavg]] to
1058
  !> zero
1059
  subroutine do_get_omega(istep,debug,exit)
×
1060
    use mp, only: proc0, broadcast
1061
    use nonlinear_terms, only: nonlin
1062
    use run_parameters, only: ieqzip
1063
    implicit none
1064
    !> The current timestep
1065
    integer, intent(in) :: istep
1066
    !> Turn on some debug messages
1067
    logical, intent(in) :: debug
1068
    !> Returns true if the simulation has converged (see
1069
    !> [[gs2_diagnostics_knobs:omegatol]]) or if a numerical instability has
1070
    !> occurred (see [[gs2_diagnostics_knobs:omegainst]]).
1071
    logical, intent(inout) :: exit
1072

1073
    if (nonlin .and. .not. any(ieqzip)) then
×
1074
       !Make sure we've at least initialised the omega arrays
1075
       !for any later output etc.
1076
       omega = 0.
×
1077
       omegaavg = 0.
×
1078
    else
1079
       if (proc0) then
×
1080
          if (debug) write(6,*) "loop_diagnostics: proc0 call get_omegaavg"
×
1081
          call get_omegaavg (istep, exit, omegaavg, debug)
×
1082
          if (debug) write(6,*) "loop_diagnostics: proc0 done called get_omegaavg"
×
1083
       endif
1084
       call broadcast (exit)
×
1085
    end if
1086

1087
  end subroutine do_get_omega
×
1088

1089
  !> Compute volume averages of the fields and write the fields, field averages,
1090
  !> heating and frequency to the netCDF files
1091
  subroutine do_write_ncloop(time, istep, phi2, apar2, bpar2, phitot)
×
1092
    use gs2_time, only: woutunits, tunits
1093
    use gs2_io, only: nc_loop
1094
    use mp, only: proc0
1095
    use kt_grids, only: ntheta0, naky
1096
    implicit none
1097
    !> Simulation time
1098
    real, intent(in) :: time
1099
    !> Current timestep
1100
    integer, intent(in) :: istep
1101
    !> Fields squared
1102
    real, intent(out) :: phi2, apar2, bpar2
1103
    !> FIXME: add documentation. Needs [[phinorm]] documenting
1104
    real, dimension (:, :), intent(out) :: phitot
1105
    real, dimension (ntheta0, naky) :: ql_metric, growth_rates
×
1106
    phitot = 0.0
×
1107
    if (.not. proc0) return
×
1108

1109
    omega = omegahist(mod(istep,navg),:,:)
×
1110

1111
    call phinorm (phitot)
×
1112

1113
    if (write_ql_metric) then
×
1114
       ! Calculate the instantaneous omega and keep the growth rate.
1115
       growth_rates = aimag(calculate_instantaneous_omega())
×
1116
       ql_metric = calculate_simple_quasilinear_flux_metric_by_k(growth_rates)
×
1117
    else
1118
       ql_metric = 0.0
×
1119
    end if
1120

1121
    call nc_loop (get_netcdf_file_id(), nout, time, &
1122
         phi2, apar2, bpar2, igomega, &
1123
         h, hk, omega, omegaavg, woutunits, tunits, phitot, ql_metric, &
×
1124
         write_omega, write_heating, write_ql_metric)
×
1125
  end subroutine do_write_ncloop
1126

1127
  !> Write \(\phi, A_\parallel, B_\parallel\) normalised to the value of
1128
  !> \(\phi\) at the outboard midplane
1129
  !>
1130
  !> Writes to text file `<runname>.eigenfunc` and/or netCDF
1131
  subroutine do_write_eigenfunc(file_id, write_text)
×
1132
    use mp, only: proc0
1133
    use file_utils, only: open_output_file, close_output_file
1134
    ! This renaming seems needed to avoid an issue with ifx
1135
    use diagnostics_fields, only: write_eigenfunc_ => write_eigenfunc
1136
    implicit none
1137
    !> NetCDF ID of the file to write to
1138
    integer, intent(in) :: file_id
1139
    !> If true, write text file
1140
    logical, intent(in) :: write_text
1141
    integer :: unit
1142
    if (.not. proc0) return
×
1143
    if (write_text) call open_output_file (unit, ".eigenfunc")
×
1144
    call write_eigenfunc_(write_text, unit, file_id)
×
1145
    if (write_text) close(unit)
×
1146
  end subroutine do_write_eigenfunc
1147

1148
  !> Write some geometry information to text file `<runname>.g`
1149
  subroutine do_write_geom
×
1150
    use mp, only: proc0
1151
    use file_utils, only: open_output_file, close_output_file
1152
    use theta_grid, only: ntgrid, theta, Rplot, Zplot, aplot, Rprime, Zprime, aprime, drhodpsi, qval, shape
1153
    implicit none
1154
    integer :: i, unit
1155

1156
    if(.not.proc0) return
×
1157

1158
    !May want to guard this with if(write_ascii) but not until we provide this
1159
    !data in main netcdf output by default.
1160
    call open_output_file (unit, ".g")
×
1161
    write (unit,fmt="('# shape: ',a)") trim(shape)
×
1162
    write (unit,fmt="('# q = ',e11.4,' drhodpsi = ',e11.4)") qval, drhodpsi
×
1163
    write (unit,fmt="('# theta1             R2                  Z3               alpha4      ', &
1164
         &   '       Rprime5              Zprime6           alpha_prime7 ')")
×
1165
    do i=-ntgrid,ntgrid
×
1166
       write (unit,1000) theta(i),Rplot(i),Zplot(i),aplot(i), &
×
1167
            Rprime(i),Zprime(i),aprime(i)
×
1168
    enddo
1169
    call close_output_file (unit)
×
1170
1000 format(20(1x,1pg18.11))
1171
  end subroutine do_write_geom
1172

1173
  !> Transform \(\phi, A_\parallel, B_\parallel\) to real space, then write to netCDF
1174
  subroutine do_write_movie(time)
×
1175
    use gs2_io, only: nc_loop_movie, get_netcdf_movie_file_id
1176
    use mp, only: proc0
1177
    implicit none
1178
    !> Current simulation time
1179
    real, intent(in) :: time
1180
    if (proc0) call nc_loop_movie(get_netcdf_movie_file_id(), nout_movie, time)
×
1181
    nout_movie = nout_movie + 1
×
1182
  end subroutine do_write_movie
×
1183

1184
  !> Print estimated frequencies and growth rates to screen/stdout
1185
  subroutine do_print_line(phitot)
×
1186
    use mp, only: proc0
1187
    use kt_grids, only: naky, ntheta0, aky, akx, theta0
1188
    use gs2_time, only: woutunits
1189
    implicit none
1190
    !> Total magnitude of all the fields
1191
    real, dimension (:, :), intent(in) :: phitot
1192
    integer :: ik, it
1193

1194
    if(.not.proc0) return
×
1195
    do ik = 1, naky
×
1196
       do it = 1, ntheta0
×
1197
          write (unit=*, fmt="('ky=',1pe9.2, ' kx=',1pe9.2, &
1198
               & ' om=',e9.2,1x,e9.2,' omav=',e9.2,1x,e9.2, &
1199
               & ' phtot=',e9.2,' theta0=',1pe9.2)") &
×
1200
               aky(ik), akx(it), &
×
1201
               real( omega(it,ik)*woutunits(ik)), &
×
1202
               aimag(omega(it,ik)*woutunits(ik)), &
×
1203
               real( omegaavg(it,ik)*woutunits(ik)), &
×
1204
               aimag(omegaavg(it,ik)*woutunits(ik)), &
×
1205
               phitot(it,ik), theta0(it,ik)
×
1206
       end do
1207
    end do
1208
    write (*,*) 
×
1209
  end subroutine do_print_line
1210

1211
  !> Calculate and write the time-averaged antenna current to [[jext_unit]]
1212
  subroutine do_write_jext(time, istep)
×
1213
    use kt_grids, only: ntheta0, naky
1214
    use mp, only: proc0
1215
    use warning_helpers, only: is_not_zero
1216
    implicit none
1217
    !> Current simulation time
1218
    real, intent(in) :: time
1219
    !> Current timestep
1220
    integer, intent(in) :: istep
1221
    integer :: ik, it
1222
    real, dimension(:,:), allocatable ::  j_ext
×
1223

1224
    if (.not.proc0) return
×
1225
    if (.not. write_ascii) return
×
1226
    allocate (j_ext(ntheta0, naky)); j_ext=0.
×
1227
    call calc_jext(istep, j_ext)
×
1228
    do ik=1,naky
×
1229
       do it = 1, ntheta0
×
1230
          if (is_not_zero(j_ext(it, ik))) then
×
1231
             write (unit=jext_unit, fmt="(es12.4,i4,i4,es12.4)")  &
1232
                  time,it,ik,j_ext(it,ik)
×
1233
          endif
1234
       enddo
1235
    enddo
1236
    deallocate(j_ext)
×
1237
  end subroutine do_write_jext
×
1238

1239
  !> Write various moments to netCDF
1240
  subroutine do_write_moments
×
1241
    use gs2_io, only: nc_write_moments
1242
    use theta_grid, only: ntgrid
1243
    use kt_grids, only: naky, ntheta0
1244
    use species, only: nspec
1245
    use diagnostics_moments, only: getmoms
1246
    use mp, only: proc0
1247
    use fields_arrays, only: phinew, bparnew
1248
    implicit none
1249
    complex, dimension (-ntgrid:ntgrid,ntheta0,naky,nspec) :: ntot, density, &
×
1250
         upar, tpar, tperp, pperpperp, qparflux, qpperpj1
×
1251

1252
    call getmoms (phinew, bparnew, ntot, density, upar, tpar, tperp, pperpperp, qparflux, qpperpj1)
×
1253
    if(proc0) call nc_write_moments(get_netcdf_file_id(), nout, ntot, density, upar, tpar, tperp, pperpperp, &
×
1254
         qparflux, qpperpj1, ob_midplane=ob_midplane)
×
1255
  end subroutine do_write_moments
×
1256

1257
  !> Calculate the cross-phase (see [[get_cross_phase]]) and write to the
1258
  !> [[phase_unit]] file
1259
  subroutine do_write_crossphase(time)
×
1260
    use mp, only: proc0
1261
    use diagnostics_turbulence, only: get_cross_phase
1262
    implicit none
1263
    !> Current simulation time
1264
    real, intent(in) :: time
1265
    real :: phase_tot, phase_theta
1266
    if (.not. write_ascii) return
×
1267
    call get_cross_phase (phase_tot, phase_theta)
×
1268
    if (proc0) write (unit=phase_unit, fmt="('t= ',e17.10,' phase_tot= ',e11.4,' phase_theta= ',e11.4)") &
×
1269
         & time, phase_tot, phase_theta
×
1270
  end subroutine do_write_crossphase
1271

1272
  !> Write estimated frequency and growth rates to [[out_unit]] for an individual \((k_y, \theta)\) point
1273
  subroutine do_write_line(time,it,ik,phitot)
×
1274
    use kt_grids, only: aky, akx, theta0
1275
    use gs2_time, only: woutunits
1276
    implicit none
1277
    !> Simulation time
1278
    real, intent(in) :: time, phitot
1279
    !> \(k_y\)- and \(\theta\)-indices
1280
    integer, intent(in) :: ik, it
1281
    if (.not. write_ascii) return
×
1282
    write (out_unit, "('t= ',e17.10,' aky= ',1p,e12.4, ' akx= ',1p,e12.4, &
1283
         &' om= ',1p,2e12.4,' omav= ', 1p,2e12.4,' phtot= ',1p,e12.4,' theta0= ',1p,e12.4)") &
1284
         time, aky(ik), akx(it), &
×
1285
         real( omega(it,ik)*woutunits(ik)), &
×
1286
         aimag(omega(it,ik)*woutunits(ik)), &
×
1287
         real( omegaavg(it,ik)*woutunits(ik)), &
×
1288
         aimag(omegaavg(it,ik)*woutunits(ik)), &
×
1289
         phitot,theta0(it,ik)
×
1290
  end subroutine do_write_line
1291

1292
  !> Write instantaneous growth rate and frequency to [[out_unit]] for an individual \((k_y, \theta)\) point
1293
  subroutine do_write_omega(it,ik)
×
1294
    use gs2_time, only: tunits, woutunits
1295
    implicit none
1296
    !> \(k_y\)- and \(\theta\)-indices
1297
    integer, intent(in) :: it, ik
1298
    if (.not. write_ascii) return
×
1299
    write (out_unit,&
1300
         fmt='(" omega= (",1p,e12.4,",",1p,e12.4,")",t45,"omega/(vt/a)= (",1p,e12.4,",",1p,e12.4,")")') &
1301
         omega(it,ik)/tunits(ik), omega(it,ik)*woutunits(ik)
×
1302
  end subroutine do_write_omega
1303

1304
  !> Write time-averaged growth rate and frequency to [[out_unit]] for an individual \((k_y, \theta)\) point
1305
  subroutine do_write_omavg(it,ik)
×
1306
    use gs2_time, only: tunits, woutunits
1307
    implicit none
1308
    integer, intent(in) :: it, ik
1309
    if (.not. write_ascii) return
×
1310
    write (out_unit,&
1311
         fmt='(" omavg= (",1p,e12.4,",",1p,e12.4,")",t45,"omavg/(vt/a)= (",1p,e12.4,",",1p,e12.4,")")') &
1312
         omegaavg(it,ik)/tunits(ik), omegaavg(it,ik)*woutunits(ik)               
×
1313
  end subroutine do_write_omavg
1314

1315
  !> Write some error estimates.
1316
  !>
1317
  !> Error estimates are calculated by:
1318
  !> - comparing standard integral with less-accurate integral
1319
  !> - monitoring amplitudes of legendre polynomial coefficients
1320
  !>
1321
  !> Only writes to text file, requires [[lpc_unit]] to be `open`
1322
  subroutine do_write_verr
×
1323
    use mp, only: proc0
1324
    use le_grids, only: grid_has_trapped_particles
1325
    use fields_arrays, only: phinew, bparnew
1326
    use gs2_time, only: user_time
1327
    use collisions, only: vnmult
1328
    use species, only: spec
1329
    use diagnostics_velocity_space, only: get_verr, get_gtran
1330
    implicit none
1331
    real, dimension(5,2) :: errest
1332
    integer, dimension (5,3) :: erridx
1333
    real :: geavg, glavg, gtavg
1334

1335
    errest = 0.0; erridx = 0
×
1336

1337
    ! error estimate obtained by comparing standard integral with less-accurate integral
1338
    call get_verr (errest, erridx, phinew, bparnew)
×
1339

1340
    ! error estimate based on monitoring amplitudes of legendre polynomial coefficients
1341
    call get_gtran (geavg, glavg, gtavg, phinew, bparnew)
×
1342

1343
    if (proc0) then
×
1344
       ! write error estimates to .nc file          
1345
       !          call nc_loop_vres (nout, errest_by_mode, lpcoef_by_mode)
1346

1347
       ! write error estimates for ion dist. fn. at outboard midplane with ik=it=1 to ascii files
1348
       if (write_ascii) then
×
1349
          if (grid_has_trapped_particles()) then
×
1350
             write(lpc_unit,"(4(1x,e13.6))") user_time, geavg, glavg, gtavg
×
1351
          else
1352
             write(lpc_unit,"(3(1x,e13.6))") user_time, geavg, glavg
×
1353
          end if
1354
          write(res_unit,"(8(1x,e13.6))") user_time, errest(1,2), errest(2,2), errest(3,2), &
×
1355
               errest(4,2), errest(5,2), vnmult(1)*spec(1)%vnewk, vnmult(2)*spec(1)%vnewk
×
1356
          if (write_max_verr) then
×
1357
             write(res_unit2,"(3(i8),(1x,e13.6),3(i8),(1x,e13.6),3(i8),(1x,e13.6),3(i8),(1x,e13.6),3(i8),(1x,e13.6))") &
1358
                  erridx(1,1), erridx(1,2), erridx(1,3), errest(1,1), &
×
1359
                  erridx(2,1), erridx(2,2), erridx(2,3), errest(2,1), &
×
1360
                  erridx(3,1), erridx(3,2), erridx(3,3), errest(3,1), &
×
1361
                  erridx(4,1), erridx(4,2), erridx(4,3), errest(4,1), &
×
1362
                  erridx(5,1), erridx(5,2), erridx(5,3), errest(5,1)
×
1363
          end if
1364
       end if
1365
    end if
1366
  end subroutine do_write_verr
×
1367

1368
  !> Write the (total) heating diagnostics to [[heat_unit]] and [[heat_unit2]] (per-species)
1369
  subroutine do_write_heating(t, file_unit, file_unit2, h)
×
1370
    use species, only: nspec
1371
    implicit none
1372
    real, intent(in) :: t
1373
    integer, intent(in) :: file_unit, file_unit2
1374
    !> Heating diagnostics
1375
    type(heating_diagnostics), intent (in) :: h
1376

1377
    integer :: is
1378

1379
    !
1380
    ! For case with two species:
1381
    !
1382
    ! Column     Item               
1383
    !   1        time              
1384
    !   2        Energy              
1385
    !   3        dEnergy/dt            
1386
    !   4        J_ant.E             
1387
    !   5        [h_(i+1)*h_*]/2 * C[h_(i+1)] * T_0 for species 1
1388
    !   6        [h_(i+1)*h_*]/2 * C[h_(i+1)] * T_0 for species 2
1389
    !   7       -[h H(h) * T_0]_1
1390
    !   8       -[h H(h) * T_0]_2
1391
    !   9       -[h C(h) * T_0]_1 
1392
    !  10       -[h C(h) * T_0]_2
1393
    !  11        [h w_* h]_1
1394
    !  12        [h w_* h]_2
1395
    !  13        [h * (q dchi/dt - dh/dt * T0)]_1
1396
    !  14        [h * (q dchi/dt - dh/dt * T0)]_2
1397
    !  15      sum (h C(h) * T_0)  in total, as in 5, 6      
1398
    !  16     -sum (h H(h) * T_0)      
1399
    !  17     -sum (h C(h) * T_0)   
1400
    !  18      sum (h w_* h)  
1401
    !  19      sum [h (q dchi/dt - dh/dt * T0)]
1402
    !  20      3 + 4 + 18 + 19
1403
    !  21      (k_perp A)**2
1404
    !  22      B_par**2
1405
    !  23      df_1 ** 2
1406
    !  24      df_2 ** 2
1407
    !  25      h_1 ** 2
1408
    !  26      h_2 ** 2
1409
    !  27      Phi_bar_1 ** 2
1410
    !  28      Phi_bar_2 ** 2
1411
    !
1412
    !
1413
    ! For case with one species:
1414
    !
1415
    ! Column     Item               
1416
    !   1        time              
1417
    !   2        Energy              
1418
    !   3        dEnergy/dt            
1419
    !   4        J_ant.E             
1420
    !   5        [h_(i+1)*h_*]/2 * C[h_(i+1)] * T_0 
1421
    !   6       -[h H(h) * T_0]
1422
    !   7       -[h C(h) * T_0]
1423
    !   8        [h w_* h]
1424
    !   9        [h * (q dchi/dt - dh/dt * T0)]_1
1425
    !  10      sum (h C(h) * T_0)  in total, as in 5, 6      
1426
    !  11     -sum (h H(h) * T_0)      
1427
    !  12     -sum (h C(h) * T_0)   
1428
    !  13      sum (h w_* h)  
1429
    !  14      sum [h (q dchi/dt - dh/dt * T0)]
1430
    !  15      3 + 4 + 9 + 10
1431
    !  16      (k_perp A)**2
1432
    !  17      B_par**2
1433
    !  18      df ** 2
1434
    !  19      h ** 2
1435
    !  20      Phi_bar ** 2
1436
    
1437
    write (unit=file_unit, fmt="(28es12.4)") t,h % energy,  &
×
1438
         h % energy_dot, h % antenna, h % imp_colls, h % hypercoll, h % collisions, &
×
1439
         h % gradients, h % heating, sum(h % imp_colls), sum(h % hypercoll), sum(h % collisions), &
×
1440
         sum(h % gradients), sum(h % heating),sum(h%heating)+h%antenna+sum(h%gradients)+h%energy_dot, &
×
1441
         h % eapar, h % ebpar, h % delfs2(:),  h % hs2(:), h % phis2(:)
×
1442

1443
    do is=1,nspec
×
1444
      write (unit=file_unit2, fmt="(15es12.4)") t,h % energy,  &
×
1445
           h % energy_dot, h % antenna, h % imp_colls(is), h % hypercoll(is), h % collisions(is), &
×
1446
           h % gradients(is), h % heating(is), &
×
1447
           h % eapar, h % ebpar, h % delfs2(is),  h % hs2(is), h % phis2(is), real(is)
×
1448
      write (unit=file_unit2, fmt=*)
×
1449
    end do
1450
    write (unit=file_unit2, fmt=*)
×
1451

1452
    flush (file_unit)
×
1453
    flush (file_unit2)
×
1454
  end subroutine do_write_heating
×
1455

1456
  !> Calculate the momentum flux as a function of \((v_\parallel, \theta, t)\)
1457
  !> and write to netCDF
1458
  subroutine do_write_symmetry(file_id, nout)
×
1459
    use diagnostics_fluxes, only: flux_vs_theta_vs_vpa
1460
    use theta_grid, only: ntgrid
1461
    use le_grids, only: nlambda, negrid
1462
    use species, only: nspec
1463
    use mp, only: proc0
1464
    use gs2_io, only: nc_loop_sym
1465
    use fields_arrays, only: phinew
1466
    implicit none
1467
    !> NetCDF ID of the file to write to
1468
    integer, intent(in) :: file_id
1469
    !> Current timestep
1470
    integer, intent(in) :: nout
1471

1472
    real, dimension(:,:,:), allocatable :: vflx_sym
×
1473
    allocate (vflx_sym(-ntgrid:ntgrid,nlambda*negrid,nspec))
×
1474
    call flux_vs_theta_vs_vpa (phinew, vflx_sym)
×
1475
    if (proc0) call nc_loop_sym (file_id, nout, vflx_sym)
×
1476
    deallocate (vflx_sym)
×
1477
  end subroutine do_write_symmetry
×
1478

1479
  subroutine do_write_kinetic_energy_transfer(file_id, nout)
×
1480
    use diagnostics_kinetic_energy_transfer, only: calculate_kinetic_energy_transfer, write_kinetic_energy_transfer
1481
    use mp, only: proc0
1482
    !> NetCDF ID of the file to write to
1483
    integer, intent(in) :: file_id
1484
    !> Current timestep
1485
    integer, intent(in) :: nout
1486
    call calculate_kinetic_energy_transfer
×
1487
    if (proc0) call write_kinetic_energy_transfer(file_id, nout)
×
1488
  end subroutine do_write_kinetic_energy_transfer
×
1489

1490
  !> Calculate the poloidal distributions of the fluxes of particles, parallel
1491
  !> momentum, perpendicular momentum, and energy (see section 3.1 and appendix
1492
  !> A of [Ball et al. PPCF 58 (2016)
1493
  !> 045023](https://doi.org/10.1088/0741-3335/58/4/045023) as well as section 5
1494
  !> of "GS2 analytic geometry specification")
1495
  subroutine do_write_nl_flux_dist(file_id, nout)
×
1496
    use diagnostics_fluxes, only: flux_dist
1497
    use theta_grid, only: ntgrid
1498
    use species, only: nspec, spec
1499
    use mp, only: proc0
1500
    use gs2_io, only: nc_loop_dist
1501
    use kt_grids, only: naky, ntheta0
1502
    use fields_arrays, only: phinew, bparnew
1503
    use run_parameters, only: has_phi
1504
    implicit none
1505
    !> NetCDF ID of the file to write to
1506
    integer, intent(in) :: file_id
1507
    !> Current timestep
1508
    integer, intent(in) :: nout
1509

1510
    real, dimension (:,:), allocatable :: part_fluxes_dist, mom_fluxes_par_dist
×
1511
    real, dimension (:,:), allocatable :: phi_dist, mom_fluxes_perp_dist, heat_fluxes_dist
×
1512
    real, dimension (:,:,:,:), allocatable :: pflux_dist, vflux_par_dist, vflux_perp_dist, qflux_dist
×
1513
    integer :: ig, is
1514
    if (.not. has_phi) return
×
1515

1516
    allocate (pflux_dist(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1517
    allocate (vflux_par_dist(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1518
    allocate (vflux_perp_dist(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1519
    allocate (qflux_dist(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1520

1521
    call flux_dist (phinew, bparnew, pflux_dist, vflux_par_dist, vflux_perp_dist, qflux_dist)
×
1522

1523
    if (proc0) then
×
1524
       allocate (part_fluxes_dist(-ntgrid:ntgrid,nspec))
×
1525
       allocate (mom_fluxes_par_dist(-ntgrid:ntgrid,nspec))
×
1526
       allocate (mom_fluxes_perp_dist(-ntgrid:ntgrid,nspec))
×
1527
       allocate (heat_fluxes_dist(-ntgrid:ntgrid,nspec))
×
1528
       allocate (phi_dist(2,-ntgrid:ntgrid))
×
1529
       do is = 1, nspec
×
1530
          do ig = -ntgrid, ntgrid
×
1531
             call get_volume_average (pflux_dist(ig,:,:,is), part_fluxes_dist(ig,is))
×
1532
             call get_volume_average (vflux_par_dist(ig,:,:,is), mom_fluxes_par_dist(ig,is))
×
1533
             call get_volume_average (vflux_perp_dist(ig,:,:,is), mom_fluxes_perp_dist(ig,is))
×
1534
             call get_volume_average (qflux_dist(ig,:,:,is), heat_fluxes_dist(ig,is))
×
1535
          end do
1536

1537
          part_fluxes_dist(:, is) = part_fluxes_dist(:, is) * spec(is)%dens
×
1538
          mom_fluxes_par_dist(:, is) = mom_fluxes_par_dist(:, is) * spec(is)%dens * sqrt(spec(is)%mass * spec(is)%temp)             
×
1539
          mom_fluxes_perp_dist(:, is) = mom_fluxes_perp_dist(:, is) * spec(is)%dens * sqrt(spec(is)%mass * spec(is)%temp)
×
1540
          heat_fluxes_dist(:, is) = heat_fluxes_dist(:, is) * spec(is)%dens * spec(is)%temp
×
1541
       end do
1542

1543
       do ig = -ntgrid, ntgrid
×
1544
          call get_volume_average (real(phinew(ig,:,:)), phi_dist(1,ig))
×
1545
          call get_volume_average (aimag(phinew(ig,:,:)), phi_dist(2,ig))
×
1546
       end do
1547

1548
       call nc_loop_dist (file_id, nout, part_fluxes_dist, mom_fluxes_par_dist, &
1549
            mom_fluxes_perp_dist, heat_fluxes_dist, phi_dist)
×
1550

1551
       deallocate (part_fluxes_dist, mom_fluxes_par_dist, mom_fluxes_perp_dist)
×
1552
       deallocate (heat_fluxes_dist, phi_dist)
×
1553
     end if
1554
    deallocate (pflux_dist, vflux_par_dist, vflux_perp_dist, qflux_dist)
×
1555
   end subroutine do_write_nl_flux_dist
×
1556

1557
  !> Calculate the correlation function over the physical domain and write to netCDF
1558
  subroutine do_write_correlation(file_id, nout)
×
1559
    use theta_grid, only: ntgrid
1560
    use kt_grids, only: naky
1561
    use mp, only: proc0
1562
    use gs2_io, only: nc_loop_corr
1563
    implicit none
1564
    !> NetCDF ID of the file to write to
1565
    integer, intent(in) :: file_id
1566
    !> Current timestep
1567
    integer, intent(in) :: nout
1568
    complex, dimension(:,:), allocatable :: phi_corr_2pi
×
1569
    allocate (phi_corr_2pi(-ntgrid:ntgrid,naky))
×
1570
    call correlation (phi_corr_2pi)
×
1571
    if (proc0) call nc_loop_corr (file_id, nout, phi_corr_2pi)
×
1572
    deallocate (phi_corr_2pi)
×
1573
  end subroutine do_write_correlation
×
1574

1575
  !> Calculate the correlation function over the extended domain and write to netCDF
1576
  !>
1577
  !> This does the calculation every time it is called, but only writes every
1578
  !> `nwrite_mult * nwrite` timesteps
1579
  subroutine do_write_correlation_extend(file_id, time, time_old)
×
1580
    use theta_grid, only: ntgrid
1581
    use kt_grids, only: jtwist, ntheta0, naky
1582
    use mp, only: proc0
1583
    use gs2_io, only: nc_loop_corr_extend
1584
    implicit none
1585
    !> NetCDF ID of the file to write to
1586
    integer, intent(in) :: file_id
1587
    !> Current and previous simulation times
1588
    real, intent(in) :: time, time_old
1589
    complex, dimension (:,:,:), allocatable, save:: phicorr_sum
1590
    real, dimension (:,:,:), allocatable, save :: phiextend_sum
1591
    complex, dimension (:,:,:), allocatable :: phi_corr
×
1592
    real, dimension (:,:,:), allocatable :: phi2_extend
×
1593
    real, save :: tcorr0 = 0.0
1594
    integer :: ntg_extend
1595
    if (.not. proc0) return
×
1596
    ntg_extend = (2*ntgrid+1) * ((ntheta0-1) / jtwist + 1)
×
1597

1598
    if (.not. allocated(phicorr_sum)) then
×
1599
       ! Warning: For ntheta=ntheta0=naky=128 and jtwist = 6 these two arrays
1600
       ! will require 750 MB and 375 MB respectively and they are not freed
1601
       ! after leaving the routine.
1602
       allocate (phicorr_sum(ntg_extend,ntheta0,naky)) ; phicorr_sum = 0.0
×
1603
       allocate (phiextend_sum(ntg_extend,ntheta0,naky)) ; phiextend_sum = 0.0
×
1604
       tcorr0 = time_old
×
1605
    end if
1606

1607
    allocate (phi_corr(ntg_extend,ntheta0,naky))
×
1608
    allocate (phi2_extend(ntg_extend,ntheta0,naky))
×
1609
    call correlation_extend (phi_corr, phi2_extend, ntg_extend)
×
1610
    phicorr_sum = phicorr_sum + phi_corr*(time-time_old)
×
1611
    phiextend_sum = phiextend_sum + phi2_extend*(time-time_old)
×
1612
    call nc_loop_corr_extend (file_id, nout_big, time, phicorr_sum/(time-tcorr0), &
×
1613
         phiextend_sum/(time-tcorr0))
×
1614
    nout_big = nout_big + 1
×
1615
    deallocate (phi_corr, phi2_extend)
×
1616
  end subroutine do_write_correlation_extend
×
1617

1618
  !> Calculate average parity of distribution function under \((\theta, k_x,
1619
  !> v_\parallel) \to (-\theta, -k_x, -v_\parallel)\), and write to [[parity_unit]]
1620
  subroutine do_write_parity(t, file_unit, write_text)
×
1621
    use theta_grid, only: ntgrid, field_line_average
×
1622
    use kt_grids, only: naky, ntheta0
1623
    use le_grids, only: negrid, nlambda, integrate_moment, integrate_kysum
1624
    use species, only: nspec
1625
    use gs2_layouts, only: init_parity_layouts, p_lo, g_lo, idx_local
1626
    use gs2_layouts, only: ik_idx, it_idx, il_idx, ie_idx, is_idx, idx, proc_id
1627
    use mp, only: send, receive, proc0, iproc, nproc
1628
    use dist_fn_arrays, only: gnew, g_adjust, aj0, to_g_gs2, from_g_gs2
1629
    use fields_arrays, only: phinew, bparnew
1630
    use constants, only: zi
1631
    implicit none
1632
    real, intent(in) :: t
1633
    !> Open formatted file to write text to
1634
    integer, intent(in) :: file_unit
1635
    !> If false, don't calculate or write parity
1636
    logical, intent(in) :: write_text
1637
    integer :: iplo, iglo, sgn2, isgn, il, ie, ig, ik, it, is, it_source
1638
    complex, dimension (:,:,:,:), allocatable :: gparity, gmx, gpx
×
1639
    complex, dimension (:,:,:), allocatable :: g0, gm, gp
×
1640
    complex, dimension (:,:,:), allocatable :: g_kint, gm_kint, gp_kint
×
1641
    complex, dimension (:,:), allocatable :: g_avg, gnorm_avg, phim
×
1642
    complex, dimension (:), allocatable :: g_all_tot, g_nokx_tot, g_nosig_tot, gtmp
×
1643
    complex, dimension (:), allocatable :: gnorm_all_tot, gnorm_nokx_tot, gnorm_nosig_tot
×
1644
    real, dimension (:,:,:), allocatable :: gmnorm, gmint, gpint, gmnormint, gmavg, gpavg, gmnormavg
×
1645
    real, dimension (:), allocatable :: gmtot, gptot, gtot, gmnormtot
×
1646
    real, dimension (:), allocatable :: gm_nokx_tot, gp_nokx_tot, gmnorm_nokx_tot
×
1647
    real, dimension (:), allocatable :: gm_nosig_tot, gp_nosig_tot, gmnorm_nosig_tot
×
1648

1649
    if (.not. write_text) return
×
1650

1651
    ! initialize layouts for parity diagnostic. Only does work on the first call
1652
    call init_parity_layouts (naky, nlambda, negrid, nspec, nproc, iproc)
×
1653

1654
    allocate (gparity(-ntgrid:ntgrid,ntheta0,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1655
    allocate (g0(-ntgrid:ntgrid,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1656
    allocate (gm(-ntgrid:ntgrid,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1657
    allocate (gp(-ntgrid:ntgrid,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1658
    allocate (gmnorm(-ntgrid:ntgrid,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1659
    allocate (gmint(-ntgrid:ntgrid,naky,nspec))
×
1660
    allocate (gpint(-ntgrid:ntgrid,naky,nspec))
×
1661
    allocate (gmnormint(-ntgrid:ntgrid,naky,nspec))
×
1662
    allocate (gmavg(ntheta0,naky,nspec))
×
1663
    allocate (gpavg(ntheta0,naky,nspec))
×
1664
    allocate (gmnormavg(ntheta0,naky,nspec))
×
1665
    allocate (gmtot(nspec), gm_nokx_tot(nspec), gm_nosig_tot(nspec))
×
1666
    allocate (gptot(nspec), gp_nokx_tot(nspec), gp_nosig_tot(nspec))
×
1667
    allocate (gtot(nspec), gmnormtot(nspec), gmnorm_nokx_tot(nspec), gmnorm_nosig_tot(nspec))
×
1668
    allocate (phim(-ntgrid:ntgrid,naky))
×
1669
    allocate (g_kint(-ntgrid:ntgrid,2,nspec), gm_kint(-ntgrid:ntgrid,2,nspec), gp_kint(-ntgrid:ntgrid,2,nspec))
×
1670
    allocate (g_avg(ntheta0,nspec), gnorm_avg(ntheta0,nspec))
×
1671
    allocate (g_all_tot(nspec), g_nokx_tot(nspec), g_nosig_tot(nspec), gtmp(nspec))
×
1672
    allocate (gnorm_all_tot(nspec), gnorm_nokx_tot(nspec), gnorm_nosig_tot(nspec))
×
1673

1674
    ! convert from g to h
1675
    call g_adjust (gnew, phinew, bparnew, direction = from_g_gs2)
×
1676

1677
    ! below we define gparity = J0 * h, where delta f = h - (q phi / T) F0
1678
    ! because we're ultimately interested in int J0 h * phi (i.e. particle flux)
1679
    ! This should probably be written as a redistribute gather/scatter?
1680
    do iglo = g_lo%llim_world, g_lo%ulim_world
×
1681
       ik = ik_idx(g_lo, iglo)
×
1682
       ie = ie_idx(g_lo, iglo)
×
1683
       il = il_idx(g_lo, iglo)
×
1684
       is = is_idx(g_lo, iglo)
×
1685
       it = it_idx(g_lo, iglo)
×
1686
       ! count total index for given (ik,il,ie,is) combo (dependent on layout)
1687
       iplo = idx(p_lo, ik, il, ie, is)
×
1688
       ! check to see if value of g corresponding to iglo is on this processor
1689
       if (idx_local(g_lo, iglo)) then
×
1690
          if (idx_local(p_lo, iplo)) then
×
1691
             ! if g value corresponding to iplo should be on this processor, then get it
1692
             gparity(:, it, :, iplo) = gnew(:, :, iglo) * spread(aj0(:, iglo), 2, 2)
×
1693
          else
1694
             ! otherwise, send g for this iplo value to correct processor
1695
             call send (gnew(:, :, iglo) * spread(aj0(:, iglo), 2, 2), proc_id(p_lo, iplo))
×
1696
          end if
1697
       else if (idx_local(p_lo, iplo)) then
×
1698
          ! if g for this iplo not on processor, receive it
1699
          call receive (gparity(:, it, :, iplo), proc_id(g_lo, iglo))
×
1700
       end if
1701
    end do
1702

1703
    ! convert from h back to g
1704
    call g_adjust (gnew, phinew, bparnew, direction = to_g_gs2)
×
1705

1706
    ! first diagnostic is phase space average of 
1707
    ! |J0*(h(z,vpa,kx) +/- h(-z,-vpa,-kx))|**2 / ( |J0*h(z,vpa,kx)|**2 + |J0*h(-z,-vpa,-kx)|**2 )
1708
    do it = 1, ntheta0
×
1709
       ! have to treat kx=0 specially
1710
       if (it == 1) then
×
1711
          it_source = 1
×
1712
       else
1713
          it_source = ntheta0 - it + 2
×
1714
       end if
1715

1716
       do isgn = 1, 2
×
1717
          sgn2 = mod(isgn,2)+1
×
1718
          do ig = -ntgrid, ntgrid
×
1719
             ! g0 = gparity(ntgrid:-ntgrid:-1, it_source, 2:1:-1, :) -- copy reversing theta and sigma
1720
             g0(ig, isgn, :) = gparity(-ig, it_source, sgn2, :)
×
1721
          end do
1722
       end do
1723

1724
       gm = gparity(:,it,:,:)-g0
×
1725
       gp = gparity(:,it,:,:)+g0
×
1726
       gmnorm = real(g0*conjg(g0))
×
1727
       ! integrate out velocity dependence
1728
       call integrate_moment (real(gm*conjg(gm)),gmint,1)
×
1729
       call integrate_moment (real(gp*conjg(gp)),gpint,1)
×
1730
       call integrate_moment (gmnorm,gmnormint,1)
×
1731
       ! average along field line
1732
       gmavg(it,:,:) = field_line_average(gmint)
×
1733
       gpavg(it,:,:) = field_line_average(gpint)
×
1734
       gmnormavg(it,:,:) = field_line_average(gmnormint)
×
1735

1736
       ! phim(theta,kx) = phi(-theta,-kx)
1737
       do ig = -ntgrid, ntgrid
×
1738
          phim(ig,:) = phinew(-ig, it_source, :)
×
1739
       end do
1740

1741
       ! want int dtheta sum_{kx} int d3v | sum_{ky} [ J0*(h+ * conjg(phi-) + h- * conjg(phi+)) ky ] |**2
1742
       ! J0*(h+ * conjg(phi-) + h- * conjg(phi+)) = h*conjg(phi) - h(-theta,-vpa,-kx)*conjg(phi(-theta,-kx))
1743
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1744
          ik = ik_idx(p_lo,iplo)
×
1745
          do isgn = 1, 2
×
1746
             gm(:,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik)) - g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1747
          end do
1748
       end do
1749
       call integrate_kysum (gm, g_kint, 1)
×
1750
       g_avg(it, :) = field_line_average(g_kint(:,1,:) + g_kint(:,2,:))
×
1751

1752
       ! get normalizing term for above diagnostic
1753
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1754
          ik = ik_idx(p_lo,iplo)
×
1755
          do isgn = 1, 2
×
1756
             gm(:,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik))
×
1757
             gp(:,isgn,iplo) = g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1758
          end do
1759
       end do
1760
       call integrate_kysum (gm, gm_kint, 1)
×
1761
       call integrate_kysum (gp, gp_kint, 1)
×
1762
       gnorm_avg(it,:) = field_line_average(gm_kint(:,1,:)+gm_kint(:,2,:) &
×
1763
            + gp_kint(:,1,:)+gp_kint(:,2,:))
×
1764
    end do
1765

1766
    ! average over perp plane
1767
    do is = 1, nspec
×
1768
       call get_volume_average (gmavg(:,:,is), gmtot(is))
×
1769
       call get_volume_average (gpavg(:,:,is), gptot(is))
×
1770
       call get_volume_average (gmnormavg(:,:,is), gmnormtot(is))    
×
1771
       g_all_tot(is) = sum(g_avg(:,is))
×
1772
       gnorm_all_tot(is) = sum(gnorm_avg(:,is))
×
1773
    end do
1774

1775
    allocate (gmx(-ntgrid:ntgrid,ntheta0,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1776
    allocate (gpx(-ntgrid:ntgrid,ntheta0,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1777

1778
    ! now we want diagnostic of phase space average of
1779
    ! |J0*(h(z,vpa) +/- h(-z,-vpa))|**2 / ( |J0*h(z,vpa)|**2 + |J0*h(-z,-vpa)|**2 )
1780
    do it = 1, ntheta0
×
1781
       do isgn = 1, 2
×
1782
          sgn2 = mod(isgn,2)+1
×
1783
          do ig = -ntgrid, ntgrid
×
1784
             g0(ig,isgn,:) = gparity(-ig,it,sgn2,:)
×
1785
          end do
1786
       end do
1787
       gm = gparity(:,it,:,:)-g0
×
1788
       gp = gparity(:,it,:,:)+g0
×
1789
       gmnorm = real(g0*conjg(g0))
×
1790
       ! integrate out velocity dependence
1791
       call integrate_moment (real(gm*conjg(gm)),gmint,1)
×
1792
       call integrate_moment (real(gp*conjg(gp)),gpint,1)
×
1793
       call integrate_moment (gmnorm,gmnormint,1)
×
1794
       ! average along field line
1795
       gmavg(it,:,:) = field_line_average(gmint)
×
1796
       gpavg(it,:,:) = field_line_average(gpint)
×
1797
       gmnormavg(it,:,:) = field_line_average(gmnormint)
×
1798

1799
       ! phim(theta) = phi(-theta)
1800
       ! have to treat kx=0 specially
1801
       do ig = -ntgrid, ntgrid
×
1802
          phim(ig,:) = phinew(-ig,it,:)
×
1803
       end do
1804

1805
       ! want int dtheta int d3v | sum_{kx} sum_{ky} [ J0*(h+ * conjg(phi-) + h- * conjg(phi+)) ky ] |**2
1806
       ! J0*(h+ * conjg(phi-) + h- * conjg(phi+)) = h*conjg(phi) - h(-theta,-vpa)*conjg(phi(-theta))
1807
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1808
          ik = ik_idx(p_lo,iplo)
×
1809
          do isgn = 1, 2
×
1810
             gmx(:,it,isgn,iplo) = g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1811
             gpx(:,it,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik)) - gmx(:,it,isgn,iplo) 
×
1812
          end do
1813
       end do
1814
    end do
1815

1816
    ! sum over kx
1817
    gp = sum(gpx,2)
×
1818
    deallocate (gpx)
×
1819
    call integrate_kysum(gp, g_kint, 1)
×
1820
    g_nokx_tot = field_line_average(g_kint(:,1,:) + g_kint(:,2,:))
×
1821

1822
    ! get normalizing terms for above diagnostic
1823
    gm = sum(gmx,2)
×
1824
    deallocate (gmx)
×
1825
    call integrate_kysum(gm, gm_kint, 1)
×
1826
    call integrate_kysum(gm + gp, gp_kint, 1)
×
1827
    gnorm_nokx_tot = field_line_average(gm_kint(:,1,:)+gm_kint(:,2,:) &
×
1828
         + gp_kint(:,1,:)+gp_kint(:,2,:))
×
1829

1830
    ! average over perp plane
1831
    do is = 1, nspec
×
1832
       call get_volume_average (gmavg(:,:,is), gm_nokx_tot(is))
×
1833
       call get_volume_average (gpavg(:,:,is), gp_nokx_tot(is))
×
1834
       call get_volume_average (gmnormavg(:,:,is), gmnorm_nokx_tot(is))    
×
1835
    end do
1836

1837
    ! final diagnostic is phase space average of 
1838
    ! |J0*(h(z,kx) +/- h(-z,-kx))|**2 / ( |J0*h(z,kx)|**2 + |J0*h(-z,-kx)|**2 )
1839
    do it = 1, ntheta0
×
1840
       ! have to treat kx=0 specially
1841
       if (it == 1) then
×
1842
          it_source = 1
×
1843
       else
1844
          it_source = ntheta0 - it + 2
×
1845
       end if
1846

1847
       do ig = -ntgrid, ntgrid
×
1848
          g0(ig, :, :) = gparity(-ig, it_source, :, :)
×
1849
       end do
1850

1851
       gm = gparity(:,it,:,:)-g0
×
1852
       gp = gparity(:,it,:,:)+g0
×
1853
       gmnorm = real(g0*conjg(g0))
×
1854
       ! integrate out velocity dependence
1855
       call integrate_moment (real(gm*conjg(gm)),gmint,1)
×
1856
       call integrate_moment (real(gp*conjg(gp)),gpint,1)
×
1857
       call integrate_moment (gmnorm,gmnormint,1)
×
1858
       ! average along field line
1859
       gmavg(it,:,:) = field_line_average(gmint)
×
1860
       gpavg(it,:,:) = field_line_average(gpint)
×
1861
       gmnormavg(it,:,:) = field_line_average(gmnormint)
×
1862

1863
       ! phim(theta,kx) = phi(-theta,-kx)
1864
       do ig = -ntgrid, ntgrid
×
1865
          phim(ig, :) = phinew(-ig, it_source, :)
×
1866
       end do
1867

1868
       ! want int dtheta sum_{kx} int dE dmu | sum_{sigma} sum_{ky} [ J0*(h+ * conjg(phi-) + h- * conjg(phi+)) ky ] |**2
1869
       ! J0*(h+ * conjg(phi-) + h- * conjg(phi+)) = h*conjg(phi) - h(-theta,-kx)*conjg(phi(-theta,-kx))
1870
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1871
          ik = ik_idx(p_lo,iplo)
×
1872
          do isgn = 1, 2
×
1873
             gm(:,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik)) - g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1874
          end do
1875
       end do
1876

1877
       ! Only sets isgn = 1 in the g_kint array here
1878
       call integrate_kysum (spread(gm(:, 1, :) + gm(:, 2, :), 2, 1), g_kint, 1)
×
1879
       g_avg(it, :) = field_line_average(g_kint(:,1,:))
×
1880

1881
       ! get normalizing term for above diagnostic
1882
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1883
          ik = ik_idx(p_lo,iplo)
×
1884
          do isgn = 1, 2
×
1885
             gm(:,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik))
×
1886
             gp(:,isgn,iplo) = g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1887
          end do
1888
       end do
1889

1890
       ! Only sets isgn = 1 in the g*_kint arrays here
1891
       call integrate_kysum (spread(gm(:, 1, :) + gm(:, 2, :), 2, 1), gm_kint, 1)
×
1892
       call integrate_kysum (spread(gp(:, 1, :) + gp(:, 2, :), 2, 1), gp_kint, 1)
×
1893
       gnorm_avg(it, :) = field_line_average(gm_kint(:,1,:) + gp_kint(:,1,:))
×
1894
    end do
1895

1896
    ! average over perp plane
1897
    do is = 1, nspec
×
1898
       call get_volume_average (gmavg(:,:,is), gm_nosig_tot(is))
×
1899
       call get_volume_average (gpavg(:,:,is), gp_nosig_tot(is))
×
1900
       call get_volume_average (gmnormavg(:,:,is), gmnorm_nosig_tot(is))    
×
1901
       g_nosig_tot(is) = sum(g_avg(:,is))
×
1902
       gnorm_nosig_tot(is) = sum(gnorm_avg(:,is))
×
1903
    end do
1904

1905
    deallocate (gparity) ; allocate (gparity(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1906
    ! obtain normalization factor = int over phase space of |g|**2
1907
    call g_adjust (gnew, phinew, bparnew, direction = from_g_gs2)
×
1908
    !Do all processors need to know the full result here? Only proc0 seems to do any writing.
1909
    !If not then remove the last two arguments in the following call.
1910
    call integrate_moment (spread(aj0,2,2)*spread(aj0,2,2)*gnew*conjg(gnew), gparity, .true., full_arr=.true.)
×
1911
    call g_adjust (gnew, phinew, bparnew, direction = to_g_gs2)
×
1912
    do is = 1, nspec
×
1913
       gmavg(:, :, is) = field_line_average(real(gparity(:,:,:,is)))
×
1914
       call get_volume_average (gmavg(:,:,is), gtot(is))
×
1915
    end do
1916

1917
    ! normalize g(theta,vpa,kx) - g(-theta,-vpa,-kx) terms
1918
    where (gtot+gmnormtot > epsilon(0.0))
×
1919
       gmtot = sqrt(gmtot/(gtot+gmnormtot)) ; gptot = sqrt(gptot/(gtot+gmnormtot))
×
1920
    elsewhere
1921
       gmtot = sqrt(gmtot) ; gptot = sqrt(gptot)
×
1922
    end where
1923

1924
    where (real(gnorm_all_tot) > epsilon(0.0))
×
1925
       gtmp = sqrt(real(g_all_tot)/real(gnorm_all_tot))
×
1926
    elsewhere
1927
       gtmp = sqrt(real(g_all_tot))
×
1928
    end where
1929
    where (aimag(gnorm_all_tot) > epsilon(0.0))
×
1930
       g_all_tot = gtmp + zi*sqrt(aimag(g_all_tot)/aimag(gnorm_all_tot))
×
1931
    elsewhere
1932
       g_all_tot = gtmp + zi*sqrt(aimag(g_all_tot))
×
1933
    end where
1934

1935
    ! normalize g(theta,vpa) +/- g(-theta,-vpa) terms
1936
    where (gtot+gmnorm_nokx_tot > epsilon(0.0))
×
1937
       gm_nokx_tot = sqrt(gm_nokx_tot/(gtot+gmnorm_nokx_tot)) ; gp_nokx_tot = sqrt(gp_nokx_tot/(gtot+gmnorm_nokx_tot))
×
1938
    elsewhere
1939
       gm_nokx_tot = sqrt(gm_nokx_tot) ; gp_nokx_tot = sqrt(gp_nokx_tot)
×
1940
    end where
1941

1942
    where (real(gnorm_nokx_tot) > epsilon(0.0))
×
1943
       gtmp = sqrt(real(g_nokx_tot)/real(gnorm_nokx_tot))
×
1944
    elsewhere
1945
       gtmp = sqrt(real(g_nokx_tot))
×
1946
    end where
1947
    where (aimag(gnorm_nokx_tot) > epsilon(0.0))
×
1948
       g_nokx_tot = gtmp + zi*sqrt(aimag(g_nokx_tot)/aimag(gnorm_nokx_tot))
×
1949
    elsewhere
1950
       g_nokx_tot = gtmp + zi*sqrt(aimag(g_nokx_tot))
×
1951
    end where
1952

1953
    ! normalize g(theta,kx) +/ g(-theta,-kx) terms
1954
    where (gtot+gmnorm_nosig_tot > epsilon(0.0))
×
1955
       gm_nosig_tot = sqrt(gm_nosig_tot/(gtot+gmnorm_nosig_tot)) ; gp_nosig_tot = sqrt(gp_nosig_tot/(gtot+gmnorm_nosig_tot))
×
1956
    elsewhere
1957
       gm_nosig_tot = sqrt(gm_nosig_tot) ; gp_nosig_tot = sqrt(gp_nosig_tot)
×
1958
    end where
1959

1960
    where (real(gnorm_nosig_tot) > epsilon(0.0))
×
1961
       gtmp = sqrt(real(g_nosig_tot)/real(gnorm_nosig_tot))
×
1962
    elsewhere
1963
       gtmp = sqrt(real(g_nosig_tot))
×
1964
    end where
1965
    where (aimag(gnorm_nosig_tot) > epsilon(0.0))
×
1966
       g_nosig_tot = gtmp + zi*sqrt(aimag(g_nosig_tot)/aimag(gnorm_nosig_tot))
×
1967
    elsewhere
1968
       g_nosig_tot = gtmp + zi*sqrt(aimag(g_nosig_tot))
×
1969
    end where
1970

1971
    if (proc0) write (file_unit,"(19(1x,e12.5))") t, gmtot, gptot, real(g_all_tot), aimag(g_all_tot), &
×
1972
         real(gnorm_all_tot), aimag(gnorm_all_tot), gm_nokx_tot, gp_nokx_tot, real(g_nokx_tot), aimag(g_nokx_tot), &
×
1973
         real(gnorm_nokx_tot), aimag(gnorm_nokx_tot), gm_nosig_tot, gp_nosig_tot, &
×
1974
         real(g_nosig_tot), aimag(g_nosig_tot), real(gnorm_nosig_tot), aimag(gnorm_nosig_tot)
×
1975

1976
    deallocate (gparity, g0)
×
1977
    deallocate (gm, gp, gmnorm, gmint, gpint, gmnormint)
×
1978
    deallocate (gmavg, gpavg, gmnormavg)
×
1979
    deallocate (gmtot, gm_nokx_tot, gm_nosig_tot)
×
1980
    deallocate (gptot, gp_nokx_tot, gp_nosig_tot)
×
1981
    deallocate (gtot, gmnormtot, gmnorm_nokx_tot, gmnorm_nosig_tot)
×
1982
    deallocate (g_avg, gnorm_avg)
×
1983
    deallocate (g_kint, gm_kint, gp_kint)
×
1984
    deallocate (g_all_tot, g_nokx_tot, g_nosig_tot, gtmp)
×
1985
    deallocate (gnorm_all_tot, gnorm_nokx_tot, gnorm_nosig_tot)
×
1986
    deallocate (phim)
×
1987
  end subroutine do_write_parity
×
1988

1989
  !> Calculate flux surfgace averaged low-order moments of \(g\) and write to netCDF
1990
  subroutine do_write_avg_moments
×
1991
    use diagnostics_moments, only: getmoms
1992
    use mp, only: proc0
1993
    use kt_grids, only: ntheta0, naky
1994
    use species, only: nspec
1995
    use fields_arrays, only: phinew, bparnew
1996
    use gs2_io, only: nc_loop_moments
1997
    use theta_grid, only: ntgrid, field_line_average
1998
    use volume_averages, only: average_theta, average_all
1999
    implicit none
2000
    complex, dimension (-ntgrid:ntgrid,ntheta0,naky,nspec) :: ntot, density, &
×
2001
         upar, tpar, tperp, pperpperp, qparflux, qpperpj1
×
2002
    complex, dimension (ntheta0, nspec) :: ntot00, density00, upar00, tpar00, tperp00, pperpperp00
×
2003
    complex, dimension (ntheta0) :: phi00
×
2004
    real, dimension (nspec) :: ntot2, ntot20, tpar2, tperp2, pperpperp2
×
2005
    real, dimension (ntheta0, naky, nspec) :: ntot2_by_mode, ntot20_by_mode
×
2006
    real, dimension (ntheta0, naky, nspec) :: tpar2_by_mode, tperp2_by_mode
×
2007
    real, dimension (ntheta0, naky, nspec) :: pperpperp2_by_mode
×
2008

2009
    ! We seem to call this routine a lot in one loop
2010
    call getmoms (phinew, bparnew, ntot, density, upar, tpar, tperp, pperpperp, qparflux, qpperpj1)
×
2011

2012
    if (proc0) then
×
2013
       ntot00 = field_line_average(ntot(:,:,1,:))
×
2014
       density00 = field_line_average(density(:,:,1,:))
×
2015
       upar00 = field_line_average(upar(:,:,1,:))
×
2016
       tpar00 = field_line_average(tpar(:,:,1,:))
×
2017
       tperp00 = field_line_average(tperp(:,:,1,:))
×
2018
       pperpperp00 = field_line_average(pperpperp(:,:,1,:))
×
2019
       phi00 = field_line_average(phinew(:,:,1))
×
2020

2021
       call average_theta(ntot, ntot, ntot2_by_mode)
×
2022
       call average_all(ntot2_by_mode, ntot2)
×
2023
       call average_theta(tpar, tpar, tpar2_by_mode)
×
2024
       call average_all(tpar2_by_mode, tpar2)
×
2025
       call average_theta(tperp, tperp, tperp2_by_mode)
×
2026
       call average_all(tperp2_by_mode, tperp2)
×
2027
       call average_theta(pperpperp, pperpperp, pperpperp2_by_mode)
×
2028
       call average_all(pperpperp2_by_mode, pperpperp2)
×
2029

2030
       ntot20_by_mode = real(conjg(ntot(0, :, :, :)) * ntot(0, :, :, :))
×
2031
       call average_all(ntot20_by_mode, ntot20)
×
2032

2033
       call nc_loop_moments (get_netcdf_file_id(), nout, ntot2, ntot2_by_mode, ntot20, &
×
2034
            ntot20_by_mode, phi00, ntot00, density00, upar00, &
×
2035
            tpar00, tperp00, tpar2_by_mode, tperp2_by_mode, pperpperp00, pperpperp2_by_mode)
×
2036
    end if
2037
  end subroutine do_write_avg_moments
×
2038

2039
  !> Flush text files (only [[out_unit]], [[res_unit]], [[lpc_unit]], and
2040
  !> [[parity_unit]])
2041
  subroutine flush_files
×
2042
    implicit none
2043
    if (.not. write_ascii) return
×
2044
    flush (out_unit)
×
2045
    if (write_verr) then
×
2046
       flush (res_unit)
×
2047
       flush (lpc_unit)
×
2048
    end if
2049
    if (write_cerr) flush (cres_unit)
×
2050
    if (write_parity) flush (parity_unit)
×
2051
    if (write_g) flush (dist_unit)
×
2052
    if (write_gyx) flush (yxdist_unit)
×
2053
  end subroutine flush_files
2054

2055
  !> Nonlinear convergence condition - simple and experimental look
2056
  !> for the averaged differential of the summed averaged heat flux to
2057
  !> drop below a threshold
2058
  subroutine check_nonlin_convergence(istep, heat_flux, exit)
×
2059
    use diagnostics_nonlinear_convergence, only: check_nonlin_convergence_calc
2060
    logical, intent(inout) :: exit
2061
    integer, intent(in) :: istep
2062
    real, intent(in) :: heat_flux
2063
    call check_nonlin_convergence_calc(istep, nwrite, heat_flux, exit, exit_when_converged, &
2064
         conv_nstep_av, conv_nsteps_converged, conv_test_multiplier, conv_min_step, &
2065
         conv_max_step)
×
2066
  end subroutine check_nonlin_convergence
×
2067

2068
  !> Calculate some heating diagnostics, and update their time history
2069
  subroutine heating(istep, navg, h, hk, h_hist, hk_hist)
×
2070
    use mp, only: proc0
2071
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
2072
    use species, only: nspec, spec
2073
    use kt_grids, only: naky, ntheta0, aky, akx
2074
    use theta_grid, only: ntgrid, delthet, jacob
2075
    use gs2_heating, only: heating_diagnostics, avg_h, avg_hk, zero_htype, get_heat
2076
    use collisions, only: collisions_heating => heating, c_rate
2077
    implicit none
2078
    integer, intent (in) :: istep, navg
2079
    !> Heating diagnostics summed over space at the current timestep
2080
    type (heating_diagnostics), intent(in out) :: h
2081
    type (heating_diagnostics), dimension (0:), intent(in out) :: h_hist
2082
    !> Heating diagnostics as a function of \((\theta, k_y)\) at the current timestep
2083
    type (heating_diagnostics), dimension(:,:), intent(in out) :: hk
2084
    type (heating_diagnostics), dimension(:,:,0:), intent(in out) :: hk_hist
2085
    real, dimension(-ntgrid:ntgrid) :: wgt
×
2086
    real :: fac
2087
    integer :: is, ik, it, ig
2088

2089
    !Zero out variables for heating diagnostics
2090
    call zero_htype(h)
×
2091
    call zero_htype(hk)
×
2092

2093
    if (proc0 .and. collisions_heating .and. allocated(c_rate)) then
×
2094
       !GGH NOTE: Here wgt is 1/(2*ntgrid+1)
2095
       wgt = delthet*jacob
×
2096
       wgt = wgt/sum(wgt)
×
2097

2098
       do is = 1, nspec
×
2099
          do ik = 1, naky
×
2100
             fac = 0.5
×
2101
             if (aky(ik) < epsilon(0.)) fac = 1.0
×
2102
             do it = 1, ntheta0
×
2103
                if (aky(ik) < epsilon(0.0) .and. abs(akx(it)) < epsilon(0.0)) cycle
×
2104
                do ig = -ntgrid, ntgrid
×
2105

2106
                   !Sum heating by k over all z points (ig)
2107
                   hk(it, ik) % collisions(is) = hk(it, ik) % collisions(is) &
×
2108
                        + real(c_rate(ig,it,ik,is,1))*fac*wgt(ig)*spec(is)%temp*spec(is)%dens
×
2109

2110
                   hk(it, ik) % hypercoll(is) = hk(it, ik) % hypercoll(is) &
×
2111
                        + real(c_rate(ig,it,ik,is,2))*fac*wgt(ig)*spec(is)%temp*spec(is)%dens
×
2112

2113
                   hk(it, ik) % imp_colls(is) = hk(it, ik) % imp_colls(is) &
×
2114
                        + real(c_rate(ig,it,ik,is,3))*fac*wgt(ig)*spec(is)%temp*spec(is)%dens
×
2115

2116
                end do
2117
                h % collisions(is) = h % collisions(is) + hk(it, ik) % collisions(is)
×
2118
                h % hypercoll(is)  = h % hypercoll(is)  + hk(it, ik) % hypercoll(is)
×
2119
                h % imp_colls(is)  = h % imp_colls(is)  + hk(it, ik) % imp_colls(is)
×
2120
             end do
2121
          end do
2122
       end do
2123
    end if
2124

2125
    ! We may be able to skip this work as well if heating is false.
2126
    call get_heat (h, hk, phi, apar, bpar, phinew, aparnew, bparnew)
×
2127

2128
    call avg_h(h, h_hist, istep, navg)
×
2129
    call avg_hk(hk, hk_hist, istep, navg)
×
2130
  end subroutine heating
×
2131

2132
  !> Calculate the time-averaged antenna current \(j_{ext} = k_\perp^2 A_{antenna}\)
2133
  subroutine calc_jext (istep, j_ext)
×
2134
    use mp, only: proc0
2135
    use antenna, only: get_jext
2136
    implicit none
2137
    !> Current simulation timestep
2138
    integer, intent (in) :: istep
2139
    !Shouldn't really need intent in here but it's beacuse we zero it before calling calc_jext
2140
    real, dimension(:,:), intent(in out) ::  j_ext
2141

2142
    integer :: i
2143
    if (.not. (proc0 .and. navg > 1)) return
×
2144
    call get_jext(j_ext)
×
2145
    ! This looks a little odd as we ignore the first step
2146
    if (istep > 1) j_ext_hist(:, :, mod(istep, navg)) = j_ext(:, :)
×
2147

2148
    !Use average of history
2149
    if (istep >= navg) then
×
2150
       j_ext = 0.
×
2151
       do i = 0, navg - 1
×
2152
          j_ext = j_ext + j_ext_hist(:, :, i) / real(navg)
×
2153
       end do
2154
    end if
2155
  end subroutine calc_jext
2156

2157
  !> A linear estimate of the diffusivity, primarily used testing
2158
  pure real function diffusivity()
×
2159
    use kt_grids, only: ntheta0, naky, kperp2
2160
    use theta_grid, only: grho
2161
    use warning_helpers, only: is_zero
2162
    real, dimension(ntheta0, naky) :: diffusivity_by_k
×
2163
    integer  :: ik, it
2164
    diffusivity_by_k = 0.0
×
2165
    do ik = 1, naky
×
2166
       do it = 1, ntheta0
×
2167
          if (is_zero(kperp2(igomega,it,ik))) cycle
×
2168
          diffusivity_by_k(it,ik) = 2.0 &
×
2169
               * max(aimag(omegaavg(it,ik)), 0.0) / kperp2(igomega, it, ik)
×
2170
       end do
2171
    end do
2172
    diffusivity = maxval(diffusivity_by_k) * grho(igomega)
×
2173
  end function diffusivity
×
2174

2175
  !> Calculates <|field|**2 kperp2>_theta / <|field|**2>_theta.
2176
  !> Useful for simple quasilinear metric
2177
  pure function get_field_weighted_average_kperp2(field) result(average)
×
2178
    use kt_grids, only: kperp2, naky, ntheta0
2179
    use theta_grid, only: ntgrid, field_line_average
2180
    implicit none
2181
    complex, dimension(-ntgrid:ntgrid, ntheta0, naky), intent(in) :: field
2182
    real, dimension(ntheta0, naky) :: average
2183
    real, dimension(-ntgrid:ntgrid, ntheta0, naky) :: field_squared
×
2184
    integer :: it, ik
2185
    field_squared = abs(field) * abs(field)
×
2186
    average = 0.0
×
2187
    do ik = 1, naky
×
2188
       do it = 1, ntheta0
×
2189
          if (maxval(abs(field_squared(:, it, ik))) <= epsilon(0.0)) cycle
×
2190
          average(it, ik) = field_line_average(field_squared(:, it, ik) * &
×
2191
               kperp2(:, it, ik)) / field_line_average(field_squared(:, it, ik))
×
2192
       end do
2193
    end do
2194
  end function get_field_weighted_average_kperp2
×
2195

2196
  !> Calculates a simple gamma/kperp2 QL flux metric
2197
  function calculate_simple_quasilinear_flux_metric_by_k(growth_rates) result(ql_metric)
×
2198
    use run_parameters, only: has_phi, has_apar, has_bpar
2199
    use kt_grids, only: naky, ntheta0, aky
2200
    use fields_arrays, only: phinew, aparnew, bparnew
2201
    use warning_helpers, only: is_zero
2202
    implicit none
2203
    real, dimension(ntheta0, naky), intent(in) :: growth_rates
2204
    real, dimension(ntheta0, naky) :: limited_growth_rates, average
×
2205
    real, dimension(ntheta0, naky) :: ql_metric, normalising_field
×
2206
    integer :: ik
2207

2208
    ! Initialise flux to zero
2209
    ql_metric = 0.0
×
2210

2211
    ! Decide on the normalising field
2212
    if (has_phi) then
×
2213
       normalising_field = maxval(abs(phinew), dim = 1)
×
2214
    else if (has_apar) then
×
2215
       normalising_field = maxval(abs(aparnew), dim = 1)
×
2216
    else if (has_bpar) then
×
2217
       normalising_field = maxval(abs(bparnew), dim = 1)
×
2218
    else
2219
       ! If we get here then no fields are active so the QL flux
2220
       ! is zero and we can exit
2221
       return
×
2222
    end if
2223

2224
    where (normalising_field > 0)
×
2225
       normalising_field = 1.0 / normalising_field
×
2226
    end where
2227

2228
    if (has_phi) then
×
2229
       average = get_field_weighted_average_kperp2(phinew)
×
2230
       where(average > 0.0)
×
2231
          ql_metric = maxval(abs(phinew), dim = 1) * normalising_field / average
×
2232
       end where
2233
    end if
2234

2235
    if (has_apar) then
×
2236
       average = get_field_weighted_average_kperp2(aparnew)
×
2237
       where(average > 0.0)
×
2238
          ql_metric = ql_metric + &
×
2239
               maxval(abs(aparnew), dim = 1) * normalising_field / average
×
2240
       end where
2241
    end if
2242

2243
    if (has_bpar) then
×
2244
       average = get_field_weighted_average_kperp2(bparnew)
×
2245
       where(average > 0.0)
×
2246
          ql_metric = ql_metric + &
×
2247
               maxval(abs(bparnew), dim = 1) * normalising_field / average
×
2248
       end where
2249
    end if
2250

2251
    ! Limit the growth rate to positive values
2252
    where (growth_rates > 0)
×
2253
       limited_growth_rates = growth_rates
×
2254
    elsewhere
2255
       limited_growth_rates = 0.0
×
2256
    end where
2257

2258
    ! MG: Avoid spurious contribution from the zonal mode
2259
    do ik = 1, naky
×
2260
       if (is_zero(aky(ik))) ql_metric(:, ik) = 0.0
×
2261
    end do
2262

2263
    ql_metric = ql_metric * limited_growth_rates
×
2264
  end function calculate_simple_quasilinear_flux_metric_by_k
×
2265

2266
  !> Calculates the instantaneous omega from chinew = chi * exp(-i * omega * dt)
2267
  !> with chi = phi + apar + bpar. This gives omega = log(chinew/chi) * i / dt.
2268
  pure function  calculate_instantaneous_omega(ig, tolerance) result(omega_inst)
×
2269
    use kt_grids, only: naky, ntheta0
2270
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
2271
    use gs2_time, only: code_dt
2272
    use constants, only: zi
2273
    use optionals, only: get_option_with_default
2274
    use run_parameters, only: has_phi, has_apar, has_bpar
2275
    use warning_helpers, only: is_zero
2276
    implicit none
2277
    integer, intent(in), optional :: ig
2278
    real, intent(in), optional :: tolerance
2279
    complex, dimension(ntheta0, naky) :: omega_inst, field_sum, field_sum_new
×
2280
    integer :: ig_use
2281
    real :: tol_use, too_small
2282

2283
    ! Determine which theta grid point to evaluate the fields at
2284
    ig_use = get_option_with_default(ig, igomega)
×
2285

2286
    ! Construct the field sums for current and old fields.
2287
    ! We always allocate the fields (for now) so we could just
2288
    ! unconditionally sum. This could make the code clearer
2289
    ! without really adding _much_ overhead.
2290
    if (has_phi) then
×
2291
       field_sum = phi(ig_use, :, :)
×
2292
       field_sum_new = phinew(ig_use, :, :)
×
2293
    else
2294
       field_sum = 0.0
×
2295
       field_sum_new = 0.0
×
2296
    end if
2297

2298
    if (has_apar) then
×
2299
       field_sum = field_sum + apar(ig_use, :, :)
×
2300
       field_sum_new = field_sum_new + aparnew(ig_use, :, :)
×
2301
    end if
2302

2303
    if (has_bpar) then
×
2304
       field_sum = field_sum + bpar(ig_use, :, :)
×
2305
       field_sum_new = field_sum_new + bparnew(ig_use, :, :)
×
2306
    end if
2307

2308
    ! Determine what tolerance to use
2309
    tol_use = get_option_with_default(tolerance, omegatol)
×
2310

2311
    ! Decide what size float we consider too small to divide by
2312
    ! Note this uses tiny rather than epsilon in order to allow
2313
    ! us to track modes with low amplitudes.
2314
    if (is_zero(tol_use)) then
×
2315
       too_small = tiny(0.0)
×
2316
    else
2317
       too_small = tiny(0.0) * 1000. / abs(tol_use)
×
2318
    end if
2319

2320
    ! Use where to guard against dividing by tool small a number
2321
    ! Note we don't divide by field_sum_new so we probably don't need to
2322
    ! check that here, just field_sum.
2323
    where (abs(field_sum) < too_small .or. abs(field_sum_new) < too_small)
×
2324
       omega_inst = 0.0
×
2325
    elsewhere
2326
       omega_inst = log(field_sum_new / field_sum) * zi / code_dt
×
2327
    end where
2328

2329
  end function calculate_instantaneous_omega
×
2330

2331
  !> Calculate the time-averaged complex frequency, check convergence
2332
  !> criterion, and numerical instability criterion.
2333
  !>
2334
  !> Time average is over previous [[gs2_diagnostics_knobs:navg]] timesteps
2335
  subroutine get_omegaavg (istep, exit, omegaavg, debopt)
×
2336
    use kt_grids, only: ntheta0, naky
2337
    use gs2_time, only: code_dt, user_time
2338
    use optionals, only: get_option_with_default
2339
    implicit none
2340
    !> The current timestep
2341
    integer, intent (in) :: istep
2342
    !> Should the simulation exit?
2343
    !> FIXME: This could be `intent(out)` only
2344
    logical, intent (in out) :: exit
2345
    !> The time-averaged complex frequency
2346
    complex, dimension (:,:), intent (out) :: omegaavg
2347
    !> If true, write some debug messages
2348
    logical, intent (in), optional :: debopt
2349
    logical :: debug
2350
    debug = get_option_with_default(debopt, .false.)
×
2351
    if (debug) write(6,*) "get_omeaavg: allocate domega"
×
2352
    if (.not. allocated(domega)) allocate(domega(navg,ntheta0,naky))
×
2353
    if (debug) write(6,*) "get_omeaavg: start"
×
2354
    if (debug) write(6,*) "get_omeaavg: set omegahist"
×
2355

2356
    ! Get and store the current instantaneous omega
2357
    omegahist(mod(istep, navg), :, :) = calculate_instantaneous_omega(igomega, omegatol)
×
2358

2359
    if (debug) write(6,*) "get_omeaavg: set omegahist at istep = 0"
×
2360
    !During initialisation fieldnew==field but floating error can lead to finite omegahist
2361
    !Force omegahist=0 here to avoid erroneous values.
2362
    !Could think about forcing omegahist=0 where abs(omegahist)<tol
2363
    if(istep==0) omegahist(:,:,:)=0.0
×
2364

2365
    if (debug) write(6,*) "get_omeaavg: set omegaavg"
×
2366
    omegaavg = sum(omegahist/real(navg),dim=1)
×
2367
    if (debug) write(6,*) "get_omegaavg: omegaavg=",omegaavg
×
2368
    if ((istep > navg) .and.(user_time >= omega_checks_start)) then
×
2369
       domega = spread(omegaavg,1,navg) - omegahist
×
2370
       if (all(sqrt(sum(abs(domega)**2/real(navg),dim=1)) &
×
2371
            .le. min(abs(omegaavg),1.0)*omegatol)) &
×
2372
            then
2373
          if (write_ascii) write (out_unit, "('*** omega converged')")
×
2374
          if (exit_when_converged) exit = .true.
×
2375
       end if
2376

2377
       if (any(abs(omegaavg)*code_dt > omegatinst)) then
×
2378
          if (write_ascii) write (out_unit, "('*** numerical instability detected')") 
×
2379
          exit = .true.
×
2380
       end if
2381

2382
       if (all(aimag(omegaavg) < damped_threshold)) then
×
2383
          if (write_ascii) write (out_unit, "('*** all modes strongly damped')")
×
2384
          exit = .true.
×
2385
       end if
2386
    end if
2387
    if (debug) write(6,*) "get_omegaavg: done"
×
2388
  end subroutine get_omegaavg
×
2389

2390
  !> Summed magnitude of all the fields
2391
  subroutine phinorm (phitot)
×
2392
    use fields_arrays, only: phinew, aparnew, bparnew
2393
    use theta_grid, only: theta
2394
    use kt_grids, only: naky, ntheta0
2395
    use constants, only: twopi
2396
    use integration, only: trapezoidal_integration
2397
    implicit none
2398
    real, dimension (:,:), intent (out) :: phitot
2399
    integer :: ik, it
2400
    do ik = 1, naky
×
2401
       do it = 1, ntheta0
×
2402
          phitot(it, ik) = trapezoidal_integration(theta, &
×
2403
               (abs(phinew(:, it, ik))**2 + abs(aparnew(:, it, ik))**2 &
×
2404
               + abs(bparnew(:, it, ik))**2)) / twopi
×
2405
       end do
2406
    end do
2407
  end subroutine phinorm
×
2408

2409
  !> FIXME : Add documentation
2410
  !>
2411
  !> @note : We should probably consider writing this to take the
2412
  !> array to ensemble average
2413
  !>
2414
  !> @note : We don't appear to actually average here, just sum.
2415
  subroutine ensemble_average (nensembles, time_int, start_time_in)
×
2416
    use mp, only: scope, allprocs, group_to_all, broadcast
2417
    use gs2_time, only: user_time
2418
    use species, only: nspec
2419
    use optionals, only: get_option_with_default
2420
    implicit none
2421
    integer, intent (in) :: nensembles
2422
    real, intent (out) :: time_int
2423
    real, intent(in), optional :: start_time_in
2424
    real, dimension (nensembles) :: dt_global
×
2425
    real, dimension (nensembles,nspec) :: pflx_global, qflx_global, heat_global, vflx_global
×
2426
    real :: start_time
2427
    start_time = get_option_with_default(start_time_in, 0.0)
×
2428
    time_int = user_time - start_time
×
2429
    call scope (allprocs)
×
2430
    call group_to_all (time_int, dt_global, nensembles)
×
2431
    call broadcast (dt_global)
×
2432
    time_int = sum(dt_global)
×
2433
    call group_to_all (pflux_avg, pflx_global, nensembles)
×
2434
    call group_to_all (qflux_avg, qflx_global, nensembles)
×
2435
    call group_to_all (vflux_avg, vflx_global, nensembles)
×
2436

2437
    call broadcast (pflx_global)
×
2438
    call broadcast (qflx_global)
×
2439
    call broadcast (vflx_global)
×
2440
    pflux_avg = sum(pflx_global, dim = 1)
×
2441
    qflux_avg = sum(qflx_global, dim = 1)
×
2442
    vflux_avg = sum(vflx_global, dim = 1)
×
2443
    if (write_heating) then
×
2444
       call group_to_all (heat_avg, heat_global, nensembles)
×
2445
       call broadcast (heat_global)
×
2446
       heat_avg = sum(heat_global, dim = 1)
×
2447
    end if
2448
    ! Shouldn't we "rescope" on entry to leave us in the same scope that we
2449
    ! entered in?
2450
  end subroutine ensemble_average
×
2451

2452
  !> FIXME : Add documentation
2453
  !> @note: Should look at moving this and weighted_ky_sum to volume_averages
2454
  subroutine get_volume_average (f, favg)
×
2455
    implicit none
2456
    real, dimension (:,:), intent (in) :: f
2457
    real, intent (out) :: favg
2458
    favg = sum(weighted_ky_sum(f))
×
2459
  end subroutine get_volume_average
×
2460

2461
  !> Sum a {kx,ky} array over ky accounting for non-uniform weighting arising
2462
  !> from gs2's non-standard Fourier coefficients:
2463
  !> ky=0 modes have correct amplitudes; rest must be scaled
2464
  !> note contrast with scaling factors in FFT routines.
2465
  !>
2466
  !>  fac values here arise because gs2's Fourier coefficients, F_k^gs2, not standard form:
2467
  !>          i.e. f(x) = f_k e^(i k.x)
2468
  !>  With standard Fourier coeffs in gs2, we would instead need:  fac=2.0 for ky > 0
2469
  !>      (fac=2.0 would account ky<0 contributions, not stored due to reality condition)
2470
  pure function weighted_ky_sum(f) result(ky_sum)
×
2471
    use kt_grids, only: naky, ntheta0, aky
2472
    use warning_helpers, only: is_zero
2473
    implicit none
2474
    real, dimension(:, :), intent (in) :: f
2475
    real, dimension(ntheta0) :: ky_sum
2476
    real :: fac
2477
    integer :: ik
2478
    ky_sum = 0.
×
2479
    do ik = 1, naky
×
2480
       fac = 0.5
×
2481
       if (is_zero(aky(ik))) fac = 1.0
×
2482
       ky_sum = ky_sum + f(:, ik) * fac
×
2483
    end do
2484
  end function weighted_ky_sum
×
2485

2486
  !> Calculate the correlation function over the extended domain
2487
  subroutine correlation_extend (cfnc, phi2extend, ntg_extend)
×
2488
    use fields_arrays, only: phinew
2489
    use theta_grid, only: ntgrid, jacob, delthet, ntgrid
2490
    use kt_grids, only: ntheta0, naky, jtwist
2491
    implicit none
2492
    real, dimension (:,:,:), intent (out) :: phi2extend
2493
    complex, dimension (:,:,:), intent (out) :: cfnc
2494
    integer, intent(in) :: ntg_extend
2495
    integer :: ig, it, ik, im, igmod, itshift, nconnect, offset
2496
    real, dimension (:), allocatable :: dl_over_b
×
2497
    complex, dimension (:,:,:), allocatable :: phiextend
×
2498
    complex, dimension (:,:), allocatable :: phir
×
2499

2500
    allocate (dl_over_b(2*ntgrid+1))
×
2501
    dl_over_b = delthet * jacob
×
2502

2503
    allocate (phiextend(ntg_extend,ntheta0,naky)) ; phiextend = 0.0
×
2504
    allocate (phir(-ntgrid:ntgrid,ntheta0))
×
2505

2506
    cfnc = 0.0 ; phiextend = 0.0
×
2507
    offset = ((ntheta0-1)/jtwist)*(2*ntgrid+1)/2
×
2508
    call reorder_kx (phinew(:, :, 1), phir(:, :))
×
2509
    phiextend(offset+1:offset+(2*ntgrid+1),:,1) = phir
×
2510
    do it = 1, ntheta0
×
2511
       do im = 1, 2*ntgrid+1
×
2512
          do ig = im+offset, offset+(2*ntgrid+1)
×
2513
             igmod = mod(ig-offset-1,2*ntgrid+1)+1
×
2514
             cfnc(im,it,1) = cfnc(im,it,1) &
×
2515
                  + phiextend(ig,it,1)*conjg(phiextend(ig-im+1,it,1)) &
×
2516
                  * dl_over_b(igmod)
×
2517
          end do
2518
       end do
2519
       if (abs(cfnc(1, it, 1)) > epsilon(0.0)) then
×
2520
         cfnc(:, it, 1) = cfnc(:, it, 1) / cfnc(1, it, 1)
×
2521
       end if
2522
    end do
2523

2524
    do ik = 2, naky
×
2525
       call reorder_kx (phinew(:, :, ik), phir(:, :))
×
2526
       ! shift in kx due to parallel boundary condition
2527
       ! also the number of independent theta0s
2528
       itshift = jtwist*(ik-1)
×
2529
       do it = 1, min(itshift,ntheta0)
×
2530
          ! number of connections between kx's
2531
          nconnect = (ntheta0-it)/itshift
×
2532
          ! shift of theta index to account for fact that not all ky's
2533
          ! have same length in extended theta
2534
          offset = (2*ntgrid+1)*((ntheta0-1)/jtwist-nconnect)/2
×
2535
          do ig = 1, nconnect+1
×
2536
             phiextend(offset+(ig-1)*(2*ntgrid+1)+1:offset+ig*(2*ntgrid+1),it,ik) &
×
2537
                  = phir(:,ntheta0-it-(ig-1)*itshift+1)
×
2538
          end do
2539
          do im = 1, (2*ntgrid+1)*(nconnect+1)
×
2540
             do ig = im+offset, offset+(2*ntgrid+1)*(nconnect+1)
×
2541
                igmod = mod(ig-offset-1,2*ntgrid+1)+1
×
2542
                cfnc(im,it,ik) = cfnc(im,it,ik) &
×
2543
                     + phiextend(ig,it,ik)*conjg(phiextend(ig-im+1,it,ik)) &
×
2544
                     * dl_over_b(igmod)
×
2545
             end do
2546
          end do
2547
          cfnc(:,it,ik) = cfnc(:,it,ik) / cfnc(1,it,ik)
×
2548
       end do
2549
    end do
2550

2551
    phi2extend = real(phiextend*conjg(phiextend))
×
2552

2553
    deallocate (dl_over_b, phir, phiextend)
×
2554
  end subroutine correlation_extend
×
2555

2556
  !> Go from kx_ind = [0, 1, ..., N, -N, ...., -1]
2557
  !> to [-N, ....,-1,0,1,....,N]
2558
  subroutine reorder_kx (unord, ord)
×
2559
    use kt_grids, only: ntheta0
2560
    implicit none
2561
    complex, dimension (:, :), intent (in) :: unord
2562
    complex, dimension (:, :), intent (out) :: ord
2563
    ord = cshift(unord, -ntheta0 / 2, dim = 2)
×
2564
  end subroutine reorder_kx
×
2565

2566
  !> Calculate the correlation function on the physical domain
2567
  subroutine correlation (cfnc_2pi)
×
2568
    use kt_grids, only: naky, ntheta0
2569
    use theta_grid, only: ntgrid
2570
    use fields_arrays, only: phinew
2571
    implicit none
2572
    complex, dimension (-ntgrid:,:), intent (out) :: cfnc_2pi
2573
    integer :: ik, it, ig
2574
    real :: fac
2575

2576
    cfnc_2pi = 0.0
×
2577

2578
    do ik = 1, naky
×
2579
       if (ik==1) then
×
2580
          fac = 1.0
×
2581
       else
2582
          fac = 0.5
×
2583
       end if
2584
       do it = 1, ntheta0
×
2585
          do ig = -ntgrid, ntgrid
×
2586
             cfnc_2pi(ig,ik) = cfnc_2pi(ig,ik) + phinew(0,it,ik)*conjg(phinew(ig,it,ik))*fac
×
2587
          end do
2588
       end do
2589
    end do
2590

2591
  end subroutine correlation
×
2592

2593
  !> Write \(g(v_\parallel,v_\perp)\) at `ik=it=is=1, ig=0` to text file `<runname>.dist`
2594
  subroutine do_write_f (unit)
×
2595
    use mp, only: proc0, send, receive
2596
    use gs2_layouts, only: g_lo, ik_idx, it_idx, is_idx, il_idx, ie_idx, idx_local, proc_id
2597
    use le_grids, only: al, energy, forbid, negrid, nlambda, speed
2598
    use theta_grid, only: bmag
2599
    use dist_fn_arrays, only: gnew
2600
    use species, only: nspec
2601
    integer, intent(in) :: unit
2602
    integer :: iglo, ik, it, is
2603
    integer :: ie, il, ig
2604
    real :: vpa, vpe
2605
    complex, dimension(2) :: gtmp
2606
    real, dimension (:,:), allocatable, save :: xpts
2607
    real, dimension (:), allocatable, save :: ypts
2608
    !> Change argument of bmag depending on which theta you want to write out
2609
    integer, parameter :: ig_index = 0
2610
    if (.not. allocated(xpts)) then
×
2611
       allocate(xpts(negrid,nspec))
×
2612
       allocate(ypts(nlambda))
×
2613

2614
       ! should really just get rid of xpts and ypts
2615
       xpts = speed
×
2616
       ypts = 0.0
×
2617

2618
       do il=1,nlambda
×
2619
          ypts(il) = sqrt(max(0.0,1.0-al(il)*bmag(ig_index)))
×
2620
       end do
2621

2622
       if (proc0) then
×
2623
          write(unit, *) negrid*nlambda
×
2624
       end if
2625
    endif
2626

2627
    do iglo = g_lo%llim_world, g_lo%ulim_world
×
2628
       ik = ik_idx(g_lo, iglo) ; if (ik /= 1) cycle
×
2629
       it = it_idx(g_lo, iglo) ; if (it /= 1) cycle
×
2630
       is = is_idx(g_lo, iglo) ; if (is /= 1) cycle
×
2631
       ie = ie_idx(g_lo, iglo)
×
2632
       ig = ig_index
×
2633
       il = il_idx(g_lo, iglo)
×
2634
       if (idx_local (g_lo, ik, it, il, ie, is)) then
×
2635
          if (proc0) then
×
2636
             gtmp = gnew(ig, :, iglo)
×
2637
          else
2638
             call send (gnew(ig,:,iglo), 0)
×
2639
          endif
2640
       else if (proc0) then
×
2641
          call receive (gtmp, proc_id(g_lo, iglo))
×
2642
       endif
2643
       if (proc0) then
×
2644
          if (.not. forbid(ig, il)) then
×
2645
             vpa = sqrt(energy(ie,is)*max(0.0, 1.0-al(il)*bmag(ig)))
×
2646
             vpe = sqrt(energy(ie,is)*al(il)*bmag(ig))
×
2647
             write (unit, "(8(1x,e13.6))") vpa, vpe, energy(ie,is), al(il), &
×
2648
                  xpts(ie,is), ypts(il), real(gtmp(1)), real(gtmp(2))
×
2649
          end if
2650
       end if
2651
    end do
2652
    if (proc0) write (unit, *)
×
2653
  end subroutine do_write_f
×
2654

2655
  !> Write distribution function (\(g\) or possibly \(f\)?) in real space to text file
2656
  !> "<runname>.yxdist"
2657
  subroutine do_write_fyx (unit, phi, bpar)
×
2658
    use mp, only: proc0, send, receive, barrier
2659
    use gs2_layouts, only: il_idx, ig_idx, ik_idx, it_idx, is_idx, isign_idx, ie_idx
2660
    use gs2_layouts, only: idx_local, proc_id, yxf_lo, accelx_lo, g_lo
2661
    use le_grids, only: al, energy=>energy_maxw, forbid, negrid, nlambda
2662
    use theta_grid, only: bmag, ntgrid
2663
    use dist_fn_arrays, only: gnew, g_adjust, g_work, to_g_gs2, from_g_gs2
2664
    use nonlinear_terms, only: accelerated
2665
    use gs2_transforms, only: transform2
2666
    use array_utils, only: zero_array, copy
2667
#ifdef SHMEM
2668
    use shm_mpi3, only: shm_alloc, shm_free
2669
#endif
2670
    integer, intent(in) :: unit
2671
    !> Electrostatic potential and parallel magnetic field
2672
    complex, dimension (-ntgrid:,:,:), intent (in) :: phi, bpar
2673
    real, dimension (:,:), allocatable :: grs, gzf
×
2674
#ifndef SHMEM
2675
    real, dimension (:,:,:), allocatable :: agrs, agzf
×
2676
#else
2677
    real, dimension (:,:,:), pointer, contiguous :: agrs => null(), agzf => null()
2678
    complex, dimension(:,:,:), pointer, contiguous :: g0_ptr => null()
2679
#endif
2680
    real, dimension (:), allocatable :: agp0, agp0zf
×
2681
    real :: gp0, gp0zf
2682
    integer :: ig, it, ik, il, ie, is, iyxlo, isign, iaclo, iglo, acc
2683
    logical, save :: first = .true.
2684

2685
    if (accelerated) then
×
2686
#ifndef SHMEM
2687
       allocate (agrs(2*ntgrid+1, 2, accelx_lo%llim_proc:accelx_lo%ulim_alloc))
×
2688
       allocate (agzf(2*ntgrid+1, 2, accelx_lo%llim_proc:accelx_lo%ulim_alloc))
×
2689
#else
2690
       call shm_alloc(agrs, [1, 2*ntgrid+1, 1, 2, accelx_lo%llim_proc, accelx_lo%ulim_alloc])
2691
       call shm_alloc(agzf, [1, 2*ntgrid+1, 1, 2, accelx_lo%llim_proc, accelx_lo%ulim_alloc])
2692
       call shm_alloc(g0_ptr, [1, 2*ntgrid+1, 1, 2, accelx_lo%llim_proc, accelx_lo%ulim_alloc])
2693
#endif
2694
       allocate (agp0(2), agp0zf(2))
×
2695
       call zero_array(agrs); call zero_array(agzf); agp0 = 0.0; agp0zf = 0.0
×
2696
    else
2697
#ifdef SHMEM
2698
       g0_ptr => g_work
2699
#endif
2700
       allocate (grs(yxf_lo%ny, yxf_lo%llim_proc:yxf_lo%ulim_alloc))
×
2701
       allocate (gzf(yxf_lo%ny, yxf_lo%llim_proc:yxf_lo%ulim_alloc))
×
2702
       call zero_array(grs); call zero_array(gzf); gp0 = 0.0; gp0zf = 0.0
×
2703
    end if
2704

2705
    if (first) then
×
2706
       if (proc0) then
×
2707
          acc = 0
×
2708
          if (accelerated) acc = 1
×
2709
          write(unit,*) 2*negrid*nlambda, bmag(0), acc
×
2710
       end if
2711

2712
       first = .false.
×
2713
    end if
2714

2715
    call g_adjust (gnew, phi, bpar, direction = from_g_gs2)
×
2716

2717
#ifndef SHMEM
2718
    call copy(gnew, g_work)
×
2719
#else
2720
    g0_ptr = gnew
2721
#endif
2722

2723
#ifndef SHMEM
2724
    if (accelerated) then
×
2725
       call transform2 (g_work, agrs)
×
2726
    else
2727
       call transform2 (g_work, grs)
×
2728
    end if
2729

2730
    call zero_array(g_work)
×
2731
    do iglo=g_lo%llim_proc, g_lo%ulim_proc
×
2732
       ik = ik_idx(g_lo,iglo)
×
2733
       if (ik == 1) g_work(:,:,iglo) = gnew(:,:,iglo)
×
2734
    end do
2735

2736
    call g_adjust (gnew, phi, bpar, direction = to_g_gs2)
×
2737

2738
    if (accelerated) then
×
2739
       call transform2 (g_work, agzf)
×
2740
    else
2741
       call transform2 (g_work, gzf)
×
2742
    end if
2743
#else
2744
    if (accelerated) then
2745
       call transform2 (g0_ptr, agrs)
2746
    else
2747
       call transform2 (g0_ptr, grs)
2748
    end if
2749

2750
    g0_ptr = 0.0
2751
    do iglo=g_lo%llim_proc, g_lo%ulim_proc
2752
       ik = ik_idx(g_lo,iglo)
2753
       if (ik == 1) g0_ptr(:,:,iglo) = gnew(:,:,iglo)
2754
    end do
2755

2756
    call g_adjust (gnew, phi, bpar, direction = to_g_gs2)
2757

2758
    if (accelerated) then
2759
       call transform2 (g0_ptr, agzf)
2760
    else
2761
       call transform2 (g0_ptr, gzf)
2762
    end if
2763
#endif
2764

2765
    if (accelerated) then
×
2766
       do iaclo=accelx_lo%llim_world, accelx_lo%ulim_world
×
2767
          it = it_idx(accelx_lo, iaclo)
×
2768
          ik = ik_idx(accelx_lo, iaclo)
×
2769
          if (it == 1 .and. ik == 1) then
×
2770
             il = il_idx(accelx_lo, iaclo)
×
2771
             ig = 0
×
2772
             if (.not. forbid(ig,il)) then
×
2773
                ie = ie_idx(accelx_lo, iaclo)
×
2774
                is = is_idx(accelx_lo, iaclo)
×
2775

2776
                if (proc0) then
×
2777
                   if (.not. idx_local(accelx_lo, ik, it, il, ie, is)) then
×
2778
                      call receive (agp0, proc_id(accelx_lo, iaclo))
×
2779
                      call receive (agp0zf, proc_id(accelx_lo, iaclo))
×
2780
                   else
2781
                      agp0 = agrs(ig+ntgrid+1, :, iaclo)
×
2782
                      agp0zf = agzf(ig+ntgrid+1, :, iaclo)
×
2783
                   end if
2784
                else if (idx_local(accelx_lo, ik, it, il, ie, is)) then
×
2785
                   call send (agrs(ig+ntgrid+1, :, iaclo), 0)
×
2786
                   call send (agzf(ig+ntgrid+1, :, iaclo), 0)
×
2787
                end if
2788

2789
                if (proc0) then
×
2790
                   write (unit, "(6(1x,e13.6))") energy(ie), al(il), &
×
2791
                        agp0(1), agp0(2), agp0zf(1), agp0zf(2)
×
2792
                end if
2793
             end if
2794
          end if
2795
          call barrier
×
2796
       end do
2797
       deallocate(agp0, agp0zf)
×
2798
#ifndef SHMEM
2799
       deallocate(agrs, agzf)
×
2800
#else
2801
       call shm_free(agrs)
2802
       call shm_free(agzf)
2803
       call shm_free(g0_ptr)
2804
#endif
2805
    else
2806
       do iyxlo=yxf_lo%llim_world, yxf_lo%ulim_world
×
2807

2808
          ig = ig_idx(yxf_lo, iyxlo)
×
2809
          it = it_idx(yxf_lo, iyxlo)
×
2810
          if (ig == 0 .and. it == 1) then
×
2811
             il = il_idx(yxf_lo, iyxlo)
×
2812
             if (.not. forbid(ig,il)) then
×
2813
                ik = 1
×
2814
                ie = ie_idx(yxf_lo, iyxlo)
×
2815
                is = is_idx(yxf_lo, iyxlo)
×
2816
                isign = isign_idx(yxf_lo, iyxlo)
×
2817

2818
                if (proc0) then
×
2819
                   if (.not. idx_local(yxf_lo, ig, isign, it, il, ie, is)) then
×
2820
                      call receive (gp0, proc_id(yxf_lo, iyxlo))
×
2821
                      call receive (gp0zf, proc_id(yxf_lo, iyxlo))
×
2822
                   else
2823
                      gp0 = grs(ik, iyxlo)
×
2824
                      gp0zf = gzf(ik, iyxlo)
×
2825
                   end if
2826
                else if (idx_local(yxf_lo, ig, isign, it, il, ie, is)) then
×
2827
                   call send (grs(ik, iyxlo), 0)
×
2828
                   call send (gzf(ik, iyxlo), 0)
×
2829
                end if
2830

2831
                if (proc0) then
×
2832
                   write (unit, "(4(1x,e13.6),i8)") energy(ie), al(il), &
×
2833
                        gp0, gp0zf, isign
×
2834
                end if
2835
             end if
2836
          end if
2837
          call barrier
×
2838
       end do
2839
       deallocate (grs, gzf)
×
2840
    end if
2841

2842
    if (proc0) flush (unit)
×
2843

2844
    if (proc0) then
×
2845
       write(unit,*)
×
2846
    end if
2847

2848
  end subroutine do_write_fyx
×
2849
end module gs2_diagnostics
×
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