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

gyrokinetics / gs2 / 2078172070

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

push

gitlab-ci

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

5049 of 46599 relevant lines covered (10.83%)

119786.99 hits per line

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

0.0
/src/gs2_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, write_collisional
26
  logical :: write_omega, write_omavg, write_ascii, write_gs, write_ql_metric, write_moments
27
  logical :: write_g, write_gyx, write_eigenfunc, write_fields, write_final_fields
28
  logical :: write_final_antot, write_final_moments, write_parity, write_final_db
29
  logical :: write_moments_over_time, write_fluxes_by_energy, write_energy_exchange
30
  logical :: write_moments_by_mode
31
  logical :: write_cross_phase, write_final_epar, write_kpar, write_heating, write_lorentzian
32
  logical :: write_fluxes, write_fluxes_by_mode, write_kinetic_energy_transfer, write_verr
33
  logical :: write_cerr, exit_when_converged, use_nonlin_convergence, write_zonal_transfer
34
  logical :: save_for_restart, save_distfn, save_glo_info_and_grids, save_velocities
35
  logical :: write_symmetry, write_correlation_extend, write_correlation, make_movie
36
  logical :: write_nl_flux_dist, file_safety_check, append_old, make_restart_dir
37
  logical :: write_phi_over_time, write_apar_over_time, write_bpar_over_time, write_jext
38
  integer :: nwrite, nmovie, navg, nsave, igomega, nwrite_mult, nc_sync_freq
39

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

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

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

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

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

70
  real :: conv_test_multiplier
71

72
  integer :: nout = 1
73
  integer :: nout_movie = 1
74
  integer :: nout_big = 1
75
  complex :: wtmp_old = 0.
76

77
contains
78

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

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

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

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

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

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

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

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

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

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

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

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

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

204
    if (write_final_epar) then
×
205
       if (write_ascii) then
×
206
          write (report_unit, fmt="('write_final_epar = T:      E_parallel(theta) written to ',a)") trim(run_name)//'.epar'
×
207
       end if
208
       write (report_unit, fmt="('write_final_epar = T:      E_parallel(theta) written to ',a)") trim(run_name)//'.out.nc'
×
209
    end if
210

211
    if (write_fluxes) then
×
212
       if (write_ascii) then
×
213
          write (report_unit, fmt="('write_fluxes = T:         Phi**2(kx, ky) written to ',a)") trim(run_name)//'.out'
×
214
       end if
215
    else
216
       write (report_unit, fmt="('write_fluxes = F:         Phi**2(kx, ky) NOT written to ',a)") trim(run_name)//'.out'
×
217
    end if
218

219
    if (save_for_restart) then
×
220
       write (report_unit, fmt="('save_for_restart = T:      Restart files written to ',a)") trim(restart_file)//'.(PE)'
×
221
    else
222
       if (nonlin) then
×
223
          write (report_unit, *) 
×
224
          write (report_unit, fmt="('################# WARNING #######################')")
×
225
          write (report_unit, fmt="('save_for_restart = F:              This run cannot be continued.')")
×
226
          write (report_unit, fmt="('THIS IS PROBABLY AN ERROR.')") 
×
227
          write (report_unit, fmt="('################# WARNING #######################')")
×
228
          write (report_unit, *) 
×
229
       end if
230
    end if
231

232
    !Verify restart file can be written
233
    if((save_for_restart.or.save_distfn).and.(file_safety_check))then
×
234
       !Can we write file?
235
       writable=restart_writable()
×
236

237
       !If we can't write the restart file then we should probably quit
238
       if((.not.writable))then
×
239
          if(save_for_restart)then 
×
240
             write (report_unit, *) 
×
241
             write (report_unit, fmt="('################# WARNING #######################')")
×
242
             write (report_unit, fmt="('save_for_restart = T:   But we cannot write to a test file like ',A,'.')") trim(restart_file)
×
243
             write (report_unit, fmt="('THIS IS PROBABLY AN ERROR --> Check restart_dir.')") 
×
244
             write (report_unit, fmt="('################# WARNING #######################')")
×
245
             write (report_unit, *) 
×
246
          endif
247
          if(save_distfn)then 
×
248
             write (report_unit, *) 
×
249
             write (report_unit, fmt="('################# WARNING #######################')")
×
250
             write (report_unit, fmt="('save_distfn = T:   But we cannot write to a test file like ',A,'.')") trim(restart_file)
×
251
             write (report_unit, fmt="('THIS IS PROBABLY AN ERROR --> Check restart_dir.')") 
×
252
             write (report_unit, fmt="('################# WARNING #######################')")
×
253
             write (report_unit, *) 
×
254
          endif
255
       endif
256
    endif
257

258
  end subroutine check_gs2_diagnostics
×
259

260
  !> Initialise this module and all its dependencies, including defining NetCDF
261
  !> vars, call real_init, which calls read_parameters; broadcast all the
262
  !> different write flags.
263
  subroutine init_gs2_diagnostics (gs2_diagnostics_config_in, header)
×
264
    use kt_grids, only: ntheta0, naky
265
    use species, only: nspec
266
    use gs2_io, only: init_gs2_io
267
    use gs2_heating, only: init_htype
268
    use collisions, only: collision_model_switch, init_lorentz_error
269
    use collisions, only: collision_model_lorentz, collision_model_lorentz_test
270
    use mp, only: broadcast, mp_abort
271
    use diagnostics_final_routines, only: init_par_filter
272
    use diagnostics_velocity_space, only: init_weights, setup_legendre_transform
273
    use standard_header, only: standard_header_type
274
    implicit none
275
    !> Input parameters for this module
276
    type(diagnostics_config_type), intent(in), optional :: gs2_diagnostics_config_in
277
    !> Header for files with build and run information
278
    type(standard_header_type), intent(in), optional :: header
279
    ! Actual value for optional `header` input
280
    type(standard_header_type) :: local_header
×
281

282
    if (present(header)) then
×
283
      local_header = header
×
284
    else
285
      local_header = standard_header_type()
×
286
    end if
287

288
    if (initialized) return
×
289
    initialized = .true.
×
290

291
    call real_init (gs2_diagnostics_config_in, header=local_header)
×
292

293
    ! initialize weights for less accurate integrals used
294
    ! to provide an error estimate for v-space integrals (energy and untrapped)
295
    if (write_verr) then
×
296
       call init_weights
×
297
       call setup_legendre_transform
×
298
    end if
299

300
    ! allocate heating diagnostic data structures
301
    if (write_heating) then
×
302
       allocate (h_hist(0:navg-1))
×
303
       call init_htype (h_hist,  nspec)
×
304

305
       allocate (hk_hist(ntheta0,naky,0:navg-1))
×
306
       call init_htype (hk_hist, nspec)
×
307

308
       call init_htype (h,  nspec)
×
309

310
       allocate (hk(ntheta0, naky))
×
311
       call init_htype (hk, nspec)
×
312
    else
313
       allocate (h_hist(0))
×
314
       allocate (hk(1,1))
×
315
       allocate (hk_hist(1,1,0))
×
316
    end if
317

318
    !GGH Allocate density and velocity perturbation diagnostic structures
319
    if (write_jext) then
×
320
       allocate (j_ext_hist(ntheta0, naky,0:navg-1))
×
321
       j_ext_hist = 0
×
322
    end if
323

324
    call init_gs2_io (append_old, make_movie, nout, header=local_header)
×
325

326
    call broadcast (nout)
×
327

328
    if (write_cerr) then
×
329
       if (collision_model_switch == collision_model_lorentz .or. &
×
330
            collision_model_switch == collision_model_lorentz_test) then
331
          call init_lorentz_error
×
332
       else
333
          write_cerr = .false.
×
334
       end if
335
    end if
336

337
    call check_restart_file_writeable(file_safety_check, save_for_restart, save_distfn, &
338
         make_restart_dir)
×
339

340
    !Setup the parallel fft if we're writing/using the parallel spectrum
341
    if (write_kpar .or. write_gs) call init_par_filter
×
342
  end subroutine init_gs2_diagnostics
×
343

344
  !> Check if we can write the restart files
345
  !>
346
  !> If restart files aren't writable, aborts if `need_restart` is
347
  !> true, or sets `extra_files` to false. Also prints a warning in
348
  !> the second case.
349
  subroutine check_restart_file_writeable(check_writable, need_restart, extra_files, &
×
350
       create_restart_dir)
351
    use init_g, only: get_restart_dir
352
    use gs2_save, only: restart_writable
353
    use mp, only: proc0, mp_abort, broadcast
354
    use file_utils, only: mkdir
355
    implicit none
356
    !> Has the user requested this check
357
    logical, intent(in) :: check_writable
358
    !> Has the user requested restart files
359
    logical, intent(in) :: need_restart
360
    !> Has the user requested distribution function to be written
361
    logical, intent(inout) :: extra_files
362
    !> Do we want to try to create the restart dir if initial writes fail?
363
    logical, intent(inout) :: create_restart_dir
364

365
    ! Error message from trying to open restart file
366
    character(len=:), allocatable :: error_message
×
367
    ! GS2 error message to show user
368
    character(len=:), allocatable :: abort_message
×
369

370
    ! Assume everything's fine if we're not checking, or if it's not needed
371
    if (.not. check_writable) return
×
372
    if (.not. (need_restart .or. extra_files)) return
×
373

374
    ! If we can write the restart files, we're done
375
    if (restart_writable(error_message=error_message)) return
×
376

377
    if (create_restart_dir) then
×
378
       if (proc0) then
×
379
          write(*, '(A," (",A,") ",A)') "Initial attempt to write to restart_dir", trim(get_restart_dir()),"failed, attempting to create it."
×
380
          call mkdir(get_restart_dir())
×
381
       end if
382

383
       ! If we can now write the restart files, we're done
384
       if (restart_writable(error_message=error_message)) return
×
385
    end if
386

387
    abort_message = " Cannot write restart files! Error message was:" // new_line('a') &
388
         // "    " // error_message // new_line('a') &
389
         // " Please check that `init_g_knobs::restart_dir = " // trim(get_restart_dir()) &
390
         // "` exists and has the correct permissions."
×
391

392
    ! User has requested restart files, but we can't write them => abort
393
    if (need_restart) then
×
394
      abort_message = abort_message // new_line('a') // "    --> Aborting"
×
395
      call mp_abort(trim(abort_message), to_screen=.true.)
×
396
    end if
397

398
    ! If it's just a case of save_distfn, then we can carry on but
399
    ! disable `save_distfn` and print a useful mesasge
400
    if (extra_files) then
×
401
      if(proc0) write(*, '(a, a, a)') abort_message, new_line('a'), "    --> Setting `save_distfn = F`"
×
402
      extra_files = .false.
×
403
    endif
404
  end subroutine check_restart_file_writeable
×
405

406
  !> Read the input parameters; open the various text output files according to
407
  !> the relevant input flags; allocate and zero the module-level flux arrays,
408
  !> [[gs2_diagnostics_knobs:omega]] and [[gs2_diagnostics_knobs:omegaavg]]
409
  subroutine real_init(gs2_diagnostics_config_in, header)
×
410
    use run_parameters, only: has_apar
411
    use file_utils, only: open_output_file
412
    use kt_grids, only: naky, ntheta0
413
    use mp, only: proc0
414
    use standard_header, only: standard_header_type
415
    use diagnostics_fluxes, only: init_diagnostics_fluxes
416
    use diagnostics_kinetic_energy_transfer, only: init_diagnostics_kinetic_energy_transfer
417
    use diagnostics_nonlinear_convergence, only: init_nonlinear_convergence
418
    use collisional_heating, only: init_collisional
419
    use diagnostics_zonal_transfer, only: init_diagnostics_transfer
420
    implicit none
421
    !> Input parameters for this module
422
    type(diagnostics_config_type), intent(in), optional :: gs2_diagnostics_config_in
423
    !> Header for files with build and run information
424
    type(standard_header_type), intent(in), optional :: header
425
    ! Actual value for optional `header` input
426
    type(standard_header_type) :: local_header
×
427

428
    if (present(header)) then
×
429
      local_header = header
×
430
    else
431
      local_header = standard_header_type()
×
432
    end if
433

434
    call read_parameters(gs2_diagnostics_config_in)
×
435

436
    if (proc0) then
×
437
       if (write_ascii) then
×
438
          call open_output_file (out_unit, ".out")          
×
439
       end if
440

441
       if (write_cross_phase .and. write_ascii) then
×
442
          call open_output_file (phase_unit, ".phase")
×
443
       end if
444

445
       if (write_heating .and. write_ascii) then
×
446
          call open_output_file (heat_unit, ".heat")
×
447
          call open_output_file (heat_unit2, ".heat2")
×
448
       end if
449

450
       if (write_verr .and. write_ascii) then
×
451
          call open_output_file (res_unit, ".vres")
×
452
          call open_output_file (lpc_unit, ".lpc")
×
453
          call open_output_file (res_unit2, ".vres2")
×
454
       end if
455

456
       if (write_cerr .and. write_ascii) then
×
457
          call open_output_file (cres_unit, ".cres")
×
458
       end if
459

460
       if (write_parity .and. write_ascii) then
×
461
          call open_output_file (parity_unit, ".parity")
×
462
       end if
463

464
       if (write_g .and. write_ascii) then
×
465
          call open_output_file(dist_unit, ".dist")
×
466
       end if
467

468
       if (write_gyx .and. write_ascii) then
×
469
          call open_output_file(yxdist_unit, ".yxdist")
×
470
       end if
471

472
       !GGH J_external, only if A_parallel is being calculated.
473
       if (write_jext .and. has_apar) then
×
474
          if (write_ascii) then
×
475
             call open_output_file (jext_unit, ".jext")
×
476
          end if
477
       else
478
          write_jext = .false.
×
479
       end if
480

481
       if (write_ascii) then
×
482
          write (unit=out_unit, fmt='(a)') local_header%to_string(file_description="GS2 output file")
×
483
       end if
484

485
       allocate (omegahist(0:navg-1,ntheta0,naky))
×
486
       omegahist = 0.0
×
487
       if (use_nonlin_convergence) call init_nonlinear_convergence(conv_nstep_av, nwrite)
×
488

489
    end if
490

491
    ! Needed to allow us to use common_calculate_fluxes later
492
    call init_diagnostics_fluxes()
×
493
    if (write_collisional) call init_collisional
×
494
    if (write_zonal_transfer) call init_diagnostics_transfer
×
495
    if (write_kinetic_energy_transfer) call init_diagnostics_kinetic_energy_transfer
×
496
    if (.not. allocated(omega)) then
×
497
       allocate(omega(ntheta0, naky))
×
498
       allocate(omegaavg(ntheta0, naky))
×
499
       omega=0
×
500
       omegaavg=0
×
501
    end if
502

503
  end subroutine real_init
×
504

505
  !> Read the input parameters for the diagnostics module
506
  subroutine read_parameters (gs2_diagnostics_config_in, warn_nonfunctional)
×
507
    use diagnostics_configuration, only: warn_about_nonfunctional_selection, diagnostics_config, check_and_disable_flags
508
    use optionals, only: get_option_with_default
509
    implicit none
510
    !> Configuration for this module, can be used to set new default values or
511
    !> avoid reading the input file
512
    type(diagnostics_config_type), intent(in), optional :: gs2_diagnostics_config_in
513
    logical, intent(in), optional :: warn_nonfunctional
514
    if (present(gs2_diagnostics_config_in)) diagnostics_config = gs2_diagnostics_config_in
×
515

516
    call diagnostics_config%init(name = 'gs2_diagnostics_knobs', requires_index = .false.)
×
517

518
    ! Print some health warnings if switches are not their default
519
    ! values and are not available in this diagnostics module
520
    if (get_option_with_default(warn_nonfunctional, .true.)) then
