• 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/diagnostics_config.f90
1
!> A module for handling the configuration of the diagnostics
2
!! module via the namelist diagnostics_config.
3
module diagnostics_config
4
  use diagnostics_ascii, only: diagnostics_ascii_type
5
  use diagnostics_configuration, only: diagnostics_config_type
6
  implicit none
7

8
  private
9

10
  public :: init_diagnostics_config, finish_diagnostics_config
11
  public :: diagnostics_type, results_summary_type, read_parameters
12
  public :: override_screen_printout_options
13

14
  real, parameter :: initial_value = -1.0
15
  
16
  !> A type for storing the current results of the simulation
17
  type results_summary_type
18
     real :: phi2 = initial_value
19
     real :: apar2 = initial_value
20
     real :: bpar2 = initial_value
21
     real :: total_heat_flux = initial_value
22
     real :: total_momentum_flux = initial_value
23
     real :: total_particle_flux = initial_value
24
     real :: max_growth_rate = initial_value
25
     real :: diffusivity = initial_value
26

27
     ! Individual heat fluxes
28
     real, dimension(:), allocatable :: species_es_heat_flux
29
     real, dimension(:), allocatable :: species_apar_heat_flux
30
     real, dimension(:), allocatable :: species_bpar_heat_flux
31

32
     ! Total fluxes
33
     real, dimension(:), allocatable :: species_heat_flux
34
     real, dimension(:), allocatable :: species_momentum_flux
35
     real, dimension(:), allocatable :: species_particle_flux
36
     real, dimension(:), allocatable :: species_energy_exchange
37

38
     ! Average total fluxes
39
     real, dimension(:), allocatable :: species_heat_flux_avg
40
     real, dimension(:), allocatable :: species_momentum_flux_avg
41
     real, dimension(:), allocatable :: species_particle_flux_avg
42

43
     ! Heating
44
     real, dimension(:), allocatable :: species_heating
45
     real, dimension(:), allocatable :: species_heating_avg
46

47
     ! Growth rates
48
     complex, dimension(:,:), allocatable :: omega_average
49

50
     ! free energy transfer due to nonlinearity
51
     complex, dimension(:,:), allocatable :: zonal_transfer
52

53
  end type results_summary_type
54

55
  !> A type for storing the diagnostics configuration,
56
  !! a reference to the output file, and current 
57
  !! results of the simulation
58
  type diagnostics_type
59
     type(diagnostics_ascii_type) :: ascii_files
60
     type(results_summary_type) :: current_results
61
     !> NetCDF file ID
62
     integer :: file_id
63
     !> Current timestep
64
     integer :: nout = 1
65
     integer :: istep
66
     integer :: verbosity = 3
67
     logical :: create
68
     logical :: writing
69
     logical :: exit
70
     logical :: calculate_fluxes
71
     logical :: appending
72
     real :: user_time
73
     real :: user_time_old
74
     real :: start_time
75
     integer :: nwrite
76
     integer :: nwrite_mult
77
     logical :: write_any
78
     logical :: append_old
79
     logical :: serial_netcdf4
80
     integer :: igomega
81
     logical :: print_line
82
     logical :: print_flux_line
83
     logical :: write_line
84
     logical :: write_flux_line
85
     logical :: write_fields
86
     logical :: write_phi_over_time
87
     logical :: write_apar_over_time
88
     logical :: write_bpar_over_time
89
     logical :: make_movie
90
     logical :: write_moments
91
     logical :: write_full_moments_notgc
92
     logical :: write_ntot_over_time
93
     logical :: write_density_over_time
94
     logical :: write_upar_over_time
95
     logical :: write_tperp_over_time
96
     logical :: write_fluxes
97
     logical :: write_fluxes_by_mode
98
     logical :: write_symmetry
99
     logical :: write_nl_flux_dist
100
     logical :: write_parity
101
     logical :: write_omega
102
     logical :: write_ql_metric
103
     integer :: navg
104
     real :: omegatinst
105
     real :: omegatol
106
     real :: damped_threshold
107
     real :: omega_checks_start
