file_get_grids Subroutine

public subroutine file_get_grids(nperiod, ntheta, ntgrid, nbset, theta, bset, bmag, gradpar, gbdrift, gbdrift0, cvdrift, cvdrift0, cdrift, cdrift0, gds2, gds21, gds22, gds23, gds24, gds24_noq, grho, Rplot, Zplot, Rprime, Zprime, aplot, aprime, shat, drhodpsi, kxfac, qval, gb_to_cv, Bpol, surfarea, dvdrhon, rhoc)

FIXME : Add documentation

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: nperiod
integer, intent(inout) :: ntheta
integer, intent(inout) :: ntgrid
integer, intent(inout) :: nbset
real, intent(out), dimension (-ntgrid:ntgrid) :: theta
real, intent(out), dimension (nbset) :: bset
real, intent(out), dimension (-ntgrid:ntgrid) :: bmag
real, intent(out), dimension (-ntgrid:ntgrid) :: gradpar
real, intent(out), dimension (-ntgrid:ntgrid) :: gbdrift
real, intent(out), dimension (-ntgrid:ntgrid) :: gbdrift0
real, intent(out), dimension (-ntgrid:ntgrid) :: cvdrift
real, intent(out), dimension (-ntgrid:ntgrid) :: cvdrift0
real, intent(out), dimension (-ntgrid:ntgrid) :: cdrift
real, intent(out), dimension (-ntgrid:ntgrid) :: cdrift0
real, intent(out), dimension (-ntgrid:ntgrid) :: gds2
real, intent(out), dimension (-ntgrid:ntgrid) :: gds21
real, intent(out), dimension (-ntgrid:ntgrid) :: gds22
real, intent(out), dimension (-ntgrid:ntgrid) :: gds23
real, intent(out), dimension (-ntgrid:ntgrid) :: gds24
real, intent(out), dimension (-ntgrid:ntgrid) :: gds24_noq
real, intent(out), dimension (-ntgrid:ntgrid) :: grho
real, intent(out), dimension (-ntgrid:ntgrid) :: Rplot
real, intent(out), dimension (-ntgrid:ntgrid) :: Zplot
real, intent(out), dimension (-ntgrid:ntgrid) :: Rprime
real, intent(out), dimension (-ntgrid:ntgrid) :: Zprime
real, intent(out), dimension (-ntgrid:ntgrid) :: aplot
real, intent(out), dimension (-ntgrid:ntgrid) :: aprime
real, intent(out) :: shat
real, intent(out) :: drhodpsi
real, intent(out) :: kxfac
real, intent(out) :: qval
logical, intent(in) :: gb_to_cv
real, intent(out), dimension (-ntgrid:ntgrid) :: Bpol
real, intent(out) :: surfarea
real, intent(out) :: dvdrhon
real, intent(out) :: rhoc

Contents

Source Code