×
521
       call warn_about_nonfunctional_selection(.not. diagnostics_config%write_any, "write_any")
×
522
    end if
523

524
    ! Turn off diagnostics which aren't sensible with setup
525
    call check_and_disable_flags(diagnostics_config)
×
526

527
    ! Copy out internal values into module level parameters
528
    associate(self => diagnostics_config)
529
#include "diagnostics_copy_out_auto_gen.inc"
530
    end associate
531

532
    write_any = write_line .or. write_omega     .or. write_omavg &
533
         .or. write_flux_line .or. write_fluxes  &
534
         .or. write_kpar   .or. write_heating     .or. write_lorentzian  .or. write_gs
×
535
    write_any_fluxes = write_flux_line .or. print_flux_line .or. write_fluxes .or. write_fluxes_by_mode
×
536
  end subroutine read_parameters
×
537

538
  subroutine do_final_gs2_diagnostics
×
539
    use mp, only: proc0
540
    use fields_arrays, only: phinew, bparnew
541
    use antenna, only: dump_ant_amp
542
    use gs2_time, only: user_time
543
    use unit_tests, only: debug_message
544
    use diagnostics_final_routines, only: do_write_final_fields, do_write_kpar
545
    use diagnostics_final_routines, only: do_write_final_epar, do_write_final_db
546
    use diagnostics_final_routines, only: do_write_final_antot, do_write_final_moments
547
    use diagnostics_final_routines, only: do_write_gs
548
    use diagnostics_velocity_space, only: collision_error
549
    use diagnostics_fields, only: get_phi0
550
    implicit none
551