108
     logical :: exit_when_converged
109
     logical :: write_verr
110
     logical :: write_cerr
111
     logical :: write_max_verr
112
     logical :: write_heating
113
     logical :: write_ascii
114
     logical :: write_gyx
115
     logical :: write_g
116
     integer :: conv_nstep_av
117
     real :: conv_test_multiplier
118
     integer :: conv_min_step
119
     integer :: conv_max_step
120
     integer :: conv_nsteps_converged
121
     logical :: use_nonlin_convergence
122
     logical :: write_cross_phase
123
     logical :: write_correlation
124
     logical :: write_correlation_extend
125
     logical :: write_jext
126
     logical :: write_lorentzian
127
     logical :: write_eigenfunc
128
     logical :: write_final_fields
129
     logical :: write_kpar
130
     logical :: write_final_epar
131
     logical :: write_final_db
132
     logical :: write_final_moments
133
     logical :: write_final_antot
134
     logical :: write_gs
135
     integer :: nsave
136
     logical :: save_for_restart
137
     logical :: save_many
138
     logical :: file_safety_check
139
     logical :: save_distfn
140
     logical :: save_glo_info_and_grids
141
     logical :: save_velocities
142
     logical :: write_zonal_transfer
143
     logical :: write_kinetic_energy_transfer
144
     logical :: write_collisional
145
     logical :: write_omavg
146
     logical :: ob_midplane
147
     logical :: write_avg_moments
148
     integer :: nmovie
149
     integer :: nc_sync_freq
150
  end type diagnostics_type
151

152
  !> Used for testing... causes screen printout to be 
153
  !! generated regardless of the values of print_line 
154
  !! and print_flux_line if set to true
155
  logical :: override_screen_printout_options = .false.
156

157
  logical :: initialized = .false.
158
  
159
contains
160
  subroutine init_diagnostics_config(gnostics, new_gs2_diagnostics_config_in)
×
161
    use unit_tests, only: debug_message
162
    implicit none
163
    type(diagnostics_type), intent(inout) :: gnostics
164
    type(diagnostics_config_type), intent(in), optional :: new_gs2_diagnostics_config_in
165
    if(initialized) return
×
166
    initialized = .true.
