salpha_get_grids Subroutine

public subroutine salpha_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, shape, gb_to_cv, Bpol, surfarea, dvdrhon, rhoc)

FIXME : Add documentation DD> The following few lines will cause an issue in the (semi-)valid case where eps=0.0 so adding a guard

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
character(len=8), intent(out) :: shape
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 salpha_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, shape, gb_to_cv, Bpol, surfarea, dvdrhon, rhoc)
    use constants, only: twopi
    use theta_grid_params, only: eps, epsl, shat_param => shat, pk
    use theta_grid_gridgen, only: theta_grid_gridgen_init, gridgen_get_grids
    use file_utils, only: error_unit
    use integration, only: trapezoidal_integration
    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
    character (8), intent(out) :: shape
    logical, intent (in) :: gb_to_cv
    integer :: i

    theta = [(real(i) * twopi / ntheta, i = -ntgrid, ntgrid)]

! BD: dummy response for graphics in s-alpha mode until I have time to fix this:
    if (abs(epsl) > epsilon(0.)) then
       Rplot = 2./epsl*(1.+eps*cos(theta))  ; Rprime = 0.
    else
       Rplot = 1. ; Rprime = 0.
    end if
    Zplot = 1.  ; Zprime = 0.
    aplot = 1.  ; aprime = 0.

! MB : should look into changing this
    Bpol = 0.

    if (model_switch == model_alpha1) then
       bmag = 1.0-eps*cos(theta)-alpha1*cos(3.0*theta)
    else if (model_switch == model_b2) then
       bmag = 1.0 - eps*cos(theta)
    else
       bmag = 1.0/(1.0 + eps*cos(theta))
    end if

    shat = shat_param
    if (eps > epsilon(0.0)) then
       drhodpsi = 0.5*epsl**2/(pk*eps)
    else
       drhodpsi = 1.0
    end if
    kxfac = 1.0
    if (epsl > epsilon(0.0)) then
       qval = epsl/pk
    else
       qval = 1.
    end if
    select case (model_switch)
    case (model_salpha,model_alpha1,model_b2)
       cvdrift = epsl*(cos(theta) + (shat*theta-shift*sin(theta))*sin(theta))
       cvdrift0 = -epsl*shat*sin(theta)
       gds2 = 1.0 + (shat*theta-shift*sin(theta))**2
       gds21 = -shat*(shat*theta - shift*sin(theta))
       gds22 = shat*shat
       grho = 1.0
       if (model_switch == model_b2) then
          cvdrift = cvdrift/bmag**2
          cvdrift0 = cvdrift0/bmag**2
       end if
       if (epsl < epsilon(0.)) shape = 'slab    '
       gbdrift = cvdrift
       gbdrift0 = cvdrift0

    case (model_normal_only)
       cvdrift = epsl*cos(theta)
       cvdrift0 = 0.
       gds2 = 1.0 + (shat*theta-shift*sin(theta))**2
       gds21 = -shat*(shat*theta - shift*sin(theta))
       gds22 = shat*shat
       grho = 1.0
       if (epsl < epsilon(0.)) shape = 'slab    '
       gbdrift = cvdrift
       gbdrift0 = cvdrift0

    case (model_eps)
       cvdrift = epsl*(cos(theta) -eps + (shat*theta-shift*sin(theta))*sin(theta))
       cvdrift0 = -epsl*shat*sin(theta)
       gds2 = 1.0 + (shat*theta-shift*sin(theta))**2
       gds21 = -shat*(shat*theta - shift*sin(theta))
       gds22 = shat*shat
       grho = 1.0
       if (epsl < epsilon(0.)) shape = 'slab    '
       gbdrift = cvdrift
       gbdrift0 = cvdrift0

    case (model_ccurv,model_nocurve)
       cvdrift = epsl
       cvdrift0 = 0.0

! Some strangeness here to get straight at some point:
!    ccurv == constant curvature should be the case used for cylindrical
!             geometry, but evidently Paolo and Barrett do not like the
!             gds2 definition there, and have been using the slab
!             option (no_curvature) for their Z-pinch studies.
!
!    Simply need to look into the shift dependence of gds2
!
       if (model_switch == model_nocurve) then
!CMR, 4/6/2014:
! commented out gbdrift=0 as looked wrong, surely really want cvdrift=0
!dja fix for no curvature
!          gbdrift = 0.0
!dja end
!CMRend
          gds2 = 1.0 + (shat*theta)**2
          gds21 = -shat*shat*theta
          shape = 'slab    '
          gbdrift = cvdrift*(1.-shift)
          gbdrift0 = cvdrift0
          cvdrift=0 !CMR, 4/6/2014: surely this is what was intended?
       else
          gds2 = 1.0 + (shat*theta-shift*sin(theta))**2
! probably should be:
!          gds2 = 1.0 + (shat*theta)**2
          gds21 = -shat*shat*theta
          shape = 'cylinder'
          gbdrift = cvdrift*(1.-shift)
          gbdrift0 = cvdrift0
       endif

       gds22 = shat*shat
       grho = 1.0

    end select

    if (gb_to_cv) then
       gbdrift = cvdrift
       gbdrift0 = cvdrift0
    end if

    gradpar = pk/2.0

    ! not sure about factor of epsl below...
    cdrift = 2.*epsl*(cos(theta)+shat*theta*sin(theta))
    cdrift0 = -2.*epsl*shat*sin(theta)
    ! BD: What are gds23 and gds24?  Who put this here?
    ! MB: gds23 and gds24 are geometrical factors appearing at next order in gk eqn
    ! MB: NEED TO INCLUDE SHIFT IN BELOW EXPRESSIONS
    !<DD> The following few lines will cause an issue in the (semi-)valid case where eps=0.0 so adding a guard
    !     here. These terms are used in lowflow calculations
    if(eps>epsilon(0.0))then
       gds23 = -0.5*epsl*shat*theta*(1.+2.*eps*cos(theta))/eps
       gds24_noq = 0.5*epsl*(1.+eps*cos(theta))/eps
    else
       write(error_unit(),'("Warning : Some lowflow related geometrical terms are forced to zero in cases with eps=0.")')
       gds23 = 0.
       gds24_noq = 0.
    endif
    gds24 = shat*gds24_noq

    if (model_switch /= model_alpha1) then
       bset = bmag(-ntheta/2:0)
    else
       call theta_grid_gridgen_init
       call gridgen_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, Bpol)
    end if

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

    ! make rhoc consistent with eps, epsl
    if (epsl > epsilon(0.0)) then
       rhoc = 2.*eps/epsl
    else
       rhoc = 1.
    end if
  end subroutine salpha_get_grids