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

gyrokinetics / gs2 / 1970319704

06 Aug 2025 03:50PM UTC coverage: 8.18% (+0.002%) from 8.178%
1970319704

push

gitlab-ci

David Dickinson
Merged in bugfix/fix_issue_88_multiple_ncheck (pull request #1109)

3667 of 44831 relevant lines covered (8.18%)

124503.35 hits per line

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

0.0
/src/diagnostics/gs2_diagnostics_new.f90
1
!> A module for calculating and writing gs2 outputs. It can write
2
!> these outputs both to a netcdf file <run_name>.cdf or to ascii text
3
!> files. It is controlled via the namelist diagnostics_config.
4
!> This module is intended to replace the old gs2_diagnostics module with a
5
!> simpler and more structured interface.
6
module gs2_diagnostics_new
7
  use diagnostics_config, only: diagnostics_type
8
  implicit none
9

10
  private
11
  
12
  public :: init_gs2_diagnostics_new
13
  public :: finish_gs2_diagnostics_new
14
  public :: run_diagnostics
15
  public :: gnostics
16

17
  type(diagnostics_type) :: gnostics 
18

19
  logical, parameter :: debug = .false.
20

21
contains
22

23
  !> Read namelist diagnostics_config, initialise submodules,
24
  !> open output file 'run_name.cdf' and create dimensions.
25
  subroutine init_gs2_diagnostics_new(header)
×
26
    use kt_grids, only: nx, ny, naky, ntheta0
27
    use le_grids, only: nlambda, negrid
28
    use species, only: nspec
29
    use theta_grid, only: ntgrid
30
    use gs2_transforms, only: init_transforms
31
    use diagnostics_config, only: init_diagnostics_config
32
    use diagnostics_fluxes, only: init_diagnostics_fluxes
33
    use diagnostics_omega, only: init_diagnostics_omega
34
    use diagnostics_velocity_space, only: init_diagnostics_velocity_space
35
    use diagnostics_heating, only: init_diagnostics_heating
36
    use diagnostics_ascii, only: init_diagnostics_ascii
37
    use diagnostics_antenna, only: init_diagnostics_antenna
38
    use diagnostics_nonlinear_convergence, only: init_nonlinear_convergence
39
    use diagnostics_zonal_transfer, only: init_diagnostics_transfer
40
    use diagnostics_kinetic_energy_transfer, only: init_diagnostics_kinetic_energy_transfer
41
    use collisional_heating, only: init_collisional
42
    use collisions, only: heating, set_heating
43
    use gs2_save, only: save_many
44
    use file_utils, only: run_name, error_unit
45
    use mp, only: proc0, broadcast, mp_abort
46
    use gs2_diagnostics, only: check_restart_file_writeable
47
    use unit_tests, only: debug_message
48
    use standard_header, only: standard_header_type
49
    use gs2_metadata, only: create_metadata
50
    use run_parameters, only: user_comments
51
    use constants, only: run_name_size
52
    use neasyf, only: neasyf_open
53
    use gs2_io, only: define_dims, nc_norms, nc_species, nc_geo, save_input, get_dim_length, nc_grids_mymovie
54
    use warning_helpers, only: is_zero
55
    implicit none
56
    !> Header for files with build and run information
57
    type(standard_header_type), intent(in) :: header
58
    logical :: ex, accelerated
59
    character(run_name_size) :: filename
60
    
61
    call debug_message(gnostics%verbosity, &
62
      'gs2_diagnostics_new::init_gs2_diagnostics_new starting')
×
63
    call init_diagnostics_config(gnostics)
×
64
    call debug_message(gnostics%verbosity, &
65
      'gs2_diagnostics_new::init_gs2_diagnostics_new initialized config')
×
66
    call check_parameters
×
67
    call check_restart_file_writeable(gnostics%file_safety_check, &
68
                                      gnostics%save_for_restart, &
69
                                      gnostics%save_distfn)
×
70
    call debug_message(gnostics%verbosity, &
71
      'gs2_diagnostics_new::init_gs2_diagnostics_new  checked restart file')
×
72
    
73
    call debug_message(gnostics%verbosity, &
74
      'gs2_diagnostics_new::init_gs2_diagnostics_new inialized vol avgs')
×
75
    
76
    !!!!!!!!!!!!!!!!!!!!!!!
77
    !! Adjust other modules
78
    !!!!!!!!!!!!!!!!!!!!!!!
79
    save_many = gnostics%save_many
×
80

81
    if (.not. gnostics%write_any) return
×
82
    
83
    gnostics%user_time_old = 0.0
×
84
    
85
    if (gnostics%write_heating .and. .not. heating) then
×
86
       if (proc0) write(*,'("Warning: Disabling write_heating as collisions:heating is false.")')
×
87
       gnostics%write_heating = .false.
×
88
    else if (heating .and. .not. &
×
89
       (gnostics%write_heating .or. gnostics%write_collisional)) then
90
       call set_heating(.false.)
×
91
    end if
92

93
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
94
    !!! Open Text Files (if required)
95
    !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
96
    if (proc0) call set_ascii_file_switches
×
97
    if (proc0) call init_diagnostics_ascii(gnostics%ascii_files)
×
98
    
99
    !!!!!!!!!!!!!!!!!!!!!!!!!!!
100
    ! Initialise submodules
101
    !!!!!!!!!!!!!!!!!!!!!!!!!!
102
    call init_diagnostics_fluxes(gnostics)
×
103
    call init_diagnostics_omega(gnostics)
×
104
    !if (gnostics%write_max_verr) gnostics%write_verr = .true.
105
    call init_diagnostics_velocity_space(gnostics)
×
106
    call init_diagnostics_antenna(gnostics)
×
107
    call init_diagnostics_transfer(gnostics)
×
108
    call init_collisional(gnostics)
×
109

110
    if (gnostics%write_kinetic_energy_transfer) call init_diagnostics_kinetic_energy_transfer
×
111
    if (gnostics%write_heating) call init_diagnostics_heating(gnostics)
×
112
    if (gnostics%use_nonlin_convergence) call init_nonlinear_convergence(gnostics%conv_nstep_av, gnostics%nwrite)
×
113
    
114
    filename = trim(trim(run_name)//'.out.nc')
×
115

116
    call debug_message(gnostics%verbosity, &
117
      'gs2_diagnostics_new::init_gs2_diagnostics_new opening file')
×
118
    if (proc0) then
×
119
       inquire(file=trim(run_name)//'.out.nc', exist=ex)
×
120
       if (gnostics%append_old .and. ex) then
×
121
         gnostics%appending=.true.
×
122
         gnostics%file_id = neasyf_open(trim(filename), "rw")
×
123
         gnostics%nout = get_dim_length(gnostics%file_id, "t")
×
124
       else
125
         gnostics%appending=.false.
×
126
         gnostics%file_id = neasyf_open(trim(filename), "w")
×
127
         call create_metadata(gnostics%file_id, "GS2 Simulation Data", header, user_comments)
×
128
         call debug_message(gnostics%verbosity, &
129
           'gs2_diagnostics_new::init_gs2_diagnostics_new written metadata')
×
130

131
         ! Write constants/parameters
132
         call define_dims(gnostics%file_id, gnostics%write_correlation_extend)
×
133
         call nc_norms(gnostics%file_id)
×
134
         call nc_species(gnostics%file_id)
×
135
         call nc_geo(gnostics%file_id)
×
136
         call save_input(gnostics%file_id)
×
137
         gnostics%nout = 1
×
138

139
         if (gnostics%make_movie) then
×
140
           call init_transforms(ntgrid, naky, ntheta0, nlambda, negrid, nspec, nx, ny, accelerated)
×
141
           call nc_grids_mymovie(gnostics%file_id)
×
142
         end if
143
       end if
144
    end if
145
    call debug_message(gnostics%verbosity, &
146
      'gs2_diagnostics_new::init_gs2_diagnostics_new opened file')
×
147

148
    ! Vital that other procs know we are appending
149
    call broadcast(gnostics%appending)
×
150
    call broadcast(gnostics%nout)
×
151

152
    call debug_message(gnostics%verbosity, &
153
      'gs2_diagnostics_new::init_gs2_diagnostics_new finished')
×
154
    
155
  end subroutine init_gs2_diagnostics_new
156

157
  !> FIXME : Add documentation  
158
  subroutine check_parameters
×
159
    use run_parameters, only: has_apar
160
    use file_utils, only: error_unit
161
    use mp, only: proc0
162
    implicit none
163
    if ((gnostics%print_line .or. gnostics%write_line) .and. .not.(gnostics%write_fields.and.gnostics%write_omega)) then 
×
164
       if (proc0) write (error_unit(), *) 'print_line and write_line require both write_fields and write_omega... enabling'
×
165
       gnostics%write_fields = .true.
×
166
       gnostics%write_omega = .true.
×
167
    end if
168
    if ((gnostics%print_flux_line .or. gnostics%write_flux_line) .and. .not.gnostics%write_fields) then 
×
169
       if (proc0) write (error_unit(), *) 'print_flux_line and write_flux_line require both write_fields ... enabling'
×
170
       gnostics%write_fields = .true.
×
171
    end if
172
    if (gnostics%write_jext .and. .not. has_apar) then
×
173
       if (proc0) write (*,*) "ERROR: it doesn't make sense to switch on write_jext without apar"
×
174
       !SHOULD THIS BE MP_ABORT? COULD WE NOT JUST DISABLE THE DIAGNOSTIC?
175
       stop 1
×
176
    end if
177
    
178
  end subroutine check_parameters
×
179

180
  !> This subroutine determines which ascii output files are enabled
181
  !! (i.e., opened, flushed at each write, and then closed).
182
  !! If an ascii file is not enabled here, writing to it will 
183
  !! cause some indeterminate unpleasant behaviour
184
  !!
185
  !! Note that the .out file is always enabled
186
  subroutine set_ascii_file_switches
×
187
    implicit none
188
    gnostics%ascii_files%write_to_out   = gnostics%write_ascii
×
189
    !gnostics%ascii_files%write_to_fields = gnostics%write_fields  .and.  gnostics%write_ascii
190
    gnostics%ascii_files%write_to_heat   = gnostics%write_heating .and.  gnostics%write_ascii
×
191
    gnostics%ascii_files%write_to_heat2  = gnostics%write_heating .and.  gnostics%write_ascii
×
192
    gnostics%ascii_files%write_to_lpc    = gnostics%write_verr    .and.  gnostics%write_ascii
×
193
    gnostics%ascii_files%write_to_vres   = gnostics%write_verr    .and.  gnostics%write_ascii
×
194
    gnostics%ascii_files%write_to_vres2  = gnostics%write_verr    .and.  gnostics%write_ascii
×
195
    gnostics%ascii_files%write_to_cres   = gnostics%write_cerr    .and.  gnostics%write_ascii
×
196
    gnostics%ascii_files%write_to_dist   = gnostics%write_g    .and.  gnostics%write_ascii
×
197
    gnostics%ascii_files%write_to_yxdist   = gnostics%write_gyx    .and.  gnostics%write_ascii
×
198
    gnostics%ascii_files%write_to_phase  = gnostics%write_cross_phase .and.  gnostics%write_ascii
×
199
    gnostics%ascii_files%write_to_jext   = gnostics%write_jext    .and.  gnostics%write_ascii
×
200
    gnostics%ascii_files%write_to_parity = gnostics%write_parity  .and.  gnostics%write_ascii
×
201
    gnostics%ascii_files%write_to_eigenfunc = gnostics%write_eigenfunc .and.  gnostics%write_ascii
×
202
  end subroutine set_ascii_file_switches
×
203

204
  !> Close the output file and deallocate arrays
205
  subroutine finish_gs2_diagnostics_new
×
206
    use diagnostics_fluxes, only: finish_diagnostics_fluxes
207
    use diagnostics_omega, only: finish_diagnostics_omega
208
    use diagnostics_heating, only: finish_diagnostics_heating
209
    use diagnostics_ascii, only: finish_diagnostics_ascii
210
    use diagnostics_config, only: finish_diagnostics_config
211
    use diagnostics_antenna, only: finish_diagnostics_antenna
212
    use diagnostics_nonlinear_convergence, only: finish_nonlinear_convergence
213
    use diagnostics_velocity_space, only: finish_diagnostics_velocity_space
214
    use collisional_heating, only: finish_collisional
215
    use diagnostics_kinetic_energy_transfer, only: finish_diagnostics_kinetic_energy_transfer
216
    use gs2_diagnostics, only: save_restart_dist_fn, do_write_geom, do_write_fyx, do_write_f
217
    use mp, only: proc0
218
    use fields_arrays, only: phinew, bparnew
219
    use unit_tests, only: debug_message
220
    use neasyf, only: neasyf_close
221
    implicit none
222
    integer, parameter :: verb=3
223
    if (.not. gnostics%write_any) return
×
224
    
225
    call debug_message(verb, 'gs2_diagnostics_new::finish_gs2_diagnostics_new &
226
         & calling save_restart_dist_fn')
×
227
    call save_restart_dist_fn(gnostics%save_for_restart, &
228
         gnostics%save_distfn, &
229
         gnostics%save_glo_info_and_grids, &
230
         gnostics%save_velocities, &
231
         gnostics%user_time)
×
232

233
    call debug_message(verb, 'gs2_diagnostics_new::finish_gs2_diagnostics_new &
234
         & calling run_old_final_routines')
×
235
    call run_old_final_routines
×
236
    
237
    call debug_message(verb, 'gs2_diagnostics_new::finish_gs2_diagnostics_new finishing submodules')
×
238
    call finish_diagnostics_fluxes
×
239
    call finish_diagnostics_omega
×
240
    call finish_collisional
×
241
    call finish_diagnostics_antenna(gnostics)
×
242
    call finish_diagnostics_velocity_space()
×
243
    call finish_diagnostics_kinetic_energy_transfer
×
244
    
245
    if (gnostics%use_nonlin_convergence) call finish_nonlinear_convergence()
×
246
    if (gnostics%write_heating) call finish_diagnostics_heating(gnostics)
×
247
    if (proc0) then
×
248
       if(proc0.and.debug) write(*,*) "Closing new diagnostics"
249
       call neasyf_close(gnostics%file_id)
×
250
    end if
251
    
252
    ! Random stuff that needs to be put in properly or removed
253
    ! Note we don't use gnostics%ascii_files%write_to_yxdist here
254
    ! because do_write_fyx is collective but gnostics%ascii_files%write_to_yxdist
255
    ! is only set on proc0
256
    if (gnostics%write_ascii .and. gnostics%write_gyx) &
×
257
         call do_write_fyx (gnostics%ascii_files%yxdist, phinew, bparnew)
×
258
    if (gnostics%write_ascii .and. gnostics%write_g) &
×
259
         call do_write_f (gnostics%ascii_files%dist)
×
260
    if (gnostics%write_ascii) call do_write_geom()
×
261
    if (proc0) call finish_diagnostics_ascii(gnostics%ascii_files)
×
262

263
    call finish_diagnostics_config(gnostics)
×
264
  end subroutine finish_gs2_diagnostics_new
265

266
  !> FIXME : Add documentation  
267
  subroutine run_diagnostics_to_be_updated
×
268
    use fields_arrays, only: phinew, bparnew
269
    use gs2_diagnostics, only: do_write_fyx, do_write_f
270
    implicit none
271
    integer :: nwrite_large
272

273
    nwrite_large = gnostics%nwrite*gnostics%nwrite_mult
×
274
    if (mod(gnostics%istep,nwrite_large) /= 0) return
×
275

276
    ! Random stuff that needs to be put in properly or removed
277
    ! Note we don't use gnostics%ascii_files%write_to_yxdist here
278
    ! because do_write_fyx is collective but gnostics%ascii_files%write_to_yxdist
279
    ! is only set on proc0
280
    if (gnostics%write_ascii .and. gnostics%write_gyx) &
×
281
         call do_write_fyx (gnostics%ascii_files%yxdist, phinew, bparnew)
×
282
    if (gnostics%write_ascii .and. gnostics%write_g) &
×
283
         call do_write_f (gnostics%ascii_files%dist)
×
284
  end subroutine run_diagnostics_to_be_updated
285

286
  !> Calculates and write the QL flux metric to netcdf
287
  subroutine write_ql_metric(gnostics)
×
288
    use gs2_diagnostics, only: calculate_simple_quasilinear_flux_metric_by_k
289
    use gs2_diagnostics, only: calculate_instantaneous_omega
290
    use kt_grids, only: ntheta0, naky
291
    use gs2_io, only: nc_write_ql_metric
292
    implicit none
293
    type(diagnostics_type), intent(inout) :: gnostics
294
    real, dimension(ntheta0, naky) :: growth_rates
×
295
    if (.not. gnostics%writing) return
×
296

297
    growth_rates = aimag(calculate_instantaneous_omega(&
×
298
         ig = gnostics%igomega, tolerance = gnostics%omegatol))
×
299
    call nc_write_ql_metric(gnostics%file_id, gnostics%nout, &
300
         ql_metric = calculate_simple_quasilinear_flux_metric_by_k(growth_rates))
×
301
  end subroutine write_ql_metric
302
  
303
  !> Create or write all variables according to the value of istep:
304
  !! istep=-1 --> Create all netcdf variables
305
  !! istep=0 --> Write constant arrays/parameters (e.g. aky) and initial values
306
  !! istep>0 --> Write variables
307
  subroutine run_diagnostics(istep_in, exit, force)
×
308
    use gs2_time, only: user_time, tunits
309
    use mp, only: proc0
310
    use diagnostics_zonal_transfer, only: write_zonal_transfer, calculate_zonal_transfer
311
    use diagnostics_kinetic_energy_transfer, only: write_kinetic_energy_transfer, calculate_kinetic_energy_transfer
312
    use collisional_heating, only: write_collisional, calculate_collisional   
313
    use diagnostics_printout, only: print_flux_line, print_line
314
    use diagnostics_printout, only: write_flux_line, write_line
315
    use diagnostics_fluxes, only: calculate_fluxes
316
    use diagnostics_fields, only: write_fields, write_movie
317
    use diagnostics_fields, only: write_eigenfunc
318
    use diagnostics_moments, only: write_moments, write_full_moments_notgc
319
    use diagnostics_omega, only: calculate_omega, write_omega
320
    use diagnostics_velocity_space, only: write_velocity_space_checks
321
    use diagnostics_velocity_space, only: write_collision_error
322
    use diagnostics_heating, only: calculate_heating, write_heating
323
    use diagnostics_nonlinear_convergence, only: check_nonlin_convergence
324
    use diagnostics_turbulence, only: write_cross_phase
325
    use diagnostics_antenna, only: write_jext, write_lorentzian
326
    use diagnostics_ascii, only: flush_output_files
327
    use collisions, only: vary_vnew, ncheck
328
    use species, only: spec, has_electron_species
329
    use unit_tests, only: debug_message
330
    use mp,  only: broadcast
331
    use neasyf, only: neasyf_write
332
    use optionals, only: get_option_with_default
333
    use run_parameters, only: nstep, wstar_units
334
    use gs2_io, only: get_dim_length, nc_sync, ky_dim, time_dim
335
    use gs2_diagnostics, only: do_write_parity, do_write_nl_flux_dist, &
336
         do_write_correlation_extend, do_write_correlation, do_write_symmetry
337
    implicit none
338
    integer, intent(in) :: istep_in
339
    logical, intent(in out) :: exit
340
    logical, intent(in), optional :: force
341
    integer, parameter :: verb=3
342
    integer :: istep
343
    integer, save :: istep_last = -1
344
    logical :: do_force
345
    
346
    call broadcast(exit)
×
347

348
    call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics starting')
×
349
    do_force = get_option_with_default(force, .false.)
×
350
    
351
    gnostics%exit = exit
×
352
    
353
    if (proc0) then
×
354
      gnostics%create = (istep_in==-1) .and. .not. gnostics%appending
×
355
      gnostics%writing = .true.
×
356
    else
357
      gnostics%create = .false.
×
358
      gnostics%writing = .false.
×
359
    end if
360

361
    ! Now that we've used istep to work out what operations we want
362
    ! to do, ensure the istep value is valid.
363
    istep = istep_in
×
364
    if(istep_in == -1) istep = 0
×
365
    gnostics%istep = istep
×
366

367
    gnostics%calculate_fluxes = (gnostics%write_fluxes &
368
         .or.  gnostics%print_flux_line &
369
         .or.  gnostics%write_flux_line)
×
370

371
    gnostics%user_time = user_time
×
372
    if (istep == 0) gnostics%start_time = user_time
×
373
    
374
    if (istep > 0) then
×
375
       call calculate_omega(gnostics)
×
376
       if (gnostics%write_heating) call calculate_heating (gnostics)
×
377
    end if
378
    call broadcast(gnostics%exit)
×
379

380
    call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics calculated &
381
      & omega and heating')
×
382

383
    if ((istep /= istep_last) .and. (mod(istep, gnostics%nwrite) == 0 .or. gnostics%exit .or. do_force)) then
×
384
       ! If istep_in = -1 (to indicate we're setting things up) then we enter
385
       ! this block (by forcing istep=0), but only to define variables - not to write them.
386
       ! We intend to write them on the next call when istep_in = 0, but if we were to
387
       ! record istep_last = istep when istep_in = -1 then we end up with istep_last = 0
388
       ! and we would actually skip the real istep_in = 0 call.
389
       if (istep_in > -1) istep_last = istep
×
390

391
       if (gnostics%writing) then
×
392
         call neasyf_write(gnostics%file_id, time_dim, user_time, dim_names=[time_dim], start=[gnostics%nout])
×
393
         if (wstar_units) then
×
394
            call neasyf_write(gnostics%file_id, "t_wstar", user_time * tunits, dim_names=[ky_dim, time_dim], &
×
395
                 start=[1, gnostics%nout], long_name="Time (wstar)", units="L/vt")
×
396
         end if
397
       end if
398

399
       gnostics%user_time = user_time
×
400
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics starting write sequence')
×
401
       if (gnostics%write_omega)  call write_omega(gnostics)
×
402
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics written omega')
×
403
       if (gnostics%write_fields) call write_fields(gnostics)
×
404
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics written fields')
×
405
       if (gnostics%write_ql_metric)  call write_ql_metric(gnostics)
×
406
       if (gnostics%calculate_fluxes) call calculate_fluxes(gnostics) ! NB  also writes fluxes if on
×
407
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics calculated fluxes')
×
408
       if (gnostics%write_symmetry) then
×
409
         call do_write_symmetry(gnostics%file_id, gnostics%nout)
×
410
       end if
411
       if (gnostics%write_nl_flux_dist) call do_write_nl_flux_dist(gnostics%file_id, gnostics%nout)
×
412
       if (gnostics%write_parity) call do_write_parity(gnostics%user_time, gnostics%ascii_files%parity, gnostics%write_ascii)
×
413
       if (gnostics%write_verr) call write_velocity_space_checks(gnostics, .false.)
×
414
       if (gnostics%write_cerr) call write_collision_error(gnostics) ! NB only ascii atm
×
415
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics writing moments')
×
416
       if (gnostics%write_moments) call write_moments(gnostics)
×
417
       if (gnostics%write_full_moments_notgc) call write_full_moments_notgc(gnostics)
×
418
       if (gnostics%make_movie) call write_movie(gnostics)
×
419
       if (gnostics%write_heating) call write_heating(gnostics)
×
420
       if (gnostics%use_nonlin_convergence) call check_nonlin_convergence(gnostics)
×
421
       if (gnostics%write_cross_phase.and.has_electron_species(spec)) call write_cross_phase(gnostics)
×
422
       if (gnostics%write_jext) call write_jext(gnostics)
×
423
       if (gnostics%write_correlation) call do_write_correlation(gnostics%file_id, gnostics%nout)
×
424
       if (gnostics%write_correlation_extend &
425
            .and. istep > nstep/4 &
426
            .and. mod(istep, gnostics%nwrite_mult * gnostics%nwrite)==0) &
×
427
            call do_write_correlation_extend(gnostics%file_id, gnostics%user_time, gnostics%user_time_old)
×
428
       if (gnostics%write_lorentzian) call write_lorentzian(gnostics)
×
429
       if (gnostics%write_eigenfunc) call write_eigenfunc(gnostics)
×
430
       
431
       if (gnostics%print_line) call print_line(gnostics)
×
432
       if (gnostics%write_line) call write_line(gnostics)
×
433
       if (proc0) then
×
434
          if (gnostics%print_flux_line) call print_flux_line(gnostics)
×
435
          if (gnostics%write_flux_line) call write_flux_line(gnostics)
×
436
       end if
437

438
       if (gnostics%write_zonal_transfer) then
×
439
          call calculate_zonal_transfer(gnostics)
×
440
          call write_zonal_transfer(gnostics)
×
441
       end if 
442

443
       if (gnostics%write_kinetic_energy_transfer) then
×
444
          call calculate_kinetic_energy_transfer
×
445
          if (gnostics%writing) call write_kinetic_energy_transfer(gnostics%file_id, gnostics%nout)
×
446
       end if
447

448
       if (gnostics%write_collisional) then  !< new diagnostic, calulate and write in new variable
×
449
          call calculate_collisional()
×
450
          call write_collisional(gnostics)
×
451
       end if
452

453
       call run_diagnostics_to_be_updated
×
454

455
       ! Don't sync movie file because it's the same as the main file
456
       if (gnostics%writing) call nc_sync(gnostics%file_id, gnostics%nout, -1, -1, gnostics%nc_sync_freq)
×
457
       if (proc0 .and. gnostics%write_ascii) call flush_output_files(gnostics%ascii_files)
×
458
       
459
       ! Update time used for time averages
460
       gnostics%user_time_old = gnostics%user_time
×
461

462
       gnostics%nout = gnostics%nout + 1
×
463
    else if (mod(istep, ncheck) == 0) then
×
464
       ! These lines cause the automated checking of velocity space resolution
465
       ! and correction by varying collisionality
466
       if (gnostics%write_verr .and. vary_vnew) call write_velocity_space_checks(gnostics, .true.)
×
467
    end if
468

469
    call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics finished')
×
470
    exit = gnostics%exit
×
471
    ! We don't currently need the below broadcast but we leave it in case any future
472
    ! diagnostic ends up only setting exit / gnostics%exit on proc0
473
    call broadcast(exit)
×
474
  end subroutine run_diagnostics
×
475

476
  !> FIXME : Add documentation  
477
  subroutine run_old_final_routines
×
478
    use diagnostics_final_routines,only: do_write_final_fields
479
    use diagnostics_final_routines,only: do_write_kpar
480
    use diagnostics_final_routines,only: do_write_final_epar
481
    use diagnostics_final_routines,only: do_write_final_db
482
    use diagnostics_final_routines,only: do_write_final_moments
483
    use diagnostics_final_routines,only: do_write_final_antot
484
    use diagnostics_final_routines,only: do_write_gs
485
    use diagnostics_final_routines,only: init_par_filter
486
    use diagnostics_fields, only: get_phi0
487
    use nonlinear_terms, only: nonlin
488
    use antenna, only: dump_ant_amp
489
    use mp, only: proc0
490
    use kt_grids, only: ntheta0, naky
491
    use unit_tests, only: debug_message
492
    implicit none
493
    complex, dimension (ntheta0, naky) :: phi0
×
494
    integer, parameter :: verb=3
495
    
496
    if(gnostics%write_kpar.or.gnostics%write_gs) call init_par_filter
×
497

498
    if (proc0) then
×
499
       call debug_message(verb, 'gs2_diagnostics_new::run_old_final_routines &
500
         & calling do_write_final_fields')
×
501
       if (gnostics%write_final_fields) call do_write_final_fields(gnostics%write_ascii, &
×
502
            file_id=gnostics%file_id)
×
503
       call debug_message(verb, 'gs2_diagnostics_new::run_old_final_routines &
504
         & calling do_write_kpar')
×
505
       if (gnostics%write_kpar) call do_write_kpar(gnostics%write_ascii)
×
506
       call debug_message(verb, 'gs2_diagnostics_new::run_old_final_routines &
507
         & calling do_write_final_epar')
×
508
       if (gnostics%write_final_epar) call do_write_final_epar(gnostics%write_ascii, &
×
509
            file_id=gnostics%file_id)
×
510
       
511
       ! definition here assumes we are not using wstar_units
512
       call debug_message(verb, 'gs2_diagnostics_new::run_old_final_routines &
513
         & calling do_write_final_db')
×
514
       if (gnostics%write_final_db) call do_write_final_db(gnostics%write_ascii)
×
515
    end if
516

517
    phi0 = get_phi0()
×
518
    if (gnostics%write_final_moments) &
×
519
      call do_write_final_moments(phi0, use_normalisation=gnostics%write_eigenfunc, &
×
520
                                  write_text=gnostics%write_ascii, &
521
                                  file_id=gnostics%file_id)
×
522

523
    call debug_message(verb, 'gs2_diagnostics_new::run_old_final_routines &
524
      & calling do_write_final_antot')
×
525
    
526
    if (gnostics%write_final_antot) call do_write_final_antot(gnostics%write_ascii, &
×
527
         file_id=gnostics%file_id)
×
528

529
    if (proc0) call dump_ant_amp
×
530
    
531
    if (nonlin.and.gnostics%write_gs) call do_write_gs(gnostics%write_ascii)
×
532
    call debug_message(verb, 'gs2_diagnostics_new::run_old_final_routines &
533
         & finished')
×
534
    
535
  end subroutine run_old_final_routines
×
536
end module gs2_diagnostics_new
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