×
167
    call debug_message(3, 'diagnostics_config::init_diagnostics_config &
168
      & starting')
×
169
    call read_parameters(gnostics, new_gs2_diagnostics_config_in)
×
170
    call debug_message(3, 'diagnostics_config::init_diagnostics_config &
171
      & read_parameters')
×
172
    call allocate_current_results(gnostics)
×
173
  end subroutine init_diagnostics_config
174

175
  subroutine finish_diagnostics_config(gnostics)
×
176
    use diagnostics_configuration, only: diagnostics_config
177
    implicit none
178
    type(diagnostics_type), intent(inout) :: gnostics
179
    initialized = .false.
×
180
    call deallocate_current_results(gnostics)
×
181
    call diagnostics_config%reset()
×
182
  end subroutine finish_diagnostics_config
×
183

184
  subroutine allocate_current_results(gnostics)
×
185
    use species, only: nspec
186
    use kt_grids, only: naky, ntheta0
187
    implicit none
188
    type(diagnostics_type), intent(inout) :: gnostics
189

190
    allocate(gnostics%current_results%species_es_heat_flux(nspec))
×
191
    allocate(gnostics%current_results%species_apar_heat_flux(nspec))
×
192
    allocate(gnostics%current_results%species_bpar_heat_flux(nspec))
×
193
    allocate(gnostics%current_results%species_heat_flux(nspec))
×
194
    allocate(gnostics%current_results%species_momentum_flux(nspec))
×
195
    allocate(gnostics%current_results%species_particle_flux(nspec))
×
196
    allocate(gnostics%current_results%species_energy_exchange(nspec))
×
197
    allocate(gnostics%current_results%species_heat_flux_avg(nspec))
×
198
    allocate(gnostics%current_results%species_momentum_flux_avg(nspec))
×
199
    allocate(gnostics%current_results%species_particle_flux_avg(nspec))
×
200
    allocate(gnostics%current_results%species_heating(nspec))
×
201
    allocate(gnostics%current_results%species_heating_avg(nspec))
×
202
    allocate(gnostics%current_results%omega_average(ntheta0, naky))
×
203
    allocate(gnostics%current_results%zonal_transfer(ntheta0,naky))
×
204

205
  end subroutine allocate_current_results
×
206

207
  subroutine deallocate_current_results(gnostics)
×
208
    implicit none
209
    type(diagnostics_type), intent(inout) :: gnostics
210
   
211
    deallocate(gnostics%current_results%species_es_heat_flux)
×
212
    deallocate(gnostics%current_results%species_apar_heat_flux)
×
213
    deallocate(gnostics%current_results%species_bpar_heat_flux)
×
214
    deallocate(gnostics%current_results%species_heat_flux)
×
215
    deallocate(gnostics%current_results%species_momentum_flux)
×
216
    deallocate(gnostics%current_results%species_particle_flux)
×
217
    deallocate(gnostics%current_results%species_heat_flux_avg)
×
218
    deallocate(gnostics%current_results%species_momentum_flux_avg)
×
219
    deallocate(gnostics%current_results%species_particle_flux_avg)
×
220
    deallocate(gnostics%current_results%species_heating)
×
221
    deallocate(gnostics%current_results%species_heating_avg)
×
222
    deallocate(gnostics%current_results%omega_average)
×
223
    deallocate(gnostics%current_results%zonal_transfer)
×
224
  end subroutine deallocate_current_results
×
225

226
  subroutine read_parameters(gnostics, new_gs2_diagnostics_config_in, warn_nonfunctional)
×
227
    use diagnostics_configuration, only: warn_about_nonfunctional_selection, diagnostics_config
228
    use collisions, only: use_le_layout
229
    use nonlinear_terms, only: nonlin
230
    use optionals, only: get_option_with_default
231
    implicit none
232
    type(diagnostics_type), intent(out) :: gnostics
233
    type(diagnostics_config_type), intent(in), optional :: new_gs2_diagnostics_config_in
234
    logical, intent(in), optional ::warn_nonfunctional
235

236
    if (present(new_gs2_diagnostics_config_in)) diagnostics_config = new_gs2_diagnostics_config_in
×
237

238
    call diagnostics_config%init(name = 'gs2_diagnostics_knobs', requires_index = .false.)
×
239

240
    ! Print some health warnings if switches are not their default
241
    ! values and are not available in this diagnostics module
242
    if (get_option_with_default(warn_nonfunctional, .true.)) then
×
243
       call warn_about_nonfunctional_selection(diagnostics_config%ob_midplane, "ob_midplane")
×
244
       call warn_about_nonfunctional_selection(.not. diagnostics_config%write_omavg, "write_omavg")
×
245
    end if
246

247
    ! Copy out internal values into module level parameters
248
    associate(self => diagnostics_config, &
249
         append_old => gnostics%append_old, conv_max_step => gnostics%conv_max_step, &
250
         conv_min_step => gnostics%conv_min_step, conv_nstep_av => gnostics%conv_nstep_av, &
251
         conv_nsteps_converged => gnostics%conv_nsteps_converged, &
252
         conv_test_multiplier => gnostics%conv_test_multiplier, &
253
         damped_threshold => gnostics%damped_threshold, &
254
         exit_when_converged => gnostics%exit_when_converged, &
255
         file_safety_check => gnostics%file_safety_check, &
256
         igomega => gnostics%igomega, make_movie => gnostics%make_movie, &
257
         navg => gnostics%navg, &
258
         nc_sync_freq => gnostics%nc_sync_freq, nmovie => gnostics%nmovie, &
259
         nsave => gnostics%nsave, nwrite => gnostics%nwrite, &
260
         nwrite_mult => gnostics%nwrite_mult, ob_midplane => gnostics%ob_midplane, &
261
         omega_checks_start => gnostics%omega_checks_start, &
262
         omegatinst => gnostics%omegatinst, omegatol => gnostics%omegatol, &
263
         print_flux_line => gnostics%print_flux_line, print_line => gnostics%print_line, &
264
         save_distfn => gnostics%save_distfn, &
265
         save_for_restart => gnostics%save_for_restart, &
266
         save_glo_info_and_grids => gnostics%save_glo_info_and_grids, &
267
         save_many => gnostics%save_many, save_velocities => gnostics%save_velocities, &
268
         serial_netcdf4 => gnostics%serial_netcdf4, &
269
         use_nonlin_convergence => gnostics%use_nonlin_convergence, &
270
         write_any => gnostics%write_any, &
271
         write_apar_over_time => gnostics%write_apar_over_time, &
272
         write_ascii => gnostics%write_ascii, &
273
         write_avg_moments => gnostics%write_avg_moments, &
274
         write_bpar_over_time => gnostics%write_bpar_over_time, &
275
         write_cerr => gnostics%write_cerr, &
276
         write_collisional => gnostics%write_collisional, &
277
         write_correlation => gnostics%write_correlation, &
278
         write_correlation_extend => gnostics%write_correlation_extend, &
279
         write_cross_phase => gnostics%write_cross_phase, &
280
         write_density_over_time => gnostics%write_density_over_time, &
281
         write_eigenfunc => gnostics%write_eigenfunc, &
282
         write_fields => gnostics%write_fields, &
283
         write_final_antot => gnostics%write_final_antot, &
284
         write_final_db => gnostics%write_final_db, &
285
         write_final_epar => gnostics%write_final_epar, &
286
         write_final_fields => gnostics%write_final_fields, &
287
         write_final_moments => gnostics%write_final_moments, &
288
         write_flux_line => gnostics%write_flux_line, &
289
         write_fluxes => gnostics%write_fluxes, &
290
         write_fluxes_by_mode => gnostics%write_fluxes_by_mode, &
291
         write_full_moments_notgc => gnostics%write_full_moments_notgc, &
292
         write_g => gnostics%write_g, write_gs => gnostics%write_gs, &
293
         write_gyx => gnostics%write_gyx, write_heating => gnostics%write_heating, &
294
         write_jext => gnostics%write_jext, &
295
         write_kinetic_energy_transfer => gnostics%write_kinetic_energy_transfer, &
296
         write_kpar => gnostics%write_kpar, write_line => gnostics%write_line, &
297
         write_lorentzian => gnostics%write_lorentzian, &
298
         write_max_verr => gnostics%write_max_verr, &
299
         write_moments => gnostics%write_moments, &
300
         write_nl_flux_dist => gnostics%write_nl_flux_dist, &
301
         write_ntot_over_time => gnostics%write_ntot_over_time, &
302
         write_omavg => gnostics%write_omavg, write_omega => gnostics%write_omega, &
303
         write_ql_metric => gnostics%write_ql_metric, &
304
         write_parity => gnostics%write_parity, &
305
         write_phi_over_time => gnostics%write_phi_over_time, &
306
         write_symmetry => gnostics%write_symmetry, &
307
         write_tperp_over_time => gnostics%write_tperp_over_time, &
308
         write_upar_over_time => gnostics%write_upar_over_time, &
309
         write_verr => gnostics%write_verr, &
310
         write_zonal_transfer => gnostics%write_zonal_transfer)
311
#include "diagnostics_copy_out_auto_gen.inc"
312
    end associate
313

314
    !Override flags
315
    ! The collision_error method assumes we have setup the lz layout.
316
    if (use_le_layout) gnostics%write_cerr = .false.
×
317
    if (.not. nonlin) gnostics%use_nonlin_convergence = .false.
×
318

319
    if (.not.(gnostics%save_for_restart.or.gnostics%save_distfn)) then
×
320
       gnostics%nsave = -1
×
321
    endif
322

323
    if (override_screen_printout_options) then 
×
324
       gnostics%print_line = .true.
×
325
       gnostics%print_flux_line = .true.
×
326
    end if
327
  end subroutine read_parameters
×
328
end module diagnostics_config
×
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