552
    call debug_message(3, 'gs2_diagnostics::final_gs2_diagnostics &
553
         & starting')
×
554

555
    if (write_gyx) call do_write_fyx (yxdist_unit, phinew, bparnew)
×
556
    if (write_g) call do_write_f (dist_unit)
×
557
    if (write_cerr) call collision_error (cres_unit, phinew, bparnew)
×
558

559
    if (proc0) then
×
560
       if (write_eigenfunc) call do_write_eigenfunc(get_netcdf_file_id(), write_ascii)
×
561
       if (write_final_fields) call do_write_final_fields(write_ascii, &
×
562
            file_id=get_netcdf_file_id())
×
563
       if (write_kpar) call do_write_kpar(write_ascii)
×
564
       if (write_final_epar) call do_write_final_epar(write_ascii, &
×
565
            file_id=get_netcdf_file_id())
×
566

567
       ! definition here assumes we are not using wstar_units
568
       if (write_final_db) call do_write_final_db(write_ascii)
×
569
    end if
570

571
    !Note pass in phase factor phi0 which may not be initialised
572
    !this is ok as phi0 will be set in routine if not already set
573
    if (write_final_moments) call do_write_final_moments(get_phi0(), &
×
574
         use_normalisation=write_eigenfunc, write_text=write_ascii, &
575
         file_id=get_netcdf_file_id())
×
576

577
    if (write_final_antot) call do_write_final_antot(write_ascii, &
×
578
         file_id=get_netcdf_file_id())
×
579

580
    call save_restart_dist_fn(save_for_restart, save_distfn, &
581
                              save_glo_info_and_grids=save_glo_info_and_grids, &
582
                              save_velocities=save_velocities, &
583
                              user_time=user_time)
×
584

585
    if (proc0) call dump_ant_amp
×
586

587
    if (write_gs) call do_write_gs(write_ascii)
×
588

589
    if (proc0) call do_write_geom
×
590
  end subroutine do_final_gs2_diagnostics
×
591

592
  !> Finalise the diagnostics module, writing final timestep diagnostics and
593
  !> closing any open files
594
  subroutine finish_gs2_diagnostics
×
595
    use gs2_io, only: nc_finish, get_netcdf_file_id
596
    use diagnostics_velocity_space, only: finish_legendre_transform, finish_weights
597
    if (.not. initialized) return
×
598
    ! Close some of the open ascii output files
599
    call close_files
×
600
    !Finalise the netcdf file
601
    call nc_finish(get_netcdf_file_id())
×
602
    !Now tidy up
603
    call deallocate_arrays
×
604
    if (write_verr) then
×
605
       call finish_weights
×
606
       call finish_legendre_transform
×
607
    end if
608
    wtmp_old = 0. ; nout = 1 ; nout_movie = 1 ; nout_big = 1
×
609
    initialized = .false.
×
610
  end subroutine finish_gs2_diagnostics
611

612
  !> Save some extra information in final restart files
613
  subroutine save_restart_dist_fn(save_for_restart, save_distfn, &
×
614
                                  save_glo_info_and_grids, &
615
                                  save_velocities, user_time, fileopt_base)
616
    use run_parameters, only: has_phi, has_apar, has_bpar
617
    use collisions, only: vnmult
618
    use gs2_save, only: gs2_save_for_restart
619
    use gs2_time, only: code_dt, code_dt_prev1, code_dt_prev2, code_dt_max
620
    use fields_arrays, only: phinew, bparnew
621
    use dist_fn_arrays, only: gnew, g_adjust, to_g_gs2, from_g_gs2
622
    use optionals, only: get_option_with_default
623
    !> See [[gs2_diagnostics_knobs:save_for_restart]]
624
    logical, intent(in) :: save_for_restart
625
    !> See [[gs2_diagnostics_knobs:save_distfn]]
626
    logical, intent(in) :: save_distfn
627
    !> See [[gs2_diagnostics_knobs:save_glo_info_and_grids]]
628
    logical, intent(in) :: save_glo_info_and_grids
629
    !> See [[gs2_diagnostics_knobs:save_velocities]]
630
    logical, intent(in) :: save_velocities
631
    !> Current simulation time
632
    real, intent(in) :: user_time
633
    !> Optional string to add to file name
634
    character(len=*), intent(in), optional :: fileopt_base
635
    character(len=:), allocatable :: fileopt
×
636

637
    fileopt = get_option_with_default(fileopt_base, "")
×
638

639
    if (save_for_restart) then
×
640
       call gs2_save_for_restart(gnew, user_time, vnmult, &
641
            has_phi, has_apar, has_bpar, &
642
            code_dt, code_dt_prev1, code_dt_prev2, code_dt_max, &
643
            save_glo_info_and_grids=save_glo_info_and_grids, &
644
            save_velocities=save_velocities, &
645
            fileopt = fileopt)
×
646
    end if
647

648
    if (save_distfn) then
×
649
       !Convert h to distribution function
650
       call g_adjust(gnew, phinew, bparnew, direction = from_g_gs2)
×
651

652
       !Save dfn, fields and velocity grids to file
653
       call gs2_save_for_restart(gnew, user_time, vnmult, &
654
            has_phi, has_apar, has_bpar, &
655
            code_dt, code_dt_prev1, code_dt_prev2, code_dt_max, &
656
            fileopt= fileopt//".dfn", &
657
            save_glo_info_and_grids=save_glo_info_and_grids, &
658
            save_velocities=save_velocities)
×
659

660
       !Convert distribution function back to h
661
       call g_adjust(gnew, phinew, bparnew, direction = to_g_gs2)
×
662
    end if
663
  end subroutine save_restart_dist_fn
×
664

665
  !> Deallocate the [[gs2_diagnostics]] module-level arrays
666
  subroutine deallocate_arrays
×
667
    use mp, only: proc0
668
    use gs2_heating, only: del_htype
669
    use diagnostics_fluxes, only: finish_diagnostics_fluxes
670
    use diagnostics_kinetic_energy_transfer, only: finish_diagnostics_kinetic_energy_transfer
671
    use diagnostics_nonlinear_convergence, only: finish_nonlinear_convergence
672
    use collisional_heating, only: finish_collisional
673
    use diagnostics_zonal_transfer, only: finish_diagnostics_transfer
674
    implicit none
675

676
    if (write_heating) then
×
677
       call del_htype (h)
×
678
       call del_htype (h_hist)
×
679
       call del_htype (hk_hist)
×
680
       call del_htype (hk)
×
681
    end if
682

683
    call finish_diagnostics_fluxes()
×
684
    call finish_diagnostics_kinetic_energy_transfer()
×
685
    call finish_collisional
×
686
    call finish_diagnostics_transfer
×
687
    if (allocated(h_hist)) deallocate (h_hist, hk_hist, hk)
×
688
    if (allocated(j_ext_hist)) deallocate (j_ext_hist)
×
689
    if (proc0 .and. allocated(omegahist)) deallocate (omegahist)
×
690

691
    if (allocated(omega)) deallocate(omega, omegaavg)
×
692
    if (use_nonlin_convergence) call finish_nonlinear_convergence
×
693

694
    if (proc0 .and. allocated(domega)) deallocate(domega)
×
695
  end subroutine deallocate_arrays
×
696

697
  !> Close various text output files
698
  subroutine close_files
×
699
    use file_utils, only: close_output_file
700
    use mp, only: proc0
701
    implicit none
702

703
    if(.not.proc0) return
×
704
    if (write_ascii .and. write_parity) call close_output_file (parity_unit)
×
705
    if (write_ascii .and. write_verr) then
×
706
       call close_output_file (res_unit)
×
707
       call close_output_file (lpc_unit)
×
708
       call close_output_file (res_unit2)
×
709
    end if
710
    if (write_ascii .and. write_cerr) call close_output_file(cres_unit)
×
711
    if (write_ascii .and. write_g) call close_output_file(dist_unit)
×
712
    if (write_ascii .and. write_gyx) call close_output_file(yxdist_unit)
×
713
    if (write_ascii) call close_output_file (out_unit)
×
714
    if (write_ascii .and. write_cross_phase) call close_output_file (phase_unit)
×
715
    if (write_ascii .and. write_heating) call close_output_file (heat_unit)
×
716
    if (write_ascii .and. write_heating) call close_output_file (heat_unit2)
×
717
    if (write_ascii .and. write_jext) call close_output_file (jext_unit)
×
718
  end subroutine close_files
719

720
  !> Calculate and write the various diagnostic quantities.
721
  !>
722
  !> This is the main routine for the "old" diagnostics.
723
  subroutine loop_diagnostics (istep, exit, debopt, force)
×
724
    use, intrinsic :: iso_fortran_env, only: output_unit
725
    use species, only: spec, has_electron_species
726
    use kt_grids, only: naky, ntheta0
727
    use run_parameters, only: nstep, has_phi, has_apar, has_bpar
728
    use fields_arrays, only: phinew, bparnew
729
    use collisions, only: ncheck, vary_vnew
730
    use mp, only: proc0, broadcast
731
    use gs2_time, only: user_time
732
    use gs2_io, only: nc_final_fields, nc_sync, nc_write_lorentzian
733
    use antenna, only: antenna_w
734
    use optionals, only: get_option_with_default
735
    use diagnostics_printout, only: write_phi_fluxes_to_unit, write_fluxes_to_unit
736
    use diagnostics_fluxes, only: calculate_fluxes, species_energy_exchange, &
737
         species_es_heat_flux, species_apar_heat_flux, species_bpar_heat_flux, &
738
         species_es_particle_flux, species_apar_particle_flux, species_bpar_particle_flux, &
739
         species_es_momentum_flux, species_heat_flux, species_particle_flux
740
    use diagnostics_velocity_space, only: collision_error
741
    use optionals, only: get_option_with_default
742
    use warning_helpers, only: is_not_zero, not_exactly_equal
743
    use collisional_heating, only: write_coll_heat => write_collisional, calculate_collisional
744
    use diagnostics_zonal_transfer, only: write_zonal_trans => write_zonal_transfer, calculate_zonal_transfer
745
    implicit none
746
    !> Current timestep
747
    integer, intent (in) :: istep
748
    !> If true, simulation should stop (for example, because it has converged)
749
    logical, intent (out) :: exit
750
    !> If true, turn on some debug prints
751
    logical, intent (in), optional:: debopt
752
    logical, intent(in), optional :: force
753
    real, dimension (ntheta0, naky) :: phitot
×
754
    complex :: wtmp_new
755
    integer :: ik, it, write_mod
756
    real :: phi2, apar2, bpar2, t
757
    logical :: do_force, debug
758
    real, save :: t_old = 0.
759
    integer, save :: istep_last = -1
760
    debug = get_option_with_default(debopt, .false.)
×
761

762
    !Set the current time
763
    t = user_time
×
764
    !Always skip if we've already done this step
765
    if (istep == istep_last) return
×
766

767
    do_force = get_option_with_default(force, .false.)
×
768

769
    exit = .false.
×
770

771
    call do_get_omega(istep,debug,exit)
×
772

773
    if (write_heating) call heating (istep, navg, h, hk, h_hist, hk_hist)
×
774

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

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

779
    if (vary_vnew) then
×
780
       write_mod = mod(istep,ncheck)
×
781
    else
782
       write_mod = mod(istep,nwrite)
×
783
    end if
784

785
    if (write_verr .and. write_mod == 0) call do_write_verr
×
786

787
    if (debug) write(6,*) "loop_diagnostics: call update_time"
×
788

789
    !########################################################
790
    !The rest of the routine only happens every nwrite steps
791
    !########################################################
792
    if (mod(istep,nwrite) /= 0 .and. .not. exit .and. .not. do_force) return
×
793

794
    ! If we get here then we're doing a full set of diagnostics
795
    ! so store the step
796
    istep_last = istep
×
797

798
    if (write_g) call do_write_f (dist_unit)
×
799

800
    ! Note this also returns phi2, apar2, bpar2 and phitot for other diagnostics
801
    if (proc0) call do_write_ncloop(t, istep, phi2, apar2, bpar2, phitot)
×
802

803
    if (print_line) call do_print_line(phitot)
×
804

805
    if (write_moments) call do_write_moments
×
806

807
    if (write_cross_phase .and. has_electron_species(spec) .and. write_ascii) call do_write_crossphase(t)
×
808

809
    !###########################
810
    ! The following large section could do with being moved to separate routines but
811
    !     at the moment its all quite interlinked which makes this hard.
812
    !###########################
813

814
    if (debug) write(6,*) "loop_diagnostics: -1"
×
815

816
    if (write_any_fluxes) then
×
817
       call calculate_fluxes(get_netcdf_file_id(), nout, write_fluxes, write_fluxes_by_mode, &
818
            write_energy_exchange, write_fluxes_by_energy)
×
819
    end if
820

821
    if (proc0 .and. print_flux_line) then
×
822
       if (has_phi) call write_phi_fluxes_to_unit(output_unit, t, phi2, &
×
823
            species_es_heat_flux, species_energy_exchange)
×
824
       if (has_apar) call write_fluxes_to_unit(output_unit, t, apar2, "apar", &
×
825
            species_apar_heat_flux)
×
826
       if (has_bpar) call write_fluxes_to_unit(output_unit, t, bpar2, "bpar", &
×
827
            species_bpar_heat_flux)
×
828
    end if
829

830
    ! Check for convergence
831
    if (use_nonlin_convergence) call check_nonlin_convergence(istep, &
×
832
         species_es_heat_flux(1), exit)
×
833
    if (debug) write(6,*) "loop_diagnostics: -1"
×
834

835
    if (.not. write_any) then
×
836
       ! We have to increment the number of outputs written to file
837
       ! before leaving. Usually we do this at the end of the routine
838
       ! so we must make sure we do this here before leaving early.
839
       nout = nout + 1
×
840
       return
×
841
    end if
842

843
    if (debug) write(output_unit, *) "loop_diagnostics: -2"
×
844

845
    if (proc0 .and. write_any) then
×
846
       if (write_ascii) then
×
847
         write (unit=out_unit, fmt=*) 'time=', t
×
848
         if (write_heating) call do_write_heating(t, heat_unit, heat_unit2, h)
×
849
         if (write_jext) call do_write_jext(t,istep)
×
850
       end if
851

852
       if (write_flux_line .and. write_ascii) then
×
853
          if (has_phi) call write_phi_fluxes_to_unit(out_unit, t, phi2, &
×
854
               species_es_heat_flux, species_energy_exchange, species_es_particle_flux, &
855
               species_es_momentum_flux)
×
856

857
          if (write_lorentzian) then
×
858
             wtmp_new = antenna_w()
×
859
             call nc_write_lorentzian(get_netcdf_file_id(), nout, wtmp_new)
×
860

861
             if (is_not_zero(real(wtmp_old)) .and. not_exactly_equal(wtmp_new, wtmp_old)) &
×
862
                  write (unit=out_unit, fmt="('w= ',e17.10, ' amp= ',e17.10)") real(wtmp_new), sqrt(2.*apar2)
×
863
             wtmp_old = wtmp_new
×
864
          end if
865
          
866
          if (has_apar) call write_fluxes_to_unit(out_unit, t, apar2, "apar", &
×
867
               species_apar_heat_flux, species_apar_particle_flux)
×
868
          
869
          if (has_bpar) call write_fluxes_to_unit(out_unit, t, bpar2, "bpar", &
×
870
               species_bpar_heat_flux, species_bpar_particle_flux)
×
871

872
          write (unit=out_unit, fmt="('t= ',e17.10,' h_tot= ',e11.4, ' z_tot= ',e11.4)") t, sum(species_heat_flux), sum(species_particle_flux * spec%z)
×
873
       end if
874

875
       if (write_ascii) then
×
876
          do ik = 1, naky
×
877
             do it = 1, ntheta0
×
878
                if (write_line) call do_write_line(t,it,ik,phitot(it,ik))
×
879
                if (write_omega) call do_write_omega(it,ik)
×
880
                if (write_omavg) call do_write_omavg(it,ik)
×
881
             end do
882
          enddo
883
       end if
884
    endif
885

886
    if (write_cerr) call collision_error(cres_unit, phinew, bparnew)
×
887

888
    if (write_nl_flux_dist) call do_write_nl_flux_dist(get_netcdf_file_id(), nout)
×
889

890
    if (write_kinetic_energy_transfer) call do_write_kinetic_energy_transfer(get_netcdf_file_id(), nout)
×
891

892
    if (write_symmetry) call do_write_symmetry(get_netcdf_file_id(), nout)
×
893

894
    if (write_correlation) call do_write_correlation(get_netcdf_file_id(), nout)
×
895

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

899
    if (write_parity) call do_write_parity(t, parity_unit, write_ascii)
×
900

901
    if (write_collisional) then
×
902
       call calculate_collisional()
×
903
       call write_coll_heat(get_netcdf_file_id(), nout)
×
904
    end if
905

906
    if (write_zonal_transfer) then
×
907
       call calculate_zonal_transfer
×
908
       call write_zonal_trans(get_netcdf_file_id(), nout)
×
909
    end if
910

911
    !Now sync the data to file (note doesn't actually sync every call)
912
    if (proc0) call nc_sync(get_netcdf_file_id(), nout, nc_sync_freq)
×
913

914
    !Increment loop counter
915
    nout = nout + 1
×
916

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

919
    !Update time
920
    t_old = t
×
921

922
    if (debug) write(6,*) "loop_diagnostics: done"
×
923
  end subroutine loop_diagnostics
924

925
  !> Calculate [[gs2_diagnostics_knobs:omegaavg]] for linear simulations or if
926
  !> [[kt_grids:eqzip]] is on; otherwise set
927
  !> [[gs2_diagnostics_knobs:omega]] and [[gs2_diagnostics_knobs:omegaavg]] to
928
  !> zero
929
  subroutine do_get_omega(istep,debug,exit)
×
930
    use mp, only: proc0, broadcast
931
    use nonlinear_terms, only: nonlin
932
    use kt_grids, only: ieqzip
933
    implicit none
934
    !> The current timestep
935
    integer, intent(in) :: istep
936
    !> Turn on some debug messages
937
    logical, intent(in) :: debug
938
    !> Returns true if the simulation has converged (see
939
    !> [[gs2_diagnostics_knobs:omegatol]]) or if a numerical instability has
940
    !> occurred (see [[gs2_diagnostics_knobs:omegainst]]).
941
    logical, intent(inout) :: exit
942

943
    if (nonlin .and. .not. any(ieqzip)) then
×
944
       !Make sure we've at least initialised the omega arrays
945
       !for any later output etc.
946
       omega = 0.
×
947
       omegaavg = 0.
×
948
    else
949
       if (proc0) then
×
950
          if (debug) write(6,*) "loop_diagnostics: proc0 call get_omegaavg"
×
951
          call get_omegaavg (istep, exit, omegaavg, debug)
×
952
          if (debug) write(6,*) "loop_diagnostics: proc0 done called get_omegaavg"
×
953
       endif
954
       call broadcast (exit)
×
955
    end if
956

957
  end subroutine do_get_omega
×
958

959
  !> Compute volume averages of the fields and write the fields, field averages,
960
  !> heating and frequency to the netCDF files
961
  subroutine do_write_ncloop(time, istep, phi2, apar2, bpar2, phitot)
×
962
    use gs2_time, only: woutunits, tunits
963
    use gs2_io, only: nc_loop
964
    use diagnostics_printout, only: phinorm
965
    use mp, only: proc0
966
    use kt_grids, only: ntheta0, naky
967
    implicit none
968
    !> Simulation time
969
    real, intent(in) :: time
970
    !> Current timestep
971
    integer, intent(in) :: istep
972
    !> Fields squared
973
    real, intent(out) :: phi2, apar2, bpar2
974
    !> FIXME: add documentation. Needs [[phinorm]] documenting
975
    real, dimension (:, :), intent(out) :: phitot
976
    real, dimension (ntheta0, naky) :: ql_metric, growth_rates
×
977
    phitot = 0.0
×
978
    if (.not. proc0) return
×
979

980
    omega = omegahist(mod(istep,navg),:,:)
×
981

982
    call phinorm (phitot)
×
983

984
    if (write_ql_metric) then
×
985
       ! Calculate the instantaneous omega and keep the growth rate.
986
       growth_rates = aimag(calculate_instantaneous_omega())
×
987
       ql_metric = calculate_simple_quasilinear_flux_metric_by_k(growth_rates)
×
988
    else
989
       ql_metric = 0.0
×
990
    end if
991

992
    call nc_loop (get_netcdf_file_id(), nout, time, phi2, apar2, bpar2, igomega, &
993
         h, hk, omega, omegaavg, woutunits, tunits, phitot, ql_metric, write_omega, &
×
994
         write_heating, write_ql_metric, write_phi_over_time, write_apar_over_time, &
995
         write_bpar_over_time)
×
996
  end subroutine do_write_ncloop
997

998
  !> Write \(\phi, A_\parallel, B_\parallel\) normalised to the value of
999
  !> \(\phi\) at the outboard midplane
1000
  !>
1001
  !> Writes to text file `<runname>.eigenfunc` and/or netCDF
1002
  subroutine do_write_eigenfunc(file_id, write_text)
×
1003
    use mp, only: proc0
1004
    use file_utils, only: open_output_file, close_output_file
1005
    ! This renaming seems needed to avoid an issue with ifx
1006
    use diagnostics_fields, only: write_eigenfunc_ => write_eigenfunc
1007
    implicit none
1008
    !> NetCDF ID of the file to write to
1009
    integer, intent(in) :: file_id
1010
    !> If true, write text file
1011
    logical, intent(in) :: write_text
1012
    integer :: unit
1013
    if (.not. proc0) return
×
1014
    if (write_text) call open_output_file (unit, ".eigenfunc")
×
1015
    call write_eigenfunc_(write_text, unit, file_id)
×
1016
    if (write_text) close(unit)
×
1017
  end subroutine do_write_eigenfunc
1018

1019
  !> Write some geometry information to text file `<runname>.g`
1020
  subroutine do_write_geom
×
1021
    use mp, only: proc0
1022
    use file_utils, only: open_output_file, close_output_file
1023
    use theta_grid, only: ntgrid, theta, Rplot, Zplot, aplot, Rprime, Zprime, aprime, drhodpsi, qval, shape
1024
    implicit none
1025
    integer :: i, unit
1026

1027
    if(.not.proc0) return
×
1028

1029
    !May want to guard this with if(write_ascii) but not until we provide this
1030
    !data in main netcdf output by default.
1031
    call open_output_file (unit, ".g")
×
1032
    write (unit,fmt="('# shape: ',a)") trim(shape)
×
1033
    write (unit,fmt="('# q = ',e11.4,' drhodpsi = ',e11.4)") qval, drhodpsi
×
1034
    write (unit,fmt="('# theta1             R2                  Z3               alpha4      ', &
1035
         &   '       Rprime5              Zprime6           alpha_prime7 ')")
×
1036
    do i=-ntgrid,ntgrid
×
1037
       write (unit,1000) theta(i),Rplot(i),Zplot(i),aplot(i), &
×
1038
            Rprime(i),Zprime(i),aprime(i)
×
1039
    enddo
1040
    call close_output_file (unit)
×
1041
1000 format(20(1x,1pg18.11))
1042
  end subroutine do_write_geom
1043

1044
  !> Transform \(\phi, A_\parallel, B_\parallel\) to real space, then write to netCDF
1045
  subroutine do_write_movie(time)
×
1046
    use gs2_io, only: nc_loop_movie, get_netcdf_file_id
1047
    use mp, only: proc0
1048
    implicit none
1049
    !> Current simulation time
1050
    real, intent(in) :: time
1051
    if (proc0) call nc_loop_movie(get_netcdf_file_id(), nout_movie, time)
×
1052
    nout_movie = nout_movie + 1
×
1053
  end subroutine do_write_movie
×
1054

1055
  !> Print estimated frequencies and growth rates to screen/stdout
1056
  subroutine do_print_line(phitot)
×
1057
    use mp, only: proc0
1058
    use kt_grids, only: naky, ntheta0, aky, akx, theta0
1059
    use gs2_time, only: woutunits
1060
    implicit none
1061
    !> Total magnitude of all the fields
1062
    real, dimension (:, :), intent(in) :: phitot
1063
    integer :: ik, it
1064

1065
    if(.not.proc0) return
×
1066
    do ik = 1, naky
×
1067
       do it = 1, ntheta0
×
1068
          write (unit=*, fmt="('ky=',1pe9.2, ' kx=',1pe9.2, &
1069
               & ' om=',e9.2,1x,e9.2,' omav=',e9.2,1x,e9.2, &
1070
               & ' phtot=',e9.2,' theta0=',1pe9.2)") &
×
1071
               aky(ik), akx(it), &
×
1072
               real( omega(it,ik)*woutunits(ik)), &
×
1073
               aimag(omega(it,ik)*woutunits(ik)), &
×
1074
               real( omegaavg(it,ik)*woutunits(ik)), &
×
1075
               aimag(omegaavg(it,ik)*woutunits(ik)), &
×
1076
               phitot(it,ik), theta0(it,ik)
×
1077
       end do
1078
    end do
1079
    write (*,*) 
×
1080
  end subroutine do_print_line
1081

1082
  !> Calculate and write the time-averaged antenna current to [[jext_unit]]
1083
  subroutine do_write_jext(time, istep)
×
1084
    use kt_grids, only: ntheta0, naky
1085
    use mp, only: proc0
1086
    use warning_helpers, only: is_not_zero
1087
    use gs2_io, only: nc_write_jext
1088
    implicit none
1089
    !> Current simulation time
1090
    real, intent(in) :: time
1091
    !> Current timestep
1092
    integer, intent(in) :: istep
1093
    integer :: ik, it
1094
    real, dimension(:,:), allocatable ::  j_ext
×
1095

1096
    if (.not. proc0) return
×
1097
    allocate (j_ext(ntheta0, naky)); j_ext=0.
×
1098
    call calc_jext(istep, j_ext)
×
1099
    call nc_write_jext(get_netcdf_file_id(), nout, j_ext)
×
1100
    if (.not. write_ascii) return
×
1101

1102
    do ik=1,naky
×
1103
       do it = 1, ntheta0
×
1104
          if (is_not_zero(j_ext(it, ik))) then
×
1105
             write (unit=jext_unit, fmt="(es12.4,i4,i4,es12.4)")  &
1106
                  time,it,ik,j_ext(it,ik)
×
1107
          endif
1108
       enddo
1109
    enddo
1110
    deallocate(j_ext)
×
1111
  end subroutine do_write_jext
×
1112

1113
  !> Write various moments to netCDF
1114
  subroutine do_write_moments
×
1115
    use diagnostics_moments, only: write_moments
1116
    implicit none
1117
    call write_moments(get_netcdf_file_id(), nout, igomega, write_moments_over_time, &
1118
         write_moments_by_mode)
×
1119
  end subroutine do_write_moments
×
1120

1121
  !> Calculate the cross-phase (see [[get_cross_phase]]) and write to the
1122
  !> [[phase_unit]] file
1123
  subroutine do_write_crossphase(time)
×
1124
    use mp, only: proc0
1125
    use diagnostics_turbulence, only: get_cross_phase
1126
    use gs2_io, only: nc_write_cross_phase
1127
    implicit none
1128
    !> Current simulation time
1129
    real, intent(in) :: time
1130
    real :: phase_tot, phase_theta
1131
    call get_cross_phase (phase_tot, phase_theta)
×
1132
    if (.not. proc0) return
×
1133
    if (write_ascii) write (unit=phase_unit, &
×
1134
         fmt="('t= ',e17.10,' phase_tot= ',e11.4,' phase_theta= ',e11.4)") &
1135
         time, phase_tot, phase_theta
×
1136
    call nc_write_cross_phase(get_netcdf_file_id(), nout, phase_theta, phase_tot)
×
1137
  end subroutine do_write_crossphase
1138

1139
  !> Write estimated frequency and growth rates to [[out_unit]] for an individual \((k_y, \theta)\) point
1140
  subroutine do_write_line(time,it,ik,phitot)
×
1141
    use kt_grids, only: aky, akx, theta0
1142
    use gs2_time, only: woutunits
1143
    implicit none
1144
    !> Simulation time
1145
    real, intent(in) :: time, phitot
1146
    !> \(k_y\)- and \(\theta\)-indices
1147
    integer, intent(in) :: ik, it
1148
    if (.not. write_ascii) return
×
1149
    write (out_unit, "('t= ',e17.10,' aky= ',1p,e12.4, ' akx= ',1p,e12.4, &
1150
         &' om= ',1p,2e12.4,' omav= ', 1p,2e12.4,' phtot= ',1p,e12.4,' theta0= ',1p,e12.4)") &
1151
         time, aky(ik), akx(it), &
×
1152
         real( omega(it,ik)*woutunits(ik)), &
×
1153
         aimag(omega(it,ik)*woutunits(ik)), &
×
1154
         real( omegaavg(it,ik)*woutunits(ik)), &
×
1155
         aimag(omegaavg(it,ik)*woutunits(ik)), &
×
1156
         phitot,theta0(it,ik)
×
1157
  end subroutine do_write_line
1158

1159
  !> Write instantaneous growth rate and frequency to [[out_unit]] for an individual \((k_y, \theta)\) point
1160
  subroutine do_write_omega(it,ik)
×
1161
    use gs2_time, only: tunits, woutunits
1162
    implicit none
1163
    !> \(k_y\)- and \(\theta\)-indices
1164
    integer, intent(in) :: it, ik
1165
    if (.not. write_ascii) return
×
1166
    write (out_unit,&
1167
         fmt='(" omega= (",1p,e12.4,",",1p,e12.4,")",t45,"omega/(vt/a)= (",1p,e12.4,",",1p,e12.4,")")') &
1168
         omega(it,ik)/tunits(ik), omega(it,ik)*woutunits(ik)
×
1169
  end subroutine do_write_omega
1170

1171
  !> Write time-averaged growth rate and frequency to [[out_unit]] for an individual \((k_y, \theta)\) point
1172
  subroutine do_write_omavg(it,ik)
×
1173
    use gs2_time, only: tunits, woutunits
1174
    implicit none
1175
    integer, intent(in) :: it, ik
1176
    if (.not. write_ascii) return
×
1177
    write (out_unit,&
1178
         fmt='(" omavg= (",1p,e12.4,",",1p,e12.4,")",t45,"omavg/(vt/a)= (",1p,e12.4,",",1p,e12.4,")")') &
1179
         omegaavg(it,ik)/tunits(ik), omegaavg(it,ik)*woutunits(ik)               
×
1180
  end subroutine do_write_omavg
1181

1182
  !> Write some error estimates.
1183
  !>
1184
  !> Error estimates are calculated by:
1185
  !> - comparing standard integral with less-accurate integral
1186
  !> - monitoring amplitudes of legendre polynomial coefficients
1187
  !>
1188
  !> Only writes to text file, requires [[lpc_unit]] to be `open`
1189
  subroutine do_write_verr
×
1190
    use mp, only: proc0
1191
    use le_grids, only: grid_has_trapped_particles
1192
    use fields_arrays, only: phinew, bparnew
1193
    use gs2_time, only: user_time
1194
    use collisions, only: vnmult
1195
    use species, only: spec
1196
    use diagnostics_velocity_space, only: get_verr, get_gtran
1197
    use gs2_io, only: nc_write_verr_est
1198
    implicit none
1199
    real, dimension(5,2) :: errest
1200
    integer, dimension (5,3) :: erridx
1201
    real :: geavg, glavg, gtavg
1202

1203
    errest = 0.0; erridx = 0
×
1204

1205
    ! error estimate obtained by comparing standard integral with less-accurate integral
1206
    call get_verr (errest, erridx, phinew, bparnew)
×
1207

1208
    ! error estimate based on monitoring amplitudes of legendre polynomial coefficients
1209
    call get_gtran (geavg, glavg, gtavg, phinew, bparnew)
×
1210

1211
    if (proc0) then
×
1212
       call nc_write_verr_est(get_netcdf_file_id(), nout, &
1213
         [geavg, glavg, gtavg], errest, [vnmult(1)*spec(1)%vnewk, vnmult(2)*spec(1)%vnewk], &
×
1214
         erridx)
×
1215
       ! write error estimates for ion dist. fn. at outboard midplane with ik=it=1 to ascii files
1216
       if (write_ascii) then
×
1217
          if (grid_has_trapped_particles()) then
×
1218
             write(lpc_unit,"(4(1x,e13.6))") user_time, geavg, glavg, gtavg
×
1219
          else
1220
             write(lpc_unit,"(3(1x,e13.6))") user_time, geavg, glavg
×
1221
          end if
1222
          write(res_unit,"(8(1x,e13.6))") user_time, errest(1,2), errest(2,2), errest(3,2), &
×
1223
               errest(4,2), errest(5,2), vnmult(1)*spec(1)%vnewk, vnmult(2)*spec(1)%vnewk
×
1224
          !Max verr
1225
          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))") &
