run_diagnostics Subroutine

public subroutine run_diagnostics(istep_in, exit, force)

Create or write all variables according to the value of istep: istep=-1 --> Create all netcdf variables istep=0 --> Write constant arrays/parameters (e.g. aky) and initial values istep>0 --> Write variables new diagnostic, calulate and write in new variable

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: istep_in
logical, intent(inout) :: exit
logical, intent(in), optional :: force

Contents

Source Code


Source Code

  subroutine run_diagnostics(istep_in, exit, force)
    use gs2_time, only: user_time, tunits
    use mp, only: proc0
    use diagnostics_zonal_transfer, only: write_zonal_transfer, calculate_zonal_transfer
    use collisional_heating, only: write_collisional, calculate_collisional   
    use diagnostics_printout, only: print_flux_line, print_line
    use diagnostics_printout, only: write_flux_line, write_line
    use diagnostics_fluxes, only: calculate_fluxes
    use diagnostics_fields, only: write_fields, write_movie
    use diagnostics_fields, only: write_eigenfunc
    use diagnostics_moments, only: write_moments, write_full_moments_notgc
    use diagnostics_omega, only: calculate_omega, write_omega
    use diagnostics_velocity_space, only: write_velocity_space_checks
    use diagnostics_velocity_space, only: write_collision_error
    use diagnostics_heating, only: calculate_heating, write_heating
    use diagnostics_nonlinear_convergence, only: check_nonlin_convergence
    use diagnostics_turbulence, only: write_cross_phase
    use diagnostics_antenna, only: write_jext, write_lorentzian
    use diagnostics_ascii, only: flush_output_files
    use collisions, only: vary_vnew
    use nonlinear_terms, only: nonlin
    use species, only: spec, has_electron_species
    use unit_tests, only: debug_message
    use mp,  only: broadcast
    use neasyf, only: neasyf_write
    use optionals, only: get_option_with_default
    use run_parameters, only: nstep, wstar_units
    use gs2_io, only: get_dim_length, nc_sync, ky_dim, time_dim
    use gs2_diagnostics, only: do_dump_fields_periodically, do_write_parity, do_write_nl_flux_dist, &
         do_write_correlation_extend, do_write_correlation, do_write_symmetry, do_write_pflux_sym

    implicit none
    integer, intent(in) :: istep_in
    logical, intent(inout) :: exit
    logical, intent(in), optional :: force
    integer, parameter :: verb=3
    integer :: istep
    integer, save :: istep_last = -1
    logical :: do_force
    if (.not. gnostics%write_any) return
    
    call broadcast(exit)

    call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics starting')
    do_force = get_option_with_default(force, .false.)
    
    gnostics%exit = exit
    
    ! If parallel, then everybody writes to netcdf,
    ! otherwise, only proc0
    if (gnostics%parallel .or. proc0) then
      gnostics%create = (istep_in==-1) .and. .not. gnostics%appending
      gnostics%writing = .true.
    else
      gnostics%create = .false.
      gnostics%writing = .false.
    end if

    ! Now that we've used istep to work out what operations we want
    ! to do, ensure the istep value is valid.
    istep = istep_in
    if(istep_in == -1) istep = 0
    gnostics%istep = istep
    
    ! Sets whether field-like arrays are assumed
    ! to be distributed across processes
    ! This line is a temporary placeholder
    ! till distributed fields are up and running
    gnostics%distributed = gnostics%parallel
    
    gnostics%calculate_fluxes = (gnostics%write_fluxes &
         .or.  gnostics%print_flux_line &
         .or.  gnostics%write_flux_line &
         .or.  gnostics%is_trinity_run)

    gnostics%user_time = user_time
    if (istep .eq. 0) gnostics%start_time = user_time
    
    if (istep > 0) then
       call calculate_omega(gnostics)
       if (gnostics%write_heating) call calculate_heating (gnostics)
    end if
    call broadcast(gnostics%exit)

    call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics calculated &
      & omega and heating')

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

       if (gnostics%writing) then
         call neasyf_write(gnostics%file_id, time_dim, user_time, dim_names=[time_dim], start=[gnostics%nout])
         if (wstar_units) then
            call neasyf_write(gnostics%file_id, "t_wstar", user_time * tunits, dim_names=[ky_dim, time_dim], &
                 start=[1, gnostics%nout], long_name="Time (wstar)", units="L/vt")
         end if
       end if

       gnostics%user_time = user_time
       gnostics%vary_vnew_only = .false.
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics starting write sequence')
       if (gnostics%write_omega)  call write_omega(gnostics)
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics written omega')
       if (gnostics%write_fields) call write_fields(gnostics)
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics written fields')
       if (gnostics%dump_fields_periodically) call do_dump_fields_periodically(gnostics%user_time)
       if (gnostics%write_ql_metric)  call write_ql_metric(gnostics)
       if (gnostics%calculate_fluxes) call calculate_fluxes(gnostics) ! NB  also writes fluxes if on
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics calculated fluxes')
       if (gnostics%write_symmetry) then
         call do_write_symmetry(gnostics%file_id, gnostics%nout)
         call do_write_pflux_sym(gnostics%file_id, gnostics%nout)
       end if
       if (gnostics%write_nl_flux_dist) call do_write_nl_flux_dist(gnostics%file_id, gnostics%nout)
       if (gnostics%write_parity) call do_write_parity(gnostics%user_time, gnostics%ascii_files%parity, gnostics%write_ascii)
       if (gnostics%write_verr) call write_velocity_space_checks(gnostics)
       if (gnostics%write_cerr) call write_collision_error(gnostics) ! NB only ascii atm
       call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics writing moments')
       if (gnostics%write_moments) call write_moments(gnostics)
       if (gnostics%write_full_moments_notgc) call write_full_moments_notgc(gnostics)
       if (gnostics%make_movie) call write_movie(gnostics)
       if (gnostics%write_heating) call write_heating(gnostics)
       if (nonlin.and.gnostics%use_nonlin_convergence) call check_nonlin_convergence(gnostics)
       if (gnostics%write_cross_phase.and.has_electron_species(spec)) call write_cross_phase(gnostics)
       if (gnostics%write_jext) call write_jext(gnostics)
       if (gnostics%write_correlation) call do_write_correlation(gnostics%file_id, gnostics%nout)
       if (gnostics%write_correlation_extend &
            .and. istep > nstep/4 &
            .and. mod(istep, gnostics%nwrite_mult * gnostics%nwrite)==0) &
            call do_write_correlation_extend(gnostics%file_id, gnostics%user_time, gnostics%user_time_old)
       if (gnostics%write_lorentzian) call write_lorentzian(gnostics)
       if (gnostics%write_eigenfunc) call write_eigenfunc(gnostics)
       
       if (gnostics%print_line) call print_line(gnostics)
       if (gnostics%write_line) call write_line(gnostics)
       if (proc0) then
          if (gnostics%print_flux_line) call print_flux_line(gnostics)
          if (gnostics%write_flux_line) call write_flux_line(gnostics)
       end if

       if (gnostics%write_zonal_transfer) then
          call calculate_zonal_transfer(gnostics)
          call write_zonal_transfer(gnostics)
       end if 

       if (gnostics%write_collisional) then  !< new diagnostic, calulate and write in new variable
          call calculate_collisional()
          call write_collisional(gnostics)
       end if

       call run_diagnostics_to_be_updated

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

       gnostics%nout = gnostics%nout + 1
    else if (mod(istep, gnostics%ncheck).eq.0) then
       ! These lines cause the automated checking of velocity space resolution
       ! and correction by varying collisionality
       gnostics%vary_vnew_only = .true.
       if (gnostics%write_verr .and. vary_vnew) call write_velocity_space_checks(gnostics)
    end if

    call debug_message(verb, 'gs2_diagnostics_new::run_diagnostics finished')
    exit = gnostics%exit
    call broadcast(exit)
  end subroutine run_diagnostics