Source Code

  subroutine file_get_grids (nperiod, ntheta, ntgrid, nbset, theta, bset, &
       bmag, gradpar, gbdrift, gbdrift0, cvdrift, cvdrift0, cdrift, cdrift0, &
       gds2, gds21, gds22, gds23, gds24, gds24_noq, grho, &
       Rplot, Zplot, Rprime, Zprime, aplot, aprime, &
       shat, drhodpsi, kxfac, qval, gb_to_cv, Bpol, surfarea, dvdrhon, rhoc)
    use file_utils, only: get_unused_unit
    use constants, only: pi
    use integration, only: trapezoidal_integration
    use theta_grid_params, only: rhoc_par => rhoc
    implicit none
    integer, intent (in) :: nperiod
    integer, intent (in out) :: ntheta, ntgrid, nbset
    real, dimension (-ntgrid:ntgrid), intent (out) :: theta
    real, dimension (nbset), intent (out) :: bset
    real, dimension (-ntgrid:ntgrid), intent (out) :: &
         bmag, gradpar, gbdrift, gbdrift0, cvdrift, cvdrift0, cdrift, cdrift0, &
         gds2, gds21, gds22, gds23, gds24, gds24_noq, grho, &
         Rplot, Zplot, Rprime, Zprime, aplot, aprime, Bpol
    real, intent (out) :: shat, drhodpsi, kxfac, qval, surfarea, dvdrhon, rhoc
    logical, intent (in) :: gb_to_cv
    integer :: unit
    character(200) :: line
    integer :: i
    logical :: first=.true.
    !<DD> Should jacob also be provided by this routine?

    !<DD> NOTE: Not currently settin Bpol here. This is used in flux calculations.
    !If not set then results will be funny. Add a warning message and set to zero
    !for now.
    if(first)then
       write(*,'("WARNING: When using file_get_grids, Bpol does not have a correct definition --> Currently just setting to zero, may impact some diagnostics")')
       Bpol=0.
       first=.false.
    endif

    shat = shat_input
    drhodpsi = drhodpsi_input
    kxfac = kxfac_input
    qval = qval_input

    call get_unused_unit (unit)
    open (unit=unit, file=gridout_file, status="old")
    read (unit=unit, fmt="(a)") line
    read (unit=unit, fmt="(a)") line
    read (unit=unit, fmt="(a)") line
    do i = 1, nbset
       read (unit=unit, fmt=*) bset(i) ! actually alambda
    end do
    bset = 1.0/bset ! switch alambda to bset

    read (unit=unit, fmt="(a)") line
    read (unit=unit, fmt="(a)") line

    read (unit=unit, fmt="(a)") line
    do i = -ntgrid, ntgrid
       read (unit=unit, fmt=*) gbdrift(i), gradpar(i), grho(i)
    end do

    read (unit=unit, fmt="(a)") line
    do i = -ntgrid, ntgrid
       read (unit=unit, fmt=*) cvdrift(i), gds2(i), bmag(i), theta(i)
    end do

    read (unit=unit, fmt="(a)") line
    do i = -ntgrid, ntgrid
       read (unit=unit, fmt=*) gds21(i), gds22(i)
    end do

    ! TMP UNTIL WORK OUT HOW TO GET FROM FILE
    gds23 = 0. ; gds24 = 0. ; gds24_noq = 0.

    ! TMP UNTIL FIGURE OUT HOW TO WORK WITH FILE -- MAB
    ! set coriolis drift to zero
    cdrift = 0. ; cdrift0 = 0.

    read (unit=unit, fmt="(a)") line
    do i = -ntgrid, ntgrid
       read (unit=unit, fmt=*) cvdrift0(i), gbdrift0(i)
    end do

    if (gb_to_cv) then
       do i =-ntgrid,ntgrid
          gbdrift(i) = cvdrift(i)
          gbdrift0(i) = cvdrift0(i)
       end do
    end if

    ! Possibly crude approximations for file
    ! Note jacob is usually defined as jacob = 1.0/(drhodpsi*gradpar*bmag)
    ! but isn't yet stored here.
    surfarea = 2 * pi * trapezoidal_integration(theta, grho / (drhodpsi*gradpar*bmag))
    dvdrhon = 2 * pi * trapezoidal_integration(theta, 1.0 / (drhodpsi*gradpar*bmag))

    ! As the eqfile doesn't specify rhoc we simply set from the value
    ! from theta_grid_params here.
    rhoc = rhoc_par

    if (.not. no_geo_info) then

       read (unit=unit, fmt="(a)",err=100) line
       do i = -ntgrid, ntgrid
          read (unit=unit, fmt=*, err=100) Rplot(i), Rprime(i)
       end do

       read (unit=unit, fmt="(a)",err=100) line
       do i = -ntgrid, ntgrid
          read (unit=unit, fmt=*, err=100) Zplot(i), Zprime(i)
       end do

       read (unit=unit, fmt="(a)",err=100) line
       do i = -ntgrid, ntgrid
          read (unit=unit, fmt=*, err=100) aplot(i), aprime(i)
       end do

    end if

    close (unit=unit)

    return

100 continue
    write(6,*) 'Error reading Rplot etc. setting to dummy values.'
! dummy values for backward compatibility
    Rplot = 1. ; Rprime = 0.
    Zplot = 1. ; Zprime = 0.
    aplot = 1. ; aprime = 0.

    close (unit=unit)

  end subroutine file_get_grids