1226
               erridx(1,1), erridx(1,2), erridx(1,3), errest(1,1), &
×
1227
               erridx(2,1), erridx(2,2), erridx(2,3), errest(2,1), &
×
1228
               erridx(3,1), erridx(3,2), erridx(3,3), errest(3,1), &
×
1229
               erridx(4,1), erridx(4,2), erridx(4,3), errest(4,1), &
×
1230
               erridx(5,1), erridx(5,2), erridx(5,3), errest(5,1)
×
1231
       end if
1232
    end if
1233
  end subroutine do_write_verr
×
1234

1235
  !> Write the (total) heating diagnostics to [[heat_unit]] and [[heat_unit2]] (per-species)
1236
  subroutine do_write_heating(t, file_unit, file_unit2, h)
×
1237
    use species, only: nspec
1238
    implicit none
1239
    real, intent(in) :: t
1240
    integer, intent(in) :: file_unit, file_unit2
1241
    !> Heating diagnostics
1242
    type(heating_diagnostics), intent (in) :: h
1243

1244
    integer :: is
1245

1246
    !
1247
    ! For case with two species:
1248
    !
1249
    ! Column     Item               
1250
    !   1        time              
1251
    !   2        Energy              
1252
    !   3        dEnergy/dt            
1253
    !   4        J_ant.E             
1254
    !   5        [h_(i+1)*h_*]/2 * C[h_(i+1)] * T_0 for species 1
1255
    !   6        [h_(i+1)*h_*]/2 * C[h_(i+1)] * T_0 for species 2
1256
    !   7       -[h H(h) * T_0]_1
1257
    !   8       -[h H(h) * T_0]_2
1258
    !   9       -[h C(h) * T_0]_1 
1259
    !  10       -[h C(h) * T_0]_2
1260
    !  11        [h w_* h]_1
1261
    !  12        [h w_* h]_2
1262
    !  13        [h * (q dchi/dt - dh/dt * T0)]_1
1263
    !  14        [h * (q dchi/dt - dh/dt * T0)]_2
1264
    !  15      sum (h C(h) * T_0)  in total, as in 5, 6      
1265
    !  16     -sum (h H(h) * T_0)      
1266
    !  17     -sum (h C(h) * T_0)   
1267
    !  18      sum (h w_* h)  
1268
    !  19      sum [h (q dchi/dt - dh/dt * T0)]
1269
    !  20      3 + 4 + 18 + 19
1270
    !  21      (k_perp A)**2
1271
    !  22      B_par**2
1272
    !  23      df_1 ** 2
1273
    !  24      df_2 ** 2
1274
    !  25      h_1 ** 2
1275
    !  26      h_2 ** 2
1276
    !  27      Phi_bar_1 ** 2
1277
    !  28      Phi_bar_2 ** 2
1278
    !
1279
    !
1280
    ! For case with one species:
1281
    !
1282
    ! Column     Item               
1283
    !   1        time              
1284
    !   2        Energy              
1285
    !   3        dEnergy/dt            
1286
    !   4        J_ant.E             
1287
    !   5        [h_(i+1)*h_*]/2 * C[h_(i+1)] * T_0 
1288
    !   6       -[h H(h) * T_0]
1289
    !   7       -[h C(h) * T_0]
1290
    !   8        [h w_* h]
1291
    !   9        [h * (q dchi/dt - dh/dt * T0)]_1
1292
    !  10      sum (h C(h) * T_0)  in total, as in 5, 6      
1293
    !  11     -sum (h H(h) * T_0)      
1294
    !  12     -sum (h C(h) * T_0)   
1295
    !  13      sum (h w_* h)  
1296
    !  14      sum [h (q dchi/dt - dh/dt * T0)]
1297
    !  15      3 + 4 + 9 + 10
1298
    !  16      (k_perp A)**2
1299
    !  17      B_par**2
1300
    !  18      df ** 2
1301
    !  19      h ** 2
1302
    !  20      Phi_bar ** 2
1303
    
1304
    write (unit=file_unit, fmt="(28es12.4)") t,h % energy,  &
×
1305
         h % energy_dot, h % antenna, h % imp_colls, h % hypercoll, h % collisions, &
×
1306
         h % gradients, h % heating, sum(h % imp_colls), sum(h % hypercoll), sum(h % collisions), &
×
1307
         sum(h % gradients), sum(h % heating),sum(h%heating)+h%antenna+sum(h%gradients)+h%energy_dot, &
×
1308
         h % eapar, h % ebpar, h % delfs2(:),  h % hs2(:), h % phis2(:)
×
1309

1310
    do is=1,nspec
×
1311
      write (unit=file_unit2, fmt="(15es12.4)") t,h % energy,  &
×
1312
           h % energy_dot, h % antenna, h % imp_colls(is), h % hypercoll(is), h % collisions(is), &
×
1313
           h % gradients(is), h % heating(is), &
×
1314
           h % eapar, h % ebpar, h % delfs2(is),  h % hs2(is), h % phis2(is), real(is)
×
1315
      write (unit=file_unit2, fmt=*)
×
1316
    end do
1317
    write (unit=file_unit2, fmt=*)
×
1318

1319
    flush (file_unit)
×
1320
    flush (file_unit2)
×
1321
  end subroutine do_write_heating
×
1322

1323
  !> Calculate the momentum flux as a function of \((v_\parallel, \theta, t)\)
1324
  !> and write to netCDF
1325
  subroutine do_write_symmetry(file_id, nout)
×
1326
    use diagnostics_fluxes, only: flux_vs_theta_vs_vpa
1327
    use theta_grid, only: ntgrid
1328
    use le_grids, only: nlambda, negrid
1329
    use species, only: nspec
1330
    use mp, only: proc0
1331
    use gs2_io, only: nc_loop_sym
1332
    use fields_arrays, only: phinew
1333
    implicit none
1334
    !> NetCDF ID of the file to write to
1335
    integer, intent(in) :: file_id
1336
    !> Current timestep
1337
    integer, intent(in) :: nout
1338

1339
    real, dimension(:,:,:), allocatable :: vflx_sym
×
1340
    allocate (vflx_sym(-ntgrid:ntgrid,nlambda*negrid,nspec))
×
1341
    call flux_vs_theta_vs_vpa (phinew, vflx_sym)
×
1342
    if (proc0) call nc_loop_sym (file_id, nout, vflx_sym)
×
1343
    deallocate (vflx_sym)
×
1344
  end subroutine do_write_symmetry
×
1345

1346
  subroutine do_write_kinetic_energy_transfer(file_id, nout)
×
1347
    use diagnostics_kinetic_energy_transfer, only: calculate_kinetic_energy_transfer, write_kinetic_energy_transfer
1348
    use mp, only: proc0
1349
    !> NetCDF ID of the file to write to
1350
    integer, intent(in) :: file_id
1351
    !> Current timestep
1352
    integer, intent(in) :: nout
1353
    call calculate_kinetic_energy_transfer
×
1354
    if (proc0) call write_kinetic_energy_transfer(file_id, nout)
×
1355
  end subroutine do_write_kinetic_energy_transfer
×
1356

1357
  !> Calculate the poloidal distributions of the fluxes of particles, parallel
