diagnostics_config.f90 Source File


Contents


Source Code

!> A module for handling the configuration of the diagnostics
!! module via the namelist diagnostics_config.
module diagnostics_config
  use diagnostics_ascii, only: diagnostics_ascii_type
  use diagnostics_configuration, only: diagnostics_config_type
  implicit none

  private

  public :: init_diagnostics_config, finish_diagnostics_config
  public :: diagnostics_type, results_summary_type, read_parameters
  public :: override_screen_printout_options

  real, parameter :: initial_value = -1.0
  
  !> A type for storing the current results of the simulation
  type results_summary_type
     real :: phi2 = initial_value
     real :: apar2 = initial_value
     real :: bpar2 = initial_value
     real :: total_heat_flux = initial_value
     real :: total_momentum_flux = initial_value
     real :: total_particle_flux = initial_value
     real :: max_growth_rate = initial_value
     real :: diffusivity = initial_value

     ! Individual heat fluxes
     real, dimension(:), allocatable :: species_es_heat_flux
     real, dimension(:), allocatable :: species_apar_heat_flux
     real, dimension(:), allocatable :: species_bpar_heat_flux

     ! Total fluxes
     real, dimension(:), allocatable :: species_heat_flux
     real, dimension(:), allocatable :: species_momentum_flux
     real, dimension(:), allocatable :: species_particle_flux
     real, dimension(:), allocatable :: species_energy_exchange

     ! Average total fluxes
     real, dimension(:), allocatable :: species_heat_flux_avg
     real, dimension(:), allocatable :: species_momentum_flux_avg
     real, dimension(:), allocatable :: species_particle_flux_avg

     ! Heating
     real, dimension(:), allocatable :: species_heating
     real, dimension(:), allocatable :: species_heating_avg

     ! Growth rates
     complex, dimension(:,:), allocatable :: omega_average

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

  end type results_summary_type

  !> A type for storing the diagnostics configuration,
  !! a reference to the output file, and current 
  !! results of the simulation
  type diagnostics_type
     type(diagnostics_ascii_type) :: ascii_files
     type(results_summary_type) :: current_results
     !> NetCDF file ID
     integer :: file_id
     !> Current timestep
     integer :: nout = 1
     integer :: istep
     integer :: verbosity = 3
     logical :: create
     logical :: writing
     logical :: distributed
     logical :: parallel
     logical :: exit
     logical :: vary_vnew_only
     logical :: calculate_fluxes
     logical :: appending
     real :: user_time
     real :: user_time_old
     real :: start_time
     real, dimension(:), allocatable :: fluxfac
     integer :: nwrite
     integer :: nwrite_mult
     logical :: write_any
     logical :: append_old
     logical :: enable_parallel
     logical :: serial_netcdf4
     integer :: igomega
     logical :: print_line
     logical :: print_flux_line
     logical :: write_line
     logical :: write_flux_line
     logical :: write_fields
     logical :: write_phi_over_time
     logical :: write_apar_over_time
     logical :: write_bpar_over_time
     logical :: make_movie
     logical :: dump_fields_periodically
     logical :: write_moments
     logical :: write_full_moments_notgc
     logical :: write_ntot_over_time
     logical :: write_density_over_time
     logical :: write_upar_over_time
     logical :: write_tperp_over_time
     logical :: write_fluxes
     logical :: write_fluxes_by_mode
     logical :: write_symmetry
     logical :: write_nl_flux_dist
     logical :: write_parity
     logical :: write_omega
     logical :: write_ql_metric
     integer :: navg
     real :: omegatinst
     real :: omegatol
     logical :: exit_when_converged
     logical :: write_verr
     logical :: write_cerr
     logical :: write_max_verr
     integer :: ncheck
     logical :: write_heating
     logical :: write_ascii
     logical :: write_gyx
     logical :: write_g
     integer :: conv_nstep_av
     real :: conv_test_multiplier
     integer :: conv_min_step
     integer :: conv_max_step
     integer :: conv_nsteps_converged
     logical :: use_nonlin_convergence
     logical :: write_cross_phase
     logical :: write_correlation
     logical :: write_correlation_extend
     logical :: write_jext
     logical :: write_lorentzian
     logical :: write_eigenfunc
     logical :: write_final_fields
     logical :: write_kpar
     logical :: write_final_epar
     logical :: write_final_db
     logical :: write_final_moments
     logical :: write_final_antot
     logical :: write_gs
     integer :: nsave
     logical :: save_for_restart
     logical :: save_many
     logical :: file_safety_check
     logical :: save_distfn
     logical :: save_glo_info_and_grids
     logical :: save_velocities
     logical :: write_zonal_transfer
     logical :: write_kinetic_energy_transfer
     logical :: write_collisional
     logical :: write_omavg
     logical :: ob_midplane
     logical :: write_avg_moments
     logical :: dump_check1
     logical :: dump_check2
     integer :: nmovie
     integer :: nc_sync_freq
  end type diagnostics_type

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

  logical :: initialized = .false.
  
