write_velocity_space_checks Subroutine

public subroutine write_velocity_space_checks(gnostics)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
type(diagnostics_type), intent(in) :: gnostics

Contents


Source Code

  subroutine write_velocity_space_checks(gnostics)
    use dist_fn, only: get_verr, get_gtran
    use mp, only: proc0
    use le_grids, only: grid_has_trapped_particles
    use fields_arrays, only: phinew, bparnew
    use gs2_time, only: user_time
    use collisions, only: vnmult
    use species, only: spec
    use diagnostics_config, only: diagnostics_type
    use neasyf, only: neasyf_write
    use gs2_io, only: starts, time_dim, dim_2, dim_3, dim_5
    implicit none
    type(diagnostics_type), intent(in) :: gnostics
    real, dimension (:,:), allocatable :: errest
    integer, dimension (:,:), allocatable :: erridx
    real :: geavg, glavg, gtavg

    allocate(errest(5,2), erridx(5,3))
    errest = 0.0; erridx = 0
    geavg = 0.0 ; glavg = 0.0 ; gtavg = 0.0

    ! error estimate obtained by comparing standard integral with less-accurate integral
    call get_verr (errest, erridx, phinew, bparnew)

    ! error estimate based on monitoring amplitudes of legendre polynomial coefficients
    call get_gtran (geavg, glavg, gtavg, phinew, bparnew)

    if (.not. gnostics%vary_vnew_only .and. gnostics%writing) then
      call neasyf_write(gnostics%file_id, "vspace_lpcfrac", [geavg, glavg, gtavg], &
           dim_names=[dim_3, time_dim], start=starts(2, gnostics%nout), &
           long_name="Fraction of free energy contained in the high order coefficients of &
           & the Legendre polynomial transform of (1) energy space, (2) untrapped &
           & pitch angles and (3) trapped pitch angles (each should ideally be < 0.1).  &
           & Note that there are no trapped pitch angles for certain geometries")
      call neasyf_write(gnostics%file_id, "vspace_err", errest, &
           dim_names=[dim_5, dim_2, time_dim], start=starts(3, gnostics%nout), &
           long_name="Estimate of the (1) absolute and (2) relative errors resulting from &
           & velocity space integrals in the calculation of the following quantities &
           & in the given dimensions: (1) k phi, energy (2) k phi, untrapped pitch angles &
           & (3) k phi, trapped pitch angles, (4) k apar, energy, (5) k apar, untrapped &
           & angles. Relative errors should be < 0.1. ")
      call neasyf_write(gnostics%file_id, "vspace_vnewk", &
           [vnmult(1)*spec(1)%vnewk, vnmult(2)*spec(1)%vnewk], &
           dim_names=[dim_2, time_dim], start=starts(2, gnostics%nout), &
           long_name="If the simulation is set to vary the collisionality in order to keep &
           & error in velocity integrals to acceptable levels, contains species 1 &
           & collisionality in (1) pitch angle and (2) energy  ")

      if (gnostics%write_max_verr) then
        call neasyf_write(gnostics%file_id, "vspace_err_maxindex", erridx, &
             dim_names=[dim_5, dim_3, time_dim], start=starts(3, gnostics%nout), &
             long_name="Gives the (1) theta index, (2) ky index and (3) kx index of the maximum &
             & error resulting from the &
             & velocity space integrals in the calculation of the following quantities &
             & in the given dimensions: (1) k phi, energy (2) k phi, untrapped pitch angles &
             & (3) k phi, trapped pitch angles, (4) k apar, energy, (5) k apar, untrapped &
             & angles. Relative errors should be < 0.1. ")
      end if
   end if
   
   if (proc0 .and. gnostics%ascii_files%write_to_vres .and. (.not. gnostics%create)) call write_ascii
   deallocate(errest,erridx)
   
 contains
   !> FIXME : Add documentation   
   subroutine write_ascii
     if (grid_has_trapped_particles()) then
        write(gnostics%ascii_files%lpc,"(4(1x,e13.6))") user_time, geavg, glavg, gtavg
     else
        write(gnostics%ascii_files%lpc,"(3(1x,e13.6))") user_time, geavg, glavg
     end if
     write(gnostics%ascii_files%vres,"(8(1x,e13.6))") user_time, errest(1,2), errest(2,2), errest(3,2), &
          errest(4,2), errest(5,2), vnmult(1)*spec(1)%vnewk, vnmult(2)*spec(1)%vnewk
     if (gnostics%write_max_verr) then
        write(gnostics%ascii_files%vres2,"(3(i8),(1x,e13.6),3(i8),(1x,e13.6),3(i8),(1x,e13.6),3(i8),(1x,e13.6),3(i8),(1x,e13.6))") &
             erridx(1,1), erridx(1,2), erridx(1,3), errest(1,1), &
             erridx(2,1), erridx(2,2), erridx(2,3), errest(2,1), &
             erridx(3,1), erridx(3,2), erridx(3,3), errest(3,1), &
             erridx(4,1), erridx(4,2), erridx(4,3), errest(4,1), &
             erridx(5,1), erridx(5,2), erridx(5,3), errest(5,1)
     end if
   end subroutine write_ascii
 end subroutine write_velocity_space_checks