1358
  !> momentum, perpendicular momentum, and energy (see section 3.1 and appendix
1359
  !> A of [Ball et al. PPCF 58 (2016)
1360
  !> 045023](https://doi.org/10.1088/0741-3335/58/4/045023) as well as section 5
1361
  !> of "GS2 analytic geometry specification")
1362
  subroutine do_write_nl_flux_dist(file_id, nout)
×
1363
    use diagnostics_fluxes, only: flux_dist
1364
    use theta_grid, only: ntgrid
1365
    use species, only: nspec, spec
1366
    use mp, only: proc0
1367
    use gs2_io, only: nc_loop_dist
1368
    use kt_grids, only: naky, ntheta0
1369
    use fields_arrays, only: phinew, bparnew
1370
    use run_parameters, only: has_phi
1371
    implicit none
1372
    !> NetCDF ID of the file to write to
1373
    integer, intent(in) :: file_id
1374
    !> Current timestep
1375
    integer, intent(in) :: nout
1376

1377
    real, dimension (:,:), allocatable :: part_fluxes_dist, mom_fluxes_par_dist
×
1378
    real, dimension (:,:), allocatable :: phi_dist, mom_fluxes_perp_dist, heat_fluxes_dist
×
1379
    real, dimension (:,:,:,:), allocatable :: pflux_dist, vflux_par_dist, vflux_perp_dist, qflux_dist
×
1380
    integer :: ig, is
1381
    if (.not. has_phi) return
×
1382

1383
    allocate (pflux_dist(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1384
    allocate (vflux_par_dist(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1385
    allocate (vflux_perp_dist(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1386
    allocate (qflux_dist(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1387

1388
    call flux_dist (phinew, bparnew, pflux_dist, vflux_par_dist, vflux_perp_dist, qflux_dist)
×
1389

1390
    if (proc0) then
×
1391
       allocate (part_fluxes_dist(-ntgrid:ntgrid,nspec))
×
1392
       allocate (mom_fluxes_par_dist(-ntgrid:ntgrid,nspec))
×
1393
       allocate (mom_fluxes_perp_dist(-ntgrid:ntgrid,nspec))
×
1394
       allocate (heat_fluxes_dist(-ntgrid:ntgrid,nspec))
×
1395
       allocate (phi_dist(2,-ntgrid:ntgrid))
×
1396
       do is = 1, nspec
×
1397
          do ig = -ntgrid, ntgrid
×
1398
             call get_volume_average (pflux_dist(ig,:,:,is), part_fluxes_dist(ig,is))
×
1399
             call get_volume_average (vflux_par_dist(ig,:,:,is), mom_fluxes_par_dist(ig,is))
×
1400
             call get_volume_average (vflux_perp_dist(ig,:,:,is), mom_fluxes_perp_dist(ig,is))
×
1401
             call get_volume_average (qflux_dist(ig,:,:,is), heat_fluxes_dist(ig,is))
×
1402
          end do
1403

1404
          part_fluxes_dist(:, is) = part_fluxes_dist(:, is) * spec(is)%dens
×
1405
          mom_fluxes_par_dist(:, is) = mom_fluxes_par_dist(:, is) * spec(is)%dens * sqrt(spec(is)%mass * spec(is)%temp)             
×
1406
          mom_fluxes_perp_dist(:, is) = mom_fluxes_perp_dist(:, is) * spec(is)%dens * sqrt(spec(is)%mass * spec(is)%temp)
×
1407
          heat_fluxes_dist(:, is) = heat_fluxes_dist(:, is) * spec(is)%dens * spec(is)%temp
×
1408
       end do
1409

1410
       do ig = -ntgrid, ntgrid
×
1411
          call get_volume_average (real(phinew(ig,:,:)), phi_dist(1,ig))
×
1412
          call get_volume_average (aimag(phinew(ig,:,:)), phi_dist(2,ig))
×
1413
       end do
1414

1415
       call nc_loop_dist (file_id, nout, part_fluxes_dist, mom_fluxes_par_dist, &
1416
            mom_fluxes_perp_dist, heat_fluxes_dist, phi_dist)
×
1417

1418
       deallocate (part_fluxes_dist, mom_fluxes_par_dist, mom_fluxes_perp_dist)
×
1419
       deallocate (heat_fluxes_dist, phi_dist)
×
1420
     end if
1421
    deallocate (pflux_dist, vflux_par_dist, vflux_perp_dist, qflux_dist)
×
1422
   end subroutine do_write_nl_flux_dist
×
1423

1424
  !> Calculate the correlation function over the physical domain and write to netCDF
1425
  subroutine do_write_correlation(file_id, nout)
×
1426
    use theta_grid, only: ntgrid
1427
    use kt_grids, only: naky
1428
    use mp, only: proc0
1429
    use gs2_io, only: nc_loop_corr
1430
    implicit none
1431
    !> NetCDF ID of the file to write to
1432
    integer, intent(in) :: file_id
1433
    !> Current timestep
1434
    integer, intent(in) :: nout
1435
    complex, dimension(:,:), allocatable :: phi_corr_2pi
×
1436
    allocate (phi_corr_2pi(-ntgrid:ntgrid,naky))
×
1437
    call correlation (phi_corr_2pi)
×
1438
    if (proc0) call nc_loop_corr (file_id, nout, phi_corr_2pi)
×
1439
    deallocate (phi_corr_2pi)
×
1440
  end subroutine do_write_correlation
×
1441

1442
  !> Calculate the correlation function over the extended domain and write to netCDF
1443
  !>
1444
  !> This does the calculation every time it is called, but only writes every
1445
  !> `nwrite_mult * nwrite` timesteps
1446
  subroutine do_write_correlation_extend(file_id, time, time_old)
×
1447
    use theta_grid, only: ntgrid
1448
    use kt_grids, only: jtwist, ntheta0, naky
1449
    use mp, only: proc0
1450
    use gs2_io, only: nc_loop_corr_extend
1451
    implicit none
1452
    !> NetCDF ID of the file to write to
1453
    integer, intent(in) :: file_id
1454
    !> Current and previous simulation times
1455
    real, intent(in) :: time, time_old
1456
    complex, dimension (:,:,:), allocatable, save:: phicorr_sum
1457
    real, dimension (:,:,:), allocatable, save :: phiextend_sum
1458
    complex, dimension (:,:,:), allocatable :: phi_corr
×
1459
    real, dimension (:,:,:), allocatable :: phi2_extend
×
1460
    real, save :: tcorr0 = 0.0
1461
    integer :: ntg_extend
1462
    if (.not. proc0) return
×
1463
    ntg_extend = (2*ntgrid+1) * ((ntheta0-1) / jtwist + 1)
×
1464

1465
    if (.not. allocated(phicorr_sum)) then
×
1466
       ! Warning: For ntheta=ntheta0=naky=128 and jtwist = 6 these two arrays
1467
       ! will require 750 MB and 375 MB respectively and they are not freed
1468
       ! after leaving the routine.
1469
       allocate (phicorr_sum(ntg_extend,ntheta0,naky)) ; phicorr_sum = 0.0
×
1470
       allocate (phiextend_sum(ntg_extend,ntheta0,naky)) ; phiextend_sum = 0.0
×
1471
       tcorr0 = time_old
×
1472
    end if
1473

1474
    allocate (phi_corr(ntg_extend,ntheta0,naky))
×
1475
    allocate (phi2_extend(ntg_extend,ntheta0,naky))
×
1476
    call correlation_extend (phi_corr, phi2_extend, ntg_extend)
×
1477
    phicorr_sum = phicorr_sum + phi_corr*(time-time_old)
×
1478
    phiextend_sum = phiextend_sum + phi2_extend*(time-time_old)
×
1479
    call nc_loop_corr_extend (file_id, nout_big, time, phicorr_sum/(time-tcorr0), &
×
1480
         phiextend_sum/(time-tcorr0))
×
1481
    nout_big = nout_big + 1
×
1482
    deallocate (phi_corr, phi2_extend)
×
1483
  end subroutine do_write_correlation_extend
×
1484

1485
  !> Calculate average parity of distribution function under \((\theta, k_x,
1486
  !> v_\parallel) \to (-\theta, -k_x, -v_\parallel)\), and write to [[parity_unit]]
1487
  subroutine do_write_parity(t, file_unit, write_text)
×
1488
    use theta_grid, only: ntgrid, field_line_average
×
1489
    use kt_grids, only: naky, ntheta0
1490
    use le_grids, only: negrid, nlambda, integrate_moment, integrate_kysum
1491
    use species, only: nspec
1492
    use gs2_layouts, only: init_parity_layouts, p_lo, g_lo, idx_local
1493
    use gs2_layouts, only: ik_idx, it_idx, il_idx, ie_idx, is_idx, idx, proc_id
1494
    use mp, only: send, receive, proc0, iproc, nproc
1495
    use dist_fn_arrays, only: gnew, g_adjust, aj0, to_g_gs2, from_g_gs2
1496
    use fields_arrays, only: phinew, bparnew
1497
    use constants, only: zi
1498
    implicit none
1499
    real, intent(in) :: t
1500
    !> Open formatted file to write text to
1501
    integer, intent(in) :: file_unit
1502
    !> If false, don't calculate or write parity
1503
    logical, intent(in) :: write_text
1504
    integer :: iplo, iglo, sgn2, isgn, il, ie, ig, ik, it, is, it_source
1505
    complex, dimension (:,:,:,:), allocatable :: gparity, gmx, gpx
×
1506
    complex, dimension (:,:,:), allocatable :: g0, gm, gp
×
1507
    complex, dimension (:,:,:), allocatable :: g_kint, gm_kint, gp_kint
×
1508
    complex, dimension (:,:), allocatable :: g_avg, gnorm_avg, phim
×
1509
    complex, dimension (:), allocatable :: g_all_tot, g_nokx_tot, g_nosig_tot, gtmp
×
1510
    complex, dimension (:), allocatable :: gnorm_all_tot, gnorm_nokx_tot, gnorm_nosig_tot
×
1511
    real, dimension (:,:,:), allocatable :: gmnorm, gmint, gpint, gmnormint, gmavg, gpavg, gmnormavg
×
1512
    real, dimension (:), allocatable :: gmtot, gptot, gtot, gmnormtot
×
1513
    real, dimension (:), allocatable :: gm_nokx_tot, gp_nokx_tot, gmnorm_nokx_tot
×
1514
    real, dimension (:), allocatable :: gm_nosig_tot, gp_nosig_tot, gmnorm_nosig_tot
×
1515

1516
    if (.not. write_text) return
×
1517

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

1521
    allocate (gparity(-ntgrid:ntgrid,ntheta0,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1522
    allocate (g0(-ntgrid:ntgrid,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1523
    allocate (gm(-ntgrid:ntgrid,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1524
    allocate (gp(-ntgrid:ntgrid,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1525
    allocate (gmnorm(-ntgrid:ntgrid,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1526
    allocate (gmint(-ntgrid:ntgrid,naky,nspec))
×
1527
    allocate (gpint(-ntgrid:ntgrid,naky,nspec))
×
1528
    allocate (gmnormint(-ntgrid:ntgrid,naky,nspec))
×
1529
    allocate (gmavg(ntheta0,naky,nspec))
×
1530
    allocate (gpavg(ntheta0,naky,nspec))
×
1531
    allocate (gmnormavg(ntheta0,naky,nspec))
×
1532
    allocate (gmtot(nspec), gm_nokx_tot(nspec), gm_nosig_tot(nspec))
×
1533
    allocate (gptot(nspec), gp_nokx_tot(nspec), gp_nosig_tot(nspec))
×
1534
    allocate (gtot(nspec), gmnormtot(nspec), gmnorm_nokx_tot(nspec), gmnorm_nosig_tot(nspec))
×
1535
    allocate (phim(-ntgrid:ntgrid,naky))
×
1536
    allocate (g_kint(-ntgrid:ntgrid,2,nspec), gm_kint(-ntgrid:ntgrid,2,nspec), gp_kint(-ntgrid:ntgrid,2,nspec))
×
1537
    allocate (g_avg(ntheta0,nspec), gnorm_avg(ntheta0,nspec))
×
1538
    allocate (g_all_tot(nspec), g_nokx_tot(nspec), g_nosig_tot(nspec), gtmp(nspec))
×
1539
    allocate (gnorm_all_tot(nspec), gnorm_nokx_tot(nspec), gnorm_nosig_tot(nspec))
×
1540

1541
    ! convert from g to h
1542
    call g_adjust (gnew, phinew, bparnew, direction = from_g_gs2)
×
1543

1544
    ! below we define gparity = J0 * h, where delta f = h - (q phi / T) F0
1545
    ! because we're ultimately interested in int J0 h * phi (i.e. particle flux)
1546
    ! This should probably be written as a redistribute gather/scatter?
1547
    do iglo = g_lo%llim_world, g_lo%ulim_world
×
1548
       ik = ik_idx(g_lo, iglo)
×
1549
       ie = ie_idx(g_lo, iglo)
×
1550
       il = il_idx(g_lo, iglo)
×
1551
       is = is_idx(g_lo, iglo)
×
1552
       it = it_idx(g_lo, iglo)
×
1553
       ! count total index for given (ik,il,ie,is) combo (dependent on layout)
1554
       iplo = idx(p_lo, ik, il, ie, is)
×
1555
       ! check to see if value of g corresponding to iglo is on this processor
1556
       if (idx_local(g_lo, iglo)) then
×
1557
          if (idx_local(p_lo, iplo)) then
×
1558
             ! if g value corresponding to iplo should be on this processor, then get it
1559
             gparity(:, it, :, iplo) = gnew(:, :, iglo) * spread(aj0(:, iglo), 2, 2)
×
1560
          else
1561
             ! otherwise, send g for this iplo value to correct processor
1562
             call send (gnew(:, :, iglo) * spread(aj0(:, iglo), 2, 2), proc_id(p_lo, iplo))
×
1563
          end if
1564
       else if (idx_local(p_lo, iplo)) then
×
1565
          ! if g for this iplo not on processor, receive it
1566
          call receive (gparity(:, it, :, iplo), proc_id(g_lo, iglo))
×
1567
       end if
1568
    end do
1569

1570
    ! convert from h back to g
1571
    call g_adjust (gnew, phinew, bparnew, direction = to_g_gs2)
×
1572

1573
    ! first diagnostic is phase space average of 
1574
    ! |J0*(h(z,vpa,kx) +/- h(-z,-vpa,-kx))|**2 / ( |J0*h(z,vpa,kx)|**2 + |J0*h(-z,-vpa,-kx)|**2 )
1575
    do it = 1, ntheta0
×
1576
       ! have to treat kx=0 specially
1577
       if (it == 1) then
×
1578
          it_source = 1
×
1579
       else
1580
          it_source = ntheta0 - it + 2
×
1581
       end if
1582

1583
       do isgn = 1, 2
×
1584
          sgn2 = mod(isgn,2)+1
×
1585
          do ig = -ntgrid, ntgrid
×
1586
             ! g0 = gparity(ntgrid:-ntgrid:-1, it_source, 2:1:-1, :) -- copy reversing theta and sigma
1587
             g0(ig, isgn, :) = gparity(-ig, it_source, sgn2, :)
×
1588
          end do
1589
       end do
1590

1591
       gm = gparity(:,it,:,:)-g0
×
1592
       gp = gparity(:,it,:,:)+g0
×
1593
       gmnorm = real(g0*conjg(g0))
×
1594
       ! integrate out velocity dependence
1595
       call integrate_moment (real(gm*conjg(gm)),gmint,1)
×
1596
       call integrate_moment (real(gp*conjg(gp)),gpint,1)
×
1597
       call integrate_moment (gmnorm,gmnormint,1)
×
1598
       ! average along field line
1599
       gmavg(it,:,:) = field_line_average(gmint)
×
1600
       gpavg(it,:,:) = field_line_average(gpint)
×
1601
       gmnormavg(it,:,:) = field_line_average(gmnormint)
×
1602

1603
       ! phim(theta,kx) = phi(-theta,-kx)
1604
       do ig = -ntgrid, ntgrid
×
1605
          phim(ig,:) = phinew(-ig, it_source, :)
×
1606
       end do
1607

1608
       ! want int dtheta sum_{kx} int d3v | sum_{ky} [ J0*(h+ * conjg(phi-) + h- * conjg(phi+)) ky ] |**2
1609
       ! J0*(h+ * conjg(phi-) + h- * conjg(phi+)) = h*conjg(phi) - h(-theta,-vpa,-kx)*conjg(phi(-theta,-kx))
1610
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1611
          ik = ik_idx(p_lo,iplo)
×
1612
          do isgn = 1, 2
×
1613
             gm(:,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik)) - g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1614
          end do
1615
       end do
1616
       call integrate_kysum (gm, g_kint, 1)
×
1617
       g_avg(it, :) = field_line_average(g_kint(:,1,:) + g_kint(:,2,:))
×
1618

1619
       ! get normalizing term for above diagnostic
1620
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1621
          ik = ik_idx(p_lo,iplo)
×
1622
          do isgn = 1, 2
×
1623
             gm(:,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik))
×
1624
             gp(:,isgn,iplo) = g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1625
          end do
1626
       end do
1627
       call integrate_kysum (gm, gm_kint, 1)
×
1628
       call integrate_kysum (gp, gp_kint, 1)
×
1629
       gnorm_avg(it,:) = field_line_average(gm_kint(:,1,:)+gm_kint(:,2,:) &
×
1630
            + gp_kint(:,1,:)+gp_kint(:,2,:))
×
1631
    end do
1632

1633
    ! average over perp plane
1634
    do is = 1, nspec
×
1635
       call get_volume_average (gmavg(:,:,is), gmtot(is))
×
1636
       call get_volume_average (gpavg(:,:,is), gptot(is))
×
1637
       call get_volume_average (gmnormavg(:,:,is), gmnormtot(is))    
×
1638
       g_all_tot(is) = sum(g_avg(:,is))
×
1639
       gnorm_all_tot(is) = sum(gnorm_avg(:,is))
×
1640
    end do
1641

1642
    allocate (gmx(-ntgrid:ntgrid,ntheta0,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1643
    allocate (gpx(-ntgrid:ntgrid,ntheta0,2,p_lo%llim_proc:p_lo%ulim_alloc))
×
1644

1645
    ! now we want diagnostic of phase space average of
1646
    ! |J0*(h(z,vpa) +/- h(-z,-vpa))|**2 / ( |J0*h(z,vpa)|**2 + |J0*h(-z,-vpa)|**2 )
1647
    do it = 1, ntheta0
×
1648
       do isgn = 1, 2
×
1649
          sgn2 = mod(isgn,2)+1
×
1650
          do ig = -ntgrid, ntgrid
×
1651
             g0(ig,isgn,:) = gparity(-ig,it,sgn2,:)
×
1652
          end do
1653
       end do
1654
       gm = gparity(:,it,:,:)-g0
×
1655
       gp = gparity(:,it,:,:)+g0
×
1656
       gmnorm = real(g0*conjg(g0))
×
1657
       ! integrate out velocity dependence
1658
       call integrate_moment (real(gm*conjg(gm)),gmint,1)
×
1659
       call integrate_moment (real(gp*conjg(gp)),gpint,1)
×
1660
       call integrate_moment (gmnorm,gmnormint,1)
×
1661
       ! average along field line
1662
       gmavg(it,:,:) = field_line_average(gmint)
×
1663
       gpavg(it,:,:) = field_line_average(gpint)
×
1664
       gmnormavg(it,:,:) = field_line_average(gmnormint)
×
1665

1666
       ! phim(theta) = phi(-theta)
1667
       ! have to treat kx=0 specially
1668
       do ig = -ntgrid, ntgrid
×
1669
          phim(ig,:) = phinew(-ig,it,:)
×
1670
       end do
1671

1672
       ! want int dtheta int d3v | sum_{kx} sum_{ky} [ J0*(h+ * conjg(phi-) + h- * conjg(phi+)) ky ] |**2
1673
       ! J0*(h+ * conjg(phi-) + h- * conjg(phi+)) = h*conjg(phi) - h(-theta,-vpa)*conjg(phi(-theta))
1674
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1675
          ik = ik_idx(p_lo,iplo)
×
1676
          do isgn = 1, 2
×
1677
             gmx(:,it,isgn,iplo) = g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1678
             gpx(:,it,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik)) - gmx(:,it,isgn,iplo) 
×
1679
          end do
1680
       end do
1681
    end do
1682

1683
    ! sum over kx
1684
    gp = sum(gpx,2)
×
1685
    deallocate (gpx)
×
1686
    call integrate_kysum(gp, g_kint, 1)
×
1687
    g_nokx_tot = field_line_average(g_kint(:,1,:) + g_kint(:,2,:))
×
1688

1689
    ! get normalizing terms for above diagnostic
1690
    gm = sum(gmx,2)
×
1691
    deallocate (gmx)
×
1692
    call integrate_kysum(gm, gm_kint, 1)
×
1693
    call integrate_kysum(gm + gp, gp_kint, 1)
×
1694
    gnorm_nokx_tot = field_line_average(gm_kint(:,1,:)+gm_kint(:,2,:) &
×
1695
         + gp_kint(:,1,:)+gp_kint(:,2,:))
×
1696

1697
    ! average over perp plane
1698
    do is = 1, nspec
×
1699
       call get_volume_average (gmavg(:,:,is), gm_nokx_tot(is))
×
1700
       call get_volume_average (gpavg(:,:,is), gp_nokx_tot(is))
×
1701
       call get_volume_average (gmnormavg(:,:,is), gmnorm_nokx_tot(is))    
×
1702
    end do
1703

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

1714
       do ig = -ntgrid, ntgrid
×
1715
          g0(ig, :, :) = gparity(-ig, it_source, :, :)
×
1716
       end do
1717

1718
       gm = gparity(:,it,:,:)-g0
×
1719
       gp = gparity(:,it,:,:)+g0
×
1720
       gmnorm = real(g0*conjg(g0))
×
1721
       ! integrate out velocity dependence
1722
       call integrate_moment (real(gm*conjg(gm)),gmint,1)
×
1723
       call integrate_moment (real(gp*conjg(gp)),gpint,1)
×
1724
       call integrate_moment (gmnorm,gmnormint,1)
×
1725
       ! average along field line
1726
       gmavg(it,:,:) = field_line_average(gmint)
×
1727
       gpavg(it,:,:) = field_line_average(gpint)
×
1728
       gmnormavg(it,:,:) = field_line_average(gmnormint)
×
1729

1730
       ! phim(theta,kx) = phi(-theta,-kx)
1731
       do ig = -ntgrid, ntgrid
×
1732
          phim(ig, :) = phinew(-ig, it_source, :)
×
1733
       end do
1734

1735
       ! want int dtheta sum_{kx} int dE dmu | sum_{sigma} sum_{ky} [ J0*(h+ * conjg(phi-) + h- * conjg(phi+)) ky ] |**2
1736
       ! J0*(h+ * conjg(phi-) + h- * conjg(phi+)) = h*conjg(phi) - h(-theta,-kx)*conjg(phi(-theta,-kx))
1737
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1738
          ik = ik_idx(p_lo,iplo)
×
1739
          do isgn = 1, 2
×
1740
             gm(:,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik)) - g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1741
          end do
1742
       end do
1743

1744
       ! Only sets isgn = 1 in the g_kint array here
1745
       call integrate_kysum (spread(gm(:, 1, :) + gm(:, 2, :), 2, 1), g_kint, 1)
×
1746
       g_avg(it, :) = field_line_average(g_kint(:,1,:))
×
1747

1748
       ! get normalizing term for above diagnostic
1749
       do iplo = p_lo%llim_proc, p_lo%ulim_proc
×
1750
          ik = ik_idx(p_lo,iplo)
×
1751
          do isgn = 1, 2
×
1752
             gm(:,isgn,iplo) = gparity(:,it,isgn,iplo)*conjg(phinew(:,it,ik))
×
1753
             gp(:,isgn,iplo) = g0(:,isgn,iplo)*conjg(phim(:,ik))
×
1754
          end do
1755
       end do
1756

1757
       ! Only sets isgn = 1 in the g*_kint arrays here
1758
       call integrate_kysum (spread(gm(:, 1, :) + gm(:, 2, :), 2, 1), gm_kint, 1)
×
1759
       call integrate_kysum (spread(gp(:, 1, :) + gp(:, 2, :), 2, 1), gp_kint, 1)
×
1760
       gnorm_avg(it, :) = field_line_average(gm_kint(:,1,:) + gp_kint(:,1,:))
×
1761
    end do
1762

1763
    ! average over perp plane
1764
    do is = 1, nspec
×
1765
       call get_volume_average (gmavg(:,:,is), gm_nosig_tot(is))
×
1766
       call get_volume_average (gpavg(:,:,is), gp_nosig_tot(is))
×
1767
       call get_volume_average (gmnormavg(:,:,is), gmnorm_nosig_tot(is))    
×
1768
       g_nosig_tot(is) = sum(g_avg(:,is))
×
1769
       gnorm_nosig_tot(is) = sum(gnorm_avg(:,is))
×
1770
    end do
1771

1772
    deallocate (gparity) ; allocate (gparity(-ntgrid:ntgrid,ntheta0,naky,nspec))
×
1773
    ! obtain normalization factor = int over phase space of |g|**2
1774
    call g_adjust (gnew, phinew, bparnew, direction = from_g_gs2)
×
1775
    !Do all processors need to know the full result here? Only proc0 seems to do any writing.
1776
    !If not then remove the last two arguments in the following call.
1777
    call integrate_moment (spread(aj0,2,2)*spread(aj0,2,2)*gnew*conjg(gnew), gparity, .true., full_arr=.true.)
×
1778
    call g_adjust (gnew, phinew, bparnew, direction = to_g_gs2)
×
1779
    do is = 1, nspec
×
1780
       gmavg(:, :, is) = field_line_average(real(gparity(:,:,:,is)))
×
1781
       call get_volume_average (gmavg(:,:,is), gtot(is))
×
1782
    end do
1783

1784
    ! normalize g(theta,vpa,kx) - g(-theta,-vpa,-kx) terms
1785
    where (gtot+gmnormtot > epsilon(0.0))
×
1786
       gmtot = sqrt(gmtot/(gtot+gmnormtot)) ; gptot = sqrt(gptot/(gtot+gmnormtot))
×
1787
    elsewhere
1788
       gmtot = sqrt(gmtot) ; gptot = sqrt(gptot)
×
1789
    end where
1790

1791
    where (real(gnorm_all_tot) > epsilon(0.0))
×
1792
       gtmp = sqrt(real(g_all_tot)/real(gnorm_all_tot))
×
1793
    elsewhere
1794
       gtmp = sqrt(real(g_all_tot))
×
1795
    end where
1796
    where (aimag(gnorm_all_tot) > epsilon(0.0))
×
1797
       g_all_tot = gtmp + zi*sqrt(aimag(g_all_tot)/aimag(gnorm_all_tot))
×
1798
    elsewhere
1799
       g_all_tot = gtmp + zi*sqrt(aimag(g_all_tot))
×
1800
    end where
1801

1802
    ! normalize g(theta,vpa) +/- g(-theta,-vpa) terms
1803
    where (gtot+gmnorm_nokx_tot > epsilon(0.0))
×
1804
       gm_nokx_tot = sqrt(gm_nokx_tot/(gtot+gmnorm_nokx_tot)) ; gp_nokx_tot = sqrt(gp_nokx_tot/(gtot+gmnorm_nokx_tot))
×
1805
    elsewhere
1806
       gm_nokx_tot = sqrt(gm_nokx_tot) ; gp_nokx_tot = sqrt(gp_nokx_tot)
×
1807
    end where
1808

1809
    where (real(gnorm_nokx_tot) > epsilon(0.0))
×
1810
       gtmp = sqrt(real(g_nokx_tot)/real(gnorm_nokx_tot))
×
1811
    elsewhere
1812
       gtmp = sqrt(real(g_nokx_tot))
×
1813
    end where
1814
    where (aimag(gnorm_nokx_tot) > epsilon(0.0))
×
1815
       g_nokx_tot = gtmp + zi*sqrt(aimag(g_nokx_tot)/aimag(gnorm_nokx_tot))
×
1816
    elsewhere
1817
       g_nokx_tot = gtmp + zi*sqrt(aimag(g_nokx_tot))
×
1818
    end where
1819

1820
    ! normalize g(theta,kx) +/ g(-theta,-kx) terms
1821
    where (gtot+gmnorm_nosig_tot > epsilon(0.0))
×
1822
       gm_nosig_tot = sqrt(gm_nosig_tot/(gtot+gmnorm_nosig_tot)) ; gp_nosig_tot = sqrt(gp_nosig_tot/(gtot+gmnorm_nosig_tot))
×
1823
    elsewhere
1824
       gm_nosig_tot = sqrt(gm_nosig_tot) ; gp_nosig_tot = sqrt(gp_nosig_tot)
×
1825
    end where
1826

1827
    where (real(gnorm_nosig_tot) > epsilon(0.0))
×
1828
       gtmp = sqrt(real(g_nosig_tot)/real(gnorm_nosig_tot))
×
1829
    elsewhere
1830
       gtmp = sqrt(real(g_nosig_tot))
×
1831
    end where
1832
    where (aimag(gnorm_nosig_tot) > epsilon(0.0))
×
1833
       g_nosig_tot = gtmp + zi*sqrt(aimag(g_nosig_tot)/aimag(gnorm_nosig_tot))
×
1834
    elsewhere
1835
       g_nosig_tot = gtmp + zi*sqrt(aimag(g_nosig_tot))
×
1836
    end where
1837

1838
    if (proc0) write (file_unit,"(19(1x,e12.5))") t, gmtot, gptot, real(g_all_tot), aimag(g_all_tot), &
×
1839
         real(gnorm_all_tot), aimag(gnorm_all_tot), gm_nokx_tot, gp_nokx_tot, real(g_nokx_tot), aimag(g_nokx_tot), &
×
1840
         real(gnorm_nokx_tot), aimag(gnorm_nokx_tot), gm_nosig_tot, gp_nosig_tot, &
×
1841
         real(g_nosig_tot), aimag(g_nosig_tot), real(gnorm_nosig_tot), aimag(gnorm_nosig_tot)
×
1842

1843
    deallocate (gparity, g0)
×
1844
    deallocate (gm, gp, gmnorm, gmint, gpint, gmnormint)
×
1845
    deallocate (gmavg, gpavg, gmnormavg)
×
1846
    deallocate (gmtot, gm_nokx_tot, gm_nosig_tot)
×
1847
    deallocate (gptot, gp_nokx_tot, gp_nosig_tot)
×
1848
    deallocate (gtot, gmnormtot, gmnorm_nokx_tot, gmnorm_nosig_tot)
×
1849
    deallocate (g_avg, gnorm_avg)
×
1850
    deallocate (g_kint, gm_kint, gp_kint)
×
1851
    deallocate (g_all_tot, g_nokx_tot, g_nosig_tot, gtmp)
×
1852
    deallocate (gnorm_all_tot, gnorm_nokx_tot, gnorm_nosig_tot)
×
1853
    deallocate (phim)
×
1854
  end subroutine do_write_parity
×
1855

1856
  !> Flush text files (only [[out_unit]], [[res_unit]], [[lpc_unit]], and
1857
  !> [[parity_unit]])
1858
  subroutine flush_files
×
1859
    implicit none
1860
    if (.not. write_ascii) return
×
1861
    flush (out_unit)
×
1862
    if (write_verr) then
×
1863
       flush (res_unit)
×
1864
       flush (lpc_unit)
×
1865
    end if
1866
    if (write_cerr) flush (cres_unit)
×
1867
    if (write_parity) flush (parity_unit)
×
1868
    if (write_g) flush (dist_unit)
×
1869
    if (write_gyx) flush (yxdist_unit)
×
1870
  end subroutine flush_files
1871

1872
  !> Nonlinear convergence condition - simple and experimental look
1873
  !> for the averaged differential of the summed averaged heat flux to
1874
  !> drop below a threshold
1875
  subroutine check_nonlin_convergence(istep, heat_flux, exit)
×
1876
    use diagnostics_nonlinear_convergence, only: check_nonlin_convergence_calc
1877
    logical, intent(inout) :: exit
1878
    integer, intent(in) :: istep
1879
    real, intent(in) :: heat_flux
1880
    call check_nonlin_convergence_calc(istep, nwrite, heat_flux, exit, exit_when_converged, &
1881
         conv_nstep_av, conv_nsteps_converged, conv_test_multiplier, conv_min_step, &
1882
         conv_max_step)
×
1883
  end subroutine check_nonlin_convergence
×
1884

1885
  !> Calculate some heating diagnostics, and update their time history
1886
  subroutine heating(istep, navg, h, hk, h_hist, hk_hist)
×
1887
    use mp, only: proc0
1888
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
1889
    use species, only: nspec, spec
1890
    use kt_grids, only: naky, ntheta0, aky, akx
1891
    use theta_grid, only: ntgrid, delthet, jacob
1892
    use gs2_heating, only: heating_diagnostics, avg_h, avg_hk, zero_htype, get_heat
1893
    use collisions, only: collisions_heating => heating, c_rate
1894
    implicit none
1895
    integer, intent (in) :: istep, navg
1896
    !> Heating diagnostics summed over space at the current timestep
1897
    type (heating_diagnostics), intent(in out) :: h
1898
    type (heating_diagnostics), dimension (0:), intent(in out) :: h_hist
1899
    !> Heating diagnostics as a function of \((\theta, k_y)\) at the current timestep
1900
    type (heating_diagnostics), dimension(:,:), intent(in out) :: hk
1901
    type (heating_diagnostics), dimension(:,:,0:), intent(in out) :: hk_hist
1902
    real, dimension(-ntgrid:ntgrid) :: wgt
×
1903
    real :: fac
1904
    integer :: is, ik, it, ig
1905

1906
    !Zero out variables for heating diagnostics
1907
    call zero_htype(h)
×
1908
    call zero_htype(hk)
×
1909

1910
    if (proc0 .and. collisions_heating .and. allocated(c_rate)) then
×
1911
       !GGH NOTE: Here wgt is 1/(2*ntgrid+1)
1912
       wgt = delthet*jacob
×
1913
       wgt = wgt/sum(wgt)
×
1914

1915
       do is = 1, nspec
×
1916
          do ik = 1, naky
×
1917
             fac = 0.5
×
1918
             if (aky(ik) < epsilon(0.)) fac = 1.0
×
1919
             do it = 1, ntheta0
×
1920
                if (aky(ik) < epsilon(0.0) .and. abs(akx(it)) < epsilon(0.0)) cycle
×
1921
                do ig = -ntgrid, ntgrid
×
1922

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

1927
                   hk(it, ik) % hypercoll(is) = hk(it, ik) % hypercoll(is) &
×
1928
                        + real(c_rate(ig,it,ik,is,2))*fac*wgt(ig)*spec(is)%temp*spec(is)%dens
×
1929

1930
                   hk(it, ik) % imp_colls(is) = hk(it, ik) % imp_colls(is) &
×
1931
                        + real(c_rate(ig,it,ik,is,3))*fac*wgt(ig)*spec(is)%temp*spec(is)%dens
×
1932

1933
                end do
1934
                h % collisions(is) = h % collisions(is) + hk(it, ik) % collisions(is)
×
1935
                h % hypercoll(is)  = h % hypercoll(is)  + hk(it, ik) % hypercoll(is)
×
1936
                h % imp_colls(is)  = h % imp_colls(is)  + hk(it, ik) % imp_colls(is)
×
1937
             end do
1938
          end do
1939
       end do
1940
    end if
1941

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

1945
    call avg_h(h, h_hist, istep, navg)
×
1946
    call avg_hk(hk, hk_hist, istep, navg)
×
1947
  end subroutine heating
×
1948

1949
  !> Calculate the time-averaged antenna current \(j_{ext} = k_\perp^2 A_{antenna}\)
1950
  subroutine calc_jext (istep, j_ext)
×
1951
    use mp, only: proc0
1952
    use antenna, only: get_jext
1953
    implicit none
1954
    !> Current simulation timestep
1955
    integer, intent (in) :: istep
1956
    !Shouldn't really need intent in here but it's beacuse we zero it before calling calc_jext
1957
    real, dimension(:,:), intent(in out) ::  j_ext
1958

1959
    integer :: i
1960
    if (.not. (proc0 .and. navg > 1)) return
×
1961
    call get_jext(j_ext)
×
1962
    ! This looks a little odd as we ignore the first step
1963
    if (istep > 1) j_ext_hist(:, :, mod(istep, navg)) = j_ext(:, :)
×
1964

1965
    !Use average of history
1966
    if (istep >= navg) then
×
1967
       j_ext = 0.
×
1968
       do i = 0, navg - 1
×
1969
          j_ext = j_ext + j_ext_hist(:, :, i) / real(navg)
×
1970
       end do
1971
    end if
1972
  end subroutine calc_jext
1973

1974
  !> A linear estimate of the diffusivity, primarily used testing
1975
  pure real function diffusivity()
×
1976
    use kt_grids, only: ntheta0, naky, kperp2
1977
    use theta_grid, only: grho
1978
    use warning_helpers, only: is_zero
1979
    real, dimension(ntheta0, naky) :: diffusivity_by_k
×
1980
    integer  :: ik, it
1981
    diffusivity_by_k = 0.0
×
1982
    do ik = 1, naky
×
1983
       do it = 1, ntheta0
×
1984
          if (is_zero(kperp2(igomega,it,ik))) cycle
×
1985
          diffusivity_by_k(it,ik) = 2.0 &
×
1986
               * max(aimag(omegaavg(it,ik)), 0.0) / kperp2(igomega, it, ik)
×
1987
       end do
1988
    end do
1989
    diffusivity = maxval(diffusivity_by_k) * grho(igomega)
×
1990
  end function diffusivity
×
1991

1992
  !> Calculates <|field|**2 kperp2>_theta / <|field|**2>_theta.
1993
  !> Useful for simple quasilinear metric
1994
  pure function get_field_weighted_average_kperp2(field) result(average)
×
1995
    use kt_grids, only: kperp2, naky, ntheta0
1996
    use theta_grid, only: ntgrid, field_line_average
1997
    implicit none
1998
    complex, dimension(-ntgrid:ntgrid, ntheta0, naky), intent(in) :: field
1999
    real, dimension(ntheta0, naky) :: average
2000
    real, dimension(-ntgrid:ntgrid, ntheta0, naky) :: field_squared
×
2001
    integer :: it, ik
2002
    field_squared = abs(field) * abs(field)
×
2003
    average = 0.0
×
2004
    do ik = 1, naky
×
2005
       do it = 1, ntheta0
×
2006
          if (maxval(abs(field_squared(:, it, ik))) <= epsilon(0.0)) cycle
×
2007
          average(it, ik) = field_line_average(field_squared(:, it, ik) * &
×
2008
               kperp2(:, it, ik)) / field_line_average(field_squared(:, it, ik))
×
2009
       end do
2010
    end do
2011
  end function get_field_weighted_average_kperp2
×
2012

2013
  !> Calculates a simple gamma/kperp2 QL flux metric
2014
  function calculate_simple_quasilinear_flux_metric_by_k(growth_rates) result(ql_metric)
×
2015
    use run_parameters, only: has_phi, has_apar, has_bpar
2016
    use kt_grids, only: naky, ntheta0, aky
2017
    use fields_arrays, only: phinew, aparnew, bparnew
2018
    use warning_helpers, only: is_zero
2019
    implicit none
2020
    real, dimension(ntheta0, naky), intent(in) :: growth_rates
2021
    real, dimension(ntheta0, naky) :: limited_growth_rates, average
×
2022
    real, dimension(ntheta0, naky) :: ql_metric, normalising_field
×
2023
    integer :: ik
2024

2025
    ! Initialise flux to zero
2026
    ql_metric = 0.0
×
2027

2028
    ! Decide on the normalising field
2029
    if (has_phi) then
×
2030
       normalising_field = maxval(abs(phinew), dim = 1)
×
2031
    else if (has_apar) then
×
2032
       normalising_field = maxval(abs(aparnew), dim = 1)
×
2033
    else if (has_bpar) then
×
2034
       normalising_field = maxval(abs(bparnew), dim = 1)
×
2035
    else
2036
       ! If we get here then no fields are active so the QL flux
2037
       ! is zero and we can exit
2038
       return
×
2039
    end if
2040

2041
    where (normalising_field > 0)
×
2042
       normalising_field = 1.0 / normalising_field
×
2043
    end where
2044

2045
    if (has_phi) then
×
2046
       average = get_field_weighted_average_kperp2(phinew)
×
2047
       where(average > 0.0)
×
2048
          ql_metric = maxval(abs(phinew), dim = 1) * normalising_field / average
×
2049
       end where
2050
    end if
2051

2052
    if (has_apar) then
×
2053
       average = get_field_weighted_average_kperp2(aparnew)
×
2054
       where(average > 0.0)
×
2055
          ql_metric = ql_metric + &
×
2056
               maxval(abs(aparnew), dim = 1) * normalising_field / average
×
2057
       end where
2058
    end if
2059

2060
    if (has_bpar) then
×
2061
       average = get_field_weighted_average_kperp2(bparnew)
×
2062
       where(average > 0.0)
×
2063
          ql_metric = ql_metric + &
×
2064
               maxval(abs(bparnew), dim = 1) * normalising_field / average
×
2065
       end where
2066
    end if
2067

2068
    ! Limit the growth rate to positive values
2069
    where (growth_rates > 0)
×
2070
       limited_growth_rates = growth_rates
×
2071
    elsewhere
2072
       limited_growth_rates = 0.0
×
2073
    end where
2074

2075
    ! MG: Avoid spurious contribution from the zonal mode
2076
    do ik = 1, naky
×
2077
       if (is_zero(aky(ik))) ql_metric(:, ik) = 0.0
×
2078
    end do
2079

2080
    ql_metric = ql_metric * limited_growth_rates
×
2081
  end function calculate_simple_quasilinear_flux_metric_by_k
×
2082

2083
  !> Calculates the instantaneous omega from chinew = chi * exp(-i * omega * dt)
2084
  !> with chi = phi + apar + bpar. This gives omega = log(chinew/chi) * i / dt.
2085
  pure function  calculate_instantaneous_omega(ig, tolerance) result(omega_inst)
×
2086
    use kt_grids, only: naky, ntheta0
2087
    use fields_arrays, only: phi, apar, bpar, phinew, aparnew, bparnew
2088
    use gs2_time, only: code_dt
2089
    use constants, only: zi
2090
    use optionals, only: get_option_with_default
2091
    use run_parameters, only: has_phi, has_apar, has_bpar
2092
    use warning_helpers, only: is_zero
2093
    implicit none
2094
    integer, intent(in), optional :: ig
2095
    real, intent(in), optional :: tolerance
2096
    complex, dimension(ntheta0, naky) :: omega_inst, field_sum, field_sum_new
×
2097
    integer :: ig_use
2098
    real :: tol_use, too_small
2099

2100
    ! Determine which theta grid point to evaluate the fields at
2101
    ig_use = get_option_with_default(ig, igomega)
×
2102

2103
    ! Construct the field sums for current and old fields.
2104
    ! We always allocate the fields (for now) so we could just
2105
    ! unconditionally sum. This could make the code clearer
2106
    ! without really adding _much_ overhead.
2107
    if (has_phi) then
×
2108
       field_sum = phi(ig_use, :, :)
×
2109
       field_sum_new = phinew(ig_use, :, :)
×
2110
    else
2111
       field_sum = 0.0
×
2112
       field_sum_new = 0.0
×
2113
    end if
2114

2115
    if (has_apar) then
×
2116
       field_sum = field_sum + apar(ig_use, :, :)
×
2117
       field_sum_new = field_sum_new + aparnew(ig_use, :, :)
×
2118
    end if
2119

2120
    if (has_bpar) then
×
2121
       field_sum = field_sum + bpar(ig_use, :, :)
×
2122
       field_sum_new = field_sum_new + bparnew(ig_use, :, :)
×
2123
    end if
2124

2125
    ! Determine what tolerance to use
2126
    tol_use = get_option_with_default(tolerance, omegatol)
×
2127

2128
    ! Decide what size float we consider too small to divide by
2129
    ! Note this uses tiny rather than epsilon in order to allow
2130
    ! us to track modes with low amplitudes.
2131
    if (is_zero(tol_use)) then
×
2132
       too_small = tiny(0.0)
×
2133
    else
2134
       too_small = tiny(0.0) * 1000. / abs(tol_use)
×
2135
    end if
2136

2137
    ! Use where to guard against dividing by tool small a number
2138
    ! Note we don't divide by field_sum_new so we probably don't need to
2139
    ! check that here, just field_sum.
2140
    where (abs(field_sum) < too_small .or. abs(field_sum_new) < too_small)
×
2141
       omega_inst = 0.0
×
2142
    elsewhere
2143
       omega_inst = log(field_sum_new / field_sum) * zi / code_dt
×
2144
    end where
2145

2146
  end function calculate_instantaneous_omega
×
2147

2148
  !> Calculate the time-averaged complex frequency, check convergence
2149
  !> criterion, and numerical instability criterion.
2150
  !>
2151
  !> Time average is over previous [[gs2_diagnostics_knobs:navg]] timesteps
2152
  subroutine get_omegaavg (istep, exit, omegaavg, debopt)
×
2153
    use kt_grids, only: ntheta0, naky
2154
    use gs2_time, only: code_dt, user_time
2155
    use optionals, only: get_option_with_default
2156
    implicit none
2157
    !> The current timestep
2158
    integer, intent (in) :: istep
2159
    !> Should the simulation exit?
2160
    !> FIXME: This could be `intent(out)` only
2161
    logical, intent (in out) :: exit
2162
    !> The time-averaged complex frequency
2163
    complex, dimension (:,:), intent (out) :: omegaavg
2164
    !> If true, write some debug messages
2165
    logical, intent (in), optional :: debopt
2166
    logical :: debug
2167
    debug = get_option_with_default(debopt, .false.)
×
2168
    if (debug) write(6,*) "get_omeaavg: allocate domega"
×
2169
    if (.not. allocated(domega)) allocate(domega(navg,ntheta0,naky))
×
2170
    if (debug) write(6,*) "get_omeaavg: start"
×
2171
    if (debug) write(6,*) "get_omeaavg: set omegahist"
×
2172

2173
    ! Get and store the current instantaneous omega
2174
    omegahist(mod(istep, navg), :, :) = calculate_instantaneous_omega(igomega, omegatol)
×
2175

2176
    if (debug) write(6,*) "get_omeaavg: set omegahist at istep = 0"
×
2177
    !During initialisation fieldnew==field but floating error can lead to finite omegahist
2178
    !Force omegahist=0 here to avoid erroneous values.
2179
    !Could think about forcing omegahist=0 where abs(omegahist)<tol
2180
    if(istep==0) omegahist(:,:,:)=0.0
×
2181

2182
    if (debug) write(6,*) "get_omeaavg: set omegaavg"
×
2183
    omegaavg = sum(omegahist/real(navg),dim=1)
×
2184
    if (debug) write(6,*) "get_omegaavg: omegaavg=",omegaavg
×
2185
    if ((istep > navg) .and.(user_time >= omega_checks_start)) then
×
2186
       domega = spread(omegaavg,1,navg) - omegahist
×
2187
       if (all(sqrt(sum(abs(domega)**2/real(navg),dim=1)) &
×
2188
            .le. min(abs(omegaavg),1.0)*omegatol)) &
×
2189
            then
2190
          if (write_ascii) write (out_unit, "('*** omega converged')")
×
2191
          if (exit_when_converged) exit = .true.
×
2192
       end if
2193

2194
       if (any(abs(omegaavg)*code_dt > omegatinst)) then
×
2195
          if (write_ascii) write (out_unit, "('*** numerical instability detected')") 
×
2196
          exit = .true.
×
2197
       end if
2198

2199
       if (all(aimag(omegaavg) < damped_threshold)) then
×
2200
          if (write_ascii) write (out_unit, "('*** all modes strongly damped')")
×
2201
          exit = .true.
×
2202
       end if
2203
    end if
2204
    if (debug) write(6,*) "get_omegaavg: done"
×
2205
  end subroutine get_omegaavg
×
2206

2207
  !> FIXME : Add documentation
2208
  !> @note: Should look at moving this and weighted_ky_sum to volume_averages
2209
  subroutine get_volume_average (f, favg)
×
2210
    implicit none
2211
    real, dimension (:,:), intent (in) :: f
2212
    real, intent (out) :: favg
2213
    favg = sum(weighted_ky_sum(f))
×
2214
  end subroutine get_volume_average
×
2215

2216
  !> Sum a {kx,ky} array over ky accounting for non-uniform weighting arising
2217
  !> from gs2's non-standard Fourier coefficients:
2218
  !> ky=0 modes have correct amplitudes; rest must be scaled
2219
  !> note contrast with scaling factors in FFT routines.
2220
  !>
2221
  !>  fac values here arise because gs2's Fourier coefficients, F_k^gs2, not standard form:
2222
  !>          i.e. f(x) = f_k e^(i k.x)
2223
  !>  With standard Fourier coeffs in gs2, we would instead need:  fac=2.0 for ky > 0
2224
  !>      (fac=2.0 would account ky<0 contributions, not stored due to reality condition)
2225
  pure function weighted_ky_sum(f) result(ky_sum)
×
2226
    use kt_grids, only: naky, ntheta0, aky
2227
    use warning_helpers, only: is_zero
2228
    implicit none
2229
    real, dimension(:, :), intent (in) :: f
2230
    real, dimension(ntheta0) :: ky_sum
2231
    real :: fac
2232
    integer :: ik
2233
    ky_sum = 0.
×
2234
    do ik = 1, naky
×
2235
       fac = 0.5
×
2236
       if (is_zero(aky(ik))) fac = 1.0
×
2237
       ky_sum = ky_sum + f(:, ik) * fac
×
2238
    end do
2239
  end function weighted_ky_sum
×
2240

2241
  !> Calculate the correlation function over the extended domain
2242
  subroutine correlation_extend (cfnc, phi2extend, ntg_extend)
×
2243
    use fields_arrays, only: phinew
2244
    use theta_grid, only: ntgrid, jacob, delthet, ntgrid
2245
    use kt_grids, only: ntheta0, naky, jtwist
2246
    implicit none
2247
    real, dimension (:,:,:), intent (out) :: phi2extend
2248
    complex, dimension (:,:,:), intent (out) :: cfnc
2249
    integer, intent(in) :: ntg_extend
2250
    integer :: ig, it, ik, im, igmod, itshift, nconnect, offset
2251
    real, dimension (:), allocatable :: dl_over_b
×
2252
    complex, dimension (:,:,:), allocatable :: phiextend
×
2253
    complex, dimension (:,:), allocatable :: phir
×
2254

2255
    allocate (dl_over_b(2*ntgrid+1))
×
2256
    dl_over_b = delthet * jacob
×
2257

2258
    allocate (phiextend(ntg_extend,ntheta0,naky)) ; phiextend = 0.0
×
2259
    allocate (phir(-ntgrid:ntgrid,ntheta0))
×
2260

2261
    cfnc = 0.0 ; phiextend = 0.0
×
2262
    offset = ((ntheta0-1)/jtwist)*(2*ntgrid+1)/2
×
2263
    call reorder_kx (phinew(:, :, 1), phir(:, :))
×
2264
    phiextend(offset+1:offset+(2*ntgrid+1),:,1) = phir
×
2265
    do it = 1, ntheta0
×
2266
       do im = 1, 2*ntgrid+1
×
2267
          do ig = im+offset, offset+(2*ntgrid+1)
×
2268
             igmod = mod(ig-offset-1,2*ntgrid+1)+1
×
2269
             cfnc(im,it,1) = cfnc(im,it,1) &
×
2270
                  + phiextend(ig,it,1)*conjg(phiextend(ig-im+1,it,1)) &
×
2271
                  * dl_over_b(igmod)
×
2272
          end do
2273
       end do
2274
       if (abs(cfnc(1, it, 1)) > epsilon(0.0)) then
×
2275
         cfnc(:, it, 1) = cfnc(:, it, 1) / cfnc(1, it, 1)
×
2276
       end if
2277
    end do
2278

2279
    do ik = 2, naky
×
2280
       call reorder_kx (phinew(:, :, ik), phir(:, :))
×
2281
       ! shift in kx due to parallel boundary condition
2282
       ! also the number of independent theta0s
2283
       itshift = jtwist*(ik-1)
×
2284
       do it = 1, min(itshift,ntheta0)
×
2285
          ! number of connections between kx's
2286
          nconnect = (ntheta0-it)/itshift
×
2287
          ! shift of theta index to account for fact that not all ky's
2288
          ! have same length in extended theta
2289
          offset = (2*ntgrid+1)*((ntheta0-1)/jtwist-nconnect)/2
×
2290
          do ig = 1, nconnect+1
×
2291
             phiextend(offset+(ig-1)*(2*ntgrid+1)+1:offset+ig*(2*ntgrid+1),it,ik) &
×
2292
                  = phir(:,ntheta0-it-(ig-1)*itshift+1)
×
2293
          end do
2294
          do im = 1, (2*ntgrid+1)*(nconnect+1)
×
2295
             do ig = im+offset, offset+(2*ntgrid+1)*(nconnect+1)
×
2296
                igmod = mod(ig-offset-1,2*ntgrid+1)+1
×
2297
                cfnc(im,it,ik) = cfnc(im,it,ik) &
×
2298
                     + phiextend(ig,it,ik)*conjg(phiextend(ig-im+1,it,ik)) &
×
2299
                     * dl_over_b(igmod)
×
2300
             end do
2301
          end do
2302
          cfnc(:,it,ik) = cfnc(:,it,ik) / cfnc(1,it,ik)
×
2303
       end do
2304
    end do
2305

2306
    phi2extend = real(phiextend*conjg(phiextend))
×
2307

2308
    deallocate (dl_over_b, phir, phiextend)
×
2309
  end subroutine correlation_extend
×
2310

2311
  !> Go from kx_ind = [0, 1, ..., N, -N, ...., -1]
2312
  !> to [-N, ....,-1,0,1,....,N]
2313
  subroutine reorder_kx (unord, ord)
×
2314
    use kt_grids, only: ntheta0
2315
    implicit none
2316
    complex, dimension (:, :), intent (in) :: unord
2317
    complex, dimension (:, :), intent (out) :: ord
2318
    ord = cshift(unord, -ntheta0 / 2, dim = 2)
×
2319
  end subroutine reorder_kx
×
2320

2321
  !> Calculate the correlation function on the physical domain
2322
  subroutine correlation (cfnc_2pi)
×
2323
    use kt_grids, only: naky, ntheta0
2324
    use theta_grid, only: ntgrid
2325
    use fields_arrays, only: phinew
2326
    implicit none
2327
    complex, dimension (-ntgrid:,:), intent (out) :: cfnc_2pi
2328
    integer :: ik, it, ig
2329
    real :: fac
2330

2331
    cfnc_2pi = 0.0
×
2332

2333
    do ik = 1, naky
×
2334
       if (ik==1) then
×
2335
          fac = 1.0
×
2336
       else
2337
          fac = 0.5
×
2338
       end if
2339
       do it = 1, ntheta0
×
2340
          do ig = -ntgrid, ntgrid
×
2341
             cfnc_2pi(ig,ik) = cfnc_2pi(ig,ik) + phinew(0,it,ik)*conjg(phinew(ig,it,ik))*fac
×
2342
          end do
2343
       end do
2344
    end do
2345

2346
  end subroutine correlation
×
2347

2348
  !> Write \(g(v_\parallel,v_\perp)\) at `ik=it=is=1, ig=0` to text file `<runname>.dist`
2349
  subroutine do_write_f (unit)
×
2350
    use mp, only: proc0, send, receive
2351
    use gs2_layouts, only: g_lo, ik_idx, it_idx, is_idx, il_idx, ie_idx, idx_local, proc_id
2352
    use le_grids, only: al, energy, forbid, negrid, nlambda, speed
2353
    use theta_grid, only: bmag
2354
    use dist_fn_arrays, only: gnew
2355
    use species, only: nspec
2356
    integer, intent(in) :: unit
2357
    integer :: iglo, ik, it, is
2358
    integer :: ie, il, ig
2359
    real :: vpa, vpe
2360
    complex, dimension(2) :: gtmp
2361
    real, dimension (:,:), allocatable, save :: xpts
2362
    real, dimension (:), allocatable, save :: ypts
2363
    !> Change argument of bmag depending on which theta you want to write out
2364
    integer, parameter :: ig_index = 0
2365
    if (.not. allocated(xpts)) then
×
2366
       allocate(xpts(negrid,nspec))
×
2367
       allocate(ypts(nlambda))
×
2368

2369
       ! should really just get rid of xpts and ypts
2370
       xpts = speed
×
2371
       ypts = 0.0
×
2372

2373
       do il=1,nlambda
×
2374
          ypts(il) = sqrt(max(0.0,1.0-al(il)*bmag(ig_index)))
×
2375
       end do
2376

2377
       if (proc0) then
×
2378
          write(unit, *) negrid*nlambda
×
2379
       end if
2380
    endif
2381

2382
    do iglo = g_lo%llim_world, g_lo%ulim_world
×
2383
       ik = ik_idx(g_lo, iglo) ; if (ik /= 1) cycle
×
2384
       it = it_idx(g_lo, iglo) ; if (it /= 1) cycle
×
2385
       is = is_idx(g_lo, iglo) ; if (is /= 1) cycle
×
2386
       ie = ie_idx(g_lo, iglo)
×
2387
       ig = ig_index
×
2388
       il = il_idx(g_lo, iglo)
×
2389
       if (idx_local (g_lo, ik, it, il, ie, is)) then
×
2390
          if (proc0) then
×
2391
             gtmp = gnew(ig, :, iglo)
×
2392
          else
2393
             call send (gnew(ig,:,iglo), 0)
×
2394
          endif
2395
       else if (proc0) then
×
2396
          call receive (gtmp, proc_id(g_lo, iglo))
×
2397
       endif
2398
       if (proc0) then
×
2399
          if (.not. forbid(ig, il)) then
×
2400
             vpa = sqrt(energy(ie,is)*max(0.0, 1.0-al(il)*bmag(ig)))
×
2401
             vpe = sqrt(energy(ie,is)*al(il)*bmag(ig))
×
2402
             write (unit, "(8(1x,e13.6))") vpa, vpe, energy(ie,is), al(il), &
×
2403
                  xpts(ie,is), ypts(il), real(gtmp(1)), real(gtmp(2))
×
2404
          end if
2405
       end if
2406
    end do
2407
    if (proc0) write (unit, *)
×
2408
  end subroutine do_write_f
×
2409

2410
  !> Write distribution function (\(g\) or possibly \(f\)?) in real space to text file
2411
  !> "<runname>.yxdist"
2412
  subroutine do_write_fyx (unit, phi, bpar)
×
2413
    use mp, only: proc0, send, receive, barrier
2414
    use gs2_layouts, only: il_idx, ig_idx, ik_idx, it_idx, is_idx, isign_idx, ie_idx
2415
    use gs2_layouts, only: idx_local, proc_id, yxf_lo, accelx_lo, g_lo
2416
    use le_grids, only: al, energy=>energy_maxw, forbid, negrid, nlambda
2417
    use theta_grid, only: bmag, ntgrid
2418
    use dist_fn_arrays, only: gnew, g_adjust, g_work, to_g_gs2, from_g_gs2
2419
    use nonlinear_terms, only: accelerated
2420
    use gs2_transforms, only: transform2
2421
    use array_utils, only: zero_array, copy
2422
#ifdef SHMEM
2423
    use shm_mpi3, only: shm_alloc, shm_free
2424
#endif
2425
    integer, intent(in) :: unit
2426
    !> Electrostatic potential and parallel magnetic field
2427
    complex, dimension (-ntgrid:,:,:), intent (in) :: phi, bpar
2428
    real, dimension (:,:), allocatable :: grs, gzf
×
2429
#ifndef SHMEM
2430
    real, dimension (:,:,:), allocatable :: agrs, agzf
×
2431
#else
2432
    real, dimension (:,:,:), pointer, contiguous :: agrs => null(), agzf => null()
2433
    complex, dimension(:,:,:), pointer, contiguous :: g0_ptr => null()
2434
#endif
2435
    real, dimension (:), allocatable :: agp0, agp0zf
×
2436
    real :: gp0, gp0zf
2437
    integer :: ig, it, ik, il, ie, is, iyxlo, isign, iaclo, iglo, acc
2438
    logical, save :: first = .true.
2439

2440
    if (accelerated) then
×
2441
#ifndef SHMEM
2442
       allocate (agrs(2*ntgrid+1, 2, accelx_lo%llim_proc:accelx_lo%ulim_alloc))
×
2443
       allocate (agzf(2*ntgrid+1, 2, accelx_lo%llim_proc:accelx_lo%ulim_alloc))
×
2444
#else
2445
       call shm_alloc(agrs, [1, 2*ntgrid+1, 1, 2, accelx_lo%llim_proc, accelx_lo%ulim_alloc])
2446
       call shm_alloc(agzf, [1, 2*ntgrid+1, 1, 2, accelx_lo%llim_proc, accelx_lo%ulim_alloc])
2447
       call shm_alloc(g0_ptr, [1, 2*ntgrid+1, 1, 2, accelx_lo%llim_proc, accelx_lo%ulim_alloc])
2448
#endif
2449
       allocate (agp0(2), agp0zf(2))
×
2450
       call zero_array(agrs); call zero_array(agzf); agp0 = 0.0; agp0zf = 0.0
×
2451
    else
2452
#ifdef SHMEM
2453
       g0_ptr => g_work
2454
#endif
2455
       allocate (grs(yxf_lo%ny, yxf_lo%llim_proc:yxf_lo%ulim_alloc))
×
2456
       allocate (gzf(yxf_lo%ny, yxf_lo%llim_proc:yxf_lo%ulim_alloc))
×
2457
       call zero_array(grs); call zero_array(gzf); gp0 = 0.0; gp0zf = 0.0
×
2458
    end if
2459

2460
    if (first) then
×
2461
       if (proc0) then
×
2462
          acc = 0
×
2463
          if (accelerated) acc = 1
×
2464
          write(unit,*) 2*negrid*nlambda, bmag(0), acc
×
2465
       end if
2466

2467
       first = .false.
×
2468
    end if
2469

2470
    call g_adjust (gnew, phi, bpar, direction = from_g_gs2)
×
2471

2472
#ifndef SHMEM
2473
    call copy(gnew, g_work)
×
2474
#else
2475
    g0_ptr = gnew
2476
#endif
2477

2478
#ifndef SHMEM
2479
    if (accelerated) then
×
2480
       call transform2 (g_work, agrs)
×
2481
    else
2482
       call transform2 (g_work, grs)
×
2483
    end if
2484

2485
    call zero_array(g_work)
×
2486
    do iglo=g_lo%llim_proc, g_lo%ulim_proc
×
2487
       ik = ik_idx(g_lo,iglo)
×
2488
       if (ik == 1) g_work(:,:,iglo) = gnew(:,:,iglo)
×
2489
    end do
2490

2491
    call g_adjust (gnew, phi, bpar, direction = to_g_gs2)
×
2492

2493
    if (accelerated) then
×
2494
       call transform2 (g_work, agzf)
×
2495
    else
2496
       call transform2 (g_work, gzf)
×
2497
    end if
2498
#else
2499
    if (accelerated) then
2500
       call transform2 (g0_ptr, agrs)
2501
    else
2502
       call transform2 (g0_ptr, grs)
2503
    end if
2504

2505
    g0_ptr = 0.0
2506
    do iglo=g_lo%llim_proc, g_lo%ulim_proc
2507
       ik = ik_idx(g_lo,iglo)
2508
       if (ik == 1) g0_ptr(:,:,iglo) = gnew(:,:,iglo)
2509
    end do
2510

2511
    call g_adjust (gnew, phi, bpar, direction = to_g_gs2)
2512

2513
    if (accelerated) then
2514
       call transform2 (g0_ptr, agzf)
2515
    else
2516
       call transform2 (g0_ptr, gzf)
2517
    end if
2518
#endif
2519

2520
    if (accelerated) then
×
2521
       do iaclo=accelx_lo%llim_world, accelx_lo%ulim_world
×
2522
          it = it_idx(accelx_lo, iaclo)
×
2523
          ik = ik_idx(accelx_lo, iaclo)
×
2524
          if (it == 1 .and. ik == 1) then
×
2525
             il = il_idx(accelx_lo, iaclo)
×
2526
             ig = 0
×
2527
             if (.not. forbid(ig,il)) then
×
2528
                ie = ie_idx(accelx_lo, iaclo)
×
2529
                is = is_idx(accelx_lo, iaclo)
×
2530

2531
                if (proc0) then
×
2532
                   if (.not. idx_local(accelx_lo, ik, it, il, ie, is)) then
×
2533
                      call receive (agp0, proc_id(accelx_lo, iaclo))
×
2534
                      call receive (agp0zf, proc_id(accelx_lo, iaclo))
×
2535
                   else
2536
                      agp0 = agrs(ig+ntgrid+1, :, iaclo)
×
2537
                      agp0zf = agzf(ig+ntgrid+1, :, iaclo)
×
2538
                   end if
2539
                else if (idx_local(accelx_lo, ik, it, il, ie, is)) then
×
2540
                   call send (agrs(ig+ntgrid+1, :, iaclo), 0)
×
2541
                   call send (agzf(ig+ntgrid+1, :, iaclo), 0)
×
2542
                end if
2543

2544
                if (proc0) then
×
2545
                   write (unit, "(6(1x,e13.6))") energy(ie), al(il), &
×
2546
                        agp0(1), agp0(2), agp0zf(1), agp0zf(2)
×
2547
                end if
2548
             end if
2549
          end if
2550
          call barrier
×
2551
       end do
2552
       deallocate(agp0, agp0zf)
×
2553
#ifndef SHMEM
2554
       deallocate(agrs, agzf)
×
2555
#else
2556
       call shm_free(agrs)
2557
       call shm_free(agzf)
2558
       call shm_free(g0_ptr)
2559
#endif
2560
    else
2561
       do iyxlo=yxf_lo%llim_world, yxf_lo%ulim_world
×
2562

2563
          ig = ig_idx(yxf_lo, iyxlo)
×
2564
          it = it_idx(yxf_lo, iyxlo)
×
2565
          if (ig == 0 .and. it == 1) then
×
2566
             il = il_idx(yxf_lo, iyxlo)
×
2567
             if (.not. forbid(ig,il)) then
×
2568
                ik = 1
×
2569
                ie = ie_idx(yxf_lo, iyxlo)
×
2570
                is = is_idx(yxf_lo, iyxlo)
×
2571
                isign = isign_idx(yxf_lo, iyxlo)
×
2572

2573
                if (proc0) then
×
2574
                   if (.not. idx_local(yxf_lo, ig, isign, it, il, ie, is)) then
×
2575
                      call receive (gp0, proc_id(yxf_lo, iyxlo))
×
2576
                      call receive (gp0zf, proc_id(yxf_lo, iyxlo))
×
2577
                   else
2578
                      gp0 = grs(ik, iyxlo)
×
2579
                      gp0zf = gzf(ik, iyxlo)
×
2580
                   end if
2581
                else if (idx_local(yxf_lo, ig, isign, it, il, ie, is)) then
×
2582
                   call send (grs(ik, iyxlo), 0)
×
2583
                   call send (gzf(ik, iyxlo), 0)
×
2584
                end if
2585

2586
                if (proc0) then
×
2587
                   write (unit, "(4(1x,e13.6),i8)") energy(ie), al(il), &
×
2588
                        gp0, gp0zf, isign
×
2589
                end if
2590
             end if
2591
          end if
2592
          call barrier
×
2593
       end do
2594
       deallocate (grs, gzf)
×
2595
    end if
2596

2597
    if (proc0) flush (unit)
×
2598

2599
    if (proc0) then
×
2600
       write(unit,*)
×
2601
    end if
2602

2603
  end subroutine do_write_fyx
×
2604
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