contains
  subroutine init_diagnostics_config(gnostics, new_gs2_diagnostics_config_in)
    use unit_tests, only: debug_message
    implicit none
    type(diagnostics_type), intent(inout) :: gnostics
    type(diagnostics_config_type), intent(in), optional :: new_gs2_diagnostics_config_in
    if(initialized) return
    initialized = .true.
    call debug_message(3, 'diagnostics_config::init_diagnostics_config &
      & starting')
    call read_parameters(gnostics, new_gs2_diagnostics_config_in)
    call debug_message(3, 'diagnostics_config::init_diagnostics_config &
      & read_parameters')
    call allocate_current_results(gnostics)
  end subroutine init_diagnostics_config

  subroutine finish_diagnostics_config(gnostics)
    use diagnostics_configuration, only: diagnostics_config
    implicit none
    type(diagnostics_type), intent(inout) :: gnostics
    initialized = .false.
    call deallocate_current_results(gnostics)
    call diagnostics_config%reset()
  end subroutine finish_diagnostics_config

  subroutine allocate_current_results(gnostics)
    use species, only: nspec
    use kt_grids, only: naky, ntheta0
    implicit none
    type(diagnostics_type), intent(inout) :: gnostics

    allocate(gnostics%current_results%species_es_heat_flux(nspec))
    allocate(gnostics%current_results%species_apar_heat_flux(nspec))
    allocate(gnostics%current_results%species_bpar_heat_flux(nspec))
    allocate(gnostics%current_results%species_heat_flux(nspec))
    allocate(gnostics%current_results%species_momentum_flux(nspec))
    allocate(gnostics%current_results%species_particle_flux(nspec))
    allocate(gnostics%current_results%species_energy_exchange(nspec))
    allocate(gnostics%current_results%species_heat_flux_avg(nspec))
    allocate(gnostics%current_results%species_momentum_flux_avg(nspec))
    allocate(gnostics%current_results%species_particle_flux_avg(nspec))
    allocate(gnostics%current_results%species_heating(nspec))
    allocate(gnostics%current_results%species_heating_avg(nspec))
    allocate(gnostics%current_results%omega_average(ntheta0, naky))
    allocate(gnostics%current_results%zonal_transfer(ntheta0,naky))

  end subroutine allocate_current_results

  subroutine deallocate_current_results(gnostics)
    implicit none
    type(diagnostics_type), intent(inout) :: gnostics
   
    deallocate(gnostics%current_results%species_es_heat_flux)
    deallocate(gnostics%current_results%species_apar_heat_flux)
    deallocate(gnostics%current_results%species_bpar_heat_flux)
    deallocate(gnostics%current_results%species_heat_flux)
    deallocate(gnostics%current_results%species_momentum_flux)
    deallocate(gnostics%current_results%species_particle_flux)
    deallocate(gnostics%current_results%species_heat_flux_avg)
    deallocate(gnostics%current_results%species_momentum_flux_avg)
    deallocate(gnostics%current_results%species_particle_flux_avg)
    deallocate(gnostics%current_results%species_heating)
    deallocate(gnostics%current_results%species_heating_avg)
    deallocate(gnostics%current_results%omega_average)
    deallocate(gnostics%current_results%zonal_transfer)
  end subroutine deallocate_current_results

  subroutine read_parameters(gnostics, new_gs2_diagnostics_config_in, warn_nonfunctional)
    use diagnostics_configuration, only: warn_about_nonfunctional_selection, diagnostics_config
    use collisions, only: use_le_layout
    use optionals, only: get_option_with_default
    implicit none
    type(diagnostics_type), intent(out) :: gnostics
    type(diagnostics_config_type), intent(in), optional :: new_gs2_diagnostics_config_in
    logical, intent(in), optional ::warn_nonfunctional

    if (present(new_gs2_diagnostics_config_in)) diagnostics_config = new_gs2_diagnostics_config_in

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

    ! Print some health warnings if switches are not their default
    ! values and are not available in this diagnostics module
    if (get_option_with_default(warn_nonfunctional, .true.)) then
       call warn_about_nonfunctional_selection(diagnostics_config%dump_check1, "dump_check1")
       call warn_about_nonfunctional_selection(diagnostics_config%dump_check2, "dump_check2")
       call warn_about_nonfunctional_selection(diagnostics_config%ob_midplane, "ob_midplane")
       call warn_about_nonfunctional_selection(.not. diagnostics_config%write_omavg, "write_omavg")
    end if

    ! Copy out internal values into module level parameters
    associate(self => diagnostics_config, &
         append_old => gnostics%append_old, conv_max_step => gnostics%conv_max_step, &
         conv_min_step => gnostics%conv_min_step, conv_nstep_av => gnostics%conv_nstep_av, &
         conv_nsteps_converged => gnostics%conv_nsteps_converged, &
         conv_test_multiplier => gnostics%conv_test_multiplier, &
         dump_check1 => gnostics%dump_check1, dump_check2 => gnostics%dump_check2, &
         dump_fields_periodically => gnostics%dump_fields_periodically, &
         enable_parallel => gnostics%enable_parallel, &
         exit_when_converged => gnostics%exit_when_converged, &
         file_safety_check => gnostics%file_safety_check, &
         igomega => gnostics%igomega, make_movie => gnostics%make_movie, &
         navg => gnostics%navg, ncheck => gnostics%ncheck, &
         nc_sync_freq => gnostics%nc_sync_freq, nmovie => gnostics%nmovie, &
         nsave => gnostics%nsave, nwrite => gnostics%nwrite, &
         nwrite_mult => gnostics%nwrite_mult, ob_midplane => gnostics%ob_midplane, &
         omegatinst => gnostics%omegatinst, omegatol => gnostics%omegatol, &
         print_flux_line => gnostics%print_flux_line, print_line => gnostics%print_line, &
         save_distfn => gnostics%save_distfn, &
         save_for_restart => gnostics%save_for_restart, &
         save_glo_info_and_grids => gnostics%save_glo_info_and_grids, &
         save_many => gnostics%save_many, save_velocities => gnostics%save_velocities, &
         serial_netcdf4 => gnostics%serial_netcdf4, &
         use_nonlin_convergence => gnostics%use_nonlin_convergence, &
         write_any => gnostics%write_any, &
         write_apar_over_time => gnostics%write_apar_over_time, &
         write_ascii => gnostics%write_ascii, &
         write_avg_moments => gnostics%write_avg_moments, &
         write_bpar_over_time => gnostics%write_bpar_over_time, &
         write_cerr => gnostics%write_cerr, &
         write_collisional => gnostics%write_collisional, &
         write_correlation => gnostics%write_correlation, &
         write_correlation_extend => gnostics%write_correlation_extend, &
         write_cross_phase => gnostics%write_cross_phase, &
         write_density_over_time => gnostics%write_density_over_time, &
         write_eigenfunc => gnostics%write_eigenfunc, &
         write_fields => gnostics%write_fields, &
         write_final_antot => gnostics%write_final_antot, &
         write_final_db => gnostics%write_final_db, &
         write_final_epar => gnostics%write_final_epar, &
         write_final_fields => gnostics%write_final_fields, &
         write_final_moments => gnostics%write_final_moments, &
         write_flux_line => gnostics%write_flux_line, &
         write_fluxes => gnostics%write_fluxes, &
         write_fluxes_by_mode => gnostics%write_fluxes_by_mode, &
         write_full_moments_notgc => gnostics%write_full_moments_notgc, &
         write_g => gnostics%write_g, write_gs => gnostics%write_gs, &
         write_gyx => gnostics%write_gyx, write_heating => gnostics%write_heating, &
         write_jext => gnostics%write_jext, &
         write_kinetic_energy_transfer => gnostics%write_kinetic_energy_transfer, &
         write_kpar => gnostics%write_kpar, write_line => gnostics%write_line, &
         write_lorentzian => gnostics%write_lorentzian, &
         write_max_verr => gnostics%write_max_verr, &
         write_moments => gnostics%write_moments, &
         write_nl_flux_dist => gnostics%write_nl_flux_dist, &
         write_ntot_over_time => gnostics%write_ntot_over_time, &
         write_omavg => gnostics%write_omavg, write_omega => gnostics%write_omega, &
         write_ql_metric => gnostics%write_ql_metric, &
         write_parity => gnostics%write_parity, &
         write_phi_over_time => gnostics%write_phi_over_time, &
         write_symmetry => gnostics%write_symmetry, &
         write_tperp_over_time => gnostics%write_tperp_over_time, &
         write_upar_over_time => gnostics%write_upar_over_time, &
         write_verr => gnostics%write_verr, &
         write_zonal_transfer => gnostics%write_zonal_transfer)
#include "diagnostics_copy_out_auto_gen.inc"
    end associate

    !Override flags
    ! The collision_error method assumes we have setup the lz layout.
    if (use_le_layout) gnostics%write_cerr = .false.

    if (.not.(gnostics%save_for_restart.or.gnostics%save_distfn)) then
       gnostics%nsave = -1
    endif

    if (override_screen_printout_options) then 
       gnostics%print_line = .true.
       gnostics%print_flux_line = .true.
    end if
  end subroutine read_parameters
end module diagnostics_config