read_parameters Subroutine

public subroutine read_parameters(is_list_run, gs2_diagnostics_config_in, warn_nonfunctional)

Read the input parameters for the diagnostics module

Arguments

Type IntentOptional Attributes Name
logical, intent(in) :: is_list_run

If true, this is a "list-mode run" and so turn off print_flux_line and print_line if set

type(diagnostics_config_type), intent(in), optional :: gs2_diagnostics_config_in

Configuration for this module, can be used to set new default values or avoid reading the input file

logical, intent(in), optional :: warn_nonfunctional

Contents

Source Code


Source Code

  subroutine read_parameters (is_list_run, gs2_diagnostics_config_in, warn_nonfunctional)
    use diagnostics_configuration, only: warn_about_nonfunctional_selection, diagnostics_config
    use run_parameters, only: has_phi
    use antenna, only: no_driver
    use collisions, only: heating, use_le_layout, set_heating
    use mp, only: proc0
    use optionals, only: get_option_with_default
    implicit none
    !> If true, this is a "list-mode run" and so turn off
    !> [[gs2_diagnostics_knobs:print_flux_line]] and
    !> [[gs2_diagnostics_knobs:print_line]] if set
    logical, intent (in) :: is_list_run
    !> Configuration for this module, can be used to set new default values or
    !> avoid reading the input file
    type(diagnostics_config_type), intent(in), optional :: gs2_diagnostics_config_in
    logical, intent(in), optional :: warn_nonfunctional
    logical :: write_zonal_transfer, write_upar_over_time, write_tperp_over_time
    logical :: write_ntot_over_time, write_density_over_time, write_collisional
    logical :: serial_netcdf4, enable_parallel
    integer :: ncheck

    if (present(gs2_diagnostics_config_in)) diagnostics_config = 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%enable_parallel, "enable_parallel")
       call warn_about_nonfunctional_selection(diagnostics_config%ncheck /= 10, "ncheck")
       call warn_about_nonfunctional_selection(diagnostics_config%serial_netcdf4, "serial_netcdf4")
       call warn_about_nonfunctional_selection(.not. diagnostics_config%write_any, "write_any")
       call warn_about_nonfunctional_selection(diagnostics_config%write_collisional, "write_collisional")
       call warn_about_nonfunctional_selection(diagnostics_config%write_density_over_time, "write_density_over_time")
       call warn_about_nonfunctional_selection(diagnostics_config%write_ntot_over_time, "write_ntot_over_time")
       call warn_about_nonfunctional_selection(diagnostics_config%write_tperp_over_time, "write_tperp_over_time")
       call warn_about_nonfunctional_selection(diagnostics_config%write_upar_over_time, "write_upar_over_time")
       call warn_about_nonfunctional_selection(diagnostics_config%write_zonal_transfer, "write_zonal_transfer")
    end if

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

    !CMR, 12/8/2014:
    ! Ensure write_full_moments_notgc=.false. if (write_moments .and. ob_midplane)
    ! to avoid a conflict.  
    ! FIXME: These two diagnostics do almost the same thing. Do we actually want both?
    if (write_moments .and. ob_midplane) write_full_moments_notgc=.false.

    !Override flags
    if (write_max_verr) write_verr = .true.

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

    print_summary = (is_list_run .and. (print_line .or. print_flux_line))

    if (is_list_run) then
       print_line = .false.
       print_flux_line = .false.
    end if

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

    !These don't store any data if we don't have phi so don't bother
    !calculating it.
    if(.not. has_phi) write_symmetry = .false.
    if(.not. has_phi) write_nl_flux_dist = .false.
    if(.not. has_phi) write_correlation = .false.
    if(.not. has_phi) write_correlation_extend = .false.

    if (.not. save_for_restart) nsave = -1
    write_avg_moments = write_avg_moments

    if (write_heating .and. .not. heating) then
       if (proc0) write(*,'("Warning: Disabling write_heating as collisions:heating is false.")')
       write_heating = .false.
    else if (heating .and. .not. write_heating) then
       call set_heating(.false.)
    end if

    write_any = write_line .or. write_omega     .or. write_omavg &
         .or. write_flux_line .or. write_fluxes .or. write_fluxes_by_mode  &
         .or. write_kpar   .or. write_heating     .or. write_lorentzian  .or. write_gs
    write_any_fluxes = write_flux_line .or. print_flux_line .or. write_fluxes .or. write_fluxes_by_mode
    dump_any = dump_check1  .or. dump_fields_periodically &
         .or.  dump_check2 .or. make_movie .or. print_summary &
         .or. write_full_moments_notgc
  end subroutine read_parameters