FIXME : Add documentation DD>NOTE: Regrid assumes nnew<nold but doesn't check it. Do we need to?
DD>NOTE: We only resize the arrays internal to theta_grid. This is what should be used
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | nperiod | |||
integer, | intent(inout) | :: | ntheta | |||
integer, | intent(inout) | :: | ntgrid | |||
integer, | intent(inout) | :: | nbset | |||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | theta | ||
real, | intent(inout), | dimension (nbset) | :: | bset | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | bmag | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gradpar | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gbdrift | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gbdrift0 | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | cvdrift | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | cvdrift0 | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | cdrift | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | cdrift0 | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gds2 | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gds21 | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gds22 | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gds23 | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gds24 | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | gds24_noq | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | grho | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | Rplot | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | Zplot | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | Rprime | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | Zprime | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | aplot | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | aprime | ||
real, | intent(inout), | dimension (-ntgrid:ntgrid) | :: | Bpol |
subroutine 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)
use gridgen4mod, only: gridgen4_2
use constants, only: pi
use mp, only: mp_abort
implicit none
integer, intent (in) :: nperiod
integer, intent (in out) :: ntheta, ntgrid, nbset
real, dimension (-ntgrid:ntgrid), intent (in out) :: theta
real, dimension (nbset), intent (in out) :: bset
real, dimension (-ntgrid:ntgrid), intent (in out) :: &
bmag, gradpar, gbdrift, gbdrift0, cvdrift, cvdrift0, cdrift, cdrift0, &
gds2, gds21, gds22, gds23, gds24, gds24_noq, grho, &
Rplot, Zplot, Rprime, Zprime, aplot, aprime, Bpol
integer :: ntheta_old, ntgrid_old, nbset_old
real, dimension (-ntgrid:ntgrid) :: thetasave
real, dimension (ntheta+1) :: thetaold, thetanew
real, dimension (ntheta+1) :: bmagold, bmagnew
integer :: i
logical, parameter :: debug=.false.
if (debug) write(6,*) 'gridgen_get_grids'
! If we're skipping gridgen then we'd better
! make sure that we set the outputs. As we're not
! changing the theta grid the only thing we need to
! set is `bset`, which is just the unique bmag values
! on our grid. Note here we're assuming bmag is symmetric,
! ordered etc. By skipping gridgen we don't guarantee that
! this will be the case.
if (skip_gridgen) then
bset = bmag(-ntheta/2:0)
return
end if
ntheta_old = ntheta
ntgrid_old = ntgrid
nbset_old = nbset
thetasave = theta
thetaold = theta(-ntheta/2:ntheta/2)
bmagold = bmag(-ntheta/2:ntheta/2)
if (debug) write(6,*) 'gridgen_get_grids: call gridgen4_2'
call gridgen4_2 (1,ntheta_old+1,thetaold,bmagold, npadd, &
alknob,epsknob,bpknob,extrknob,thetamax,deltaw,widthw,tension, &
ntheta,nbset,thetanew,bmagnew,bset)
if (ntheta_old /= ntheta) then
write(*,*) 'Error in theta_grid_gridgen?'
write(*,*) 'ntheta_old = ',ntheta_old
write(*,*) 'ntheta_new = ',ntheta
write(*,*) 'Stopping this run would be wise so will now abort.'
write(*,*) 'Try again with ntheta = ',ntheta_old + 2
if(ntheta_old<ntheta)then
write(*,*) 'ntheta_old<ntheta but code assumes ntheta<ntheta_old.'
endif
call mp_abort("Bad behaviour spotted in theta_grid_gridgen. Consider changing ntheta or set skip_gridgen = .true.", to_screen = .true.)
end if
! interpolate to new grid
ntgrid = ntheta/2 + (nperiod-1)*ntheta
theta(-ntheta/2:ntheta/2-1) = thetanew(1:ntheta)
theta(ntheta/2) = thetanew(1) + real(2)*pi
bmag(-ntheta/2:ntheta/2-1) = bmagnew(1:ntheta)
bmag(ntheta/2) = bmagnew(1)
do i = 1, nperiod-1
theta(-ntheta/2+i*ntheta:ntheta/2-1+i*ntheta) &
= thetanew(1:ntheta) + real(2*i)*pi
theta(ntheta/2+i*ntheta) = thetanew(1) + real(2*(i+1))*pi
theta(-ntheta/2-i*ntheta:ntheta/2-1-i*ntheta) &
= thetanew(1:ntheta) - real(2*i)*pi
bmag(-ntheta/2+i*ntheta:ntheta/2-1+i*ntheta) = bmagnew(1:ntheta)
bmag( ntheta/2+i*ntheta) = bmagnew(1)
bmag(-ntheta/2-i*ntheta:ntheta/2-1-i*ntheta) = bmagnew(1:ntheta)
end do
if (debug) write(6,*) 'gridgen_get_grids: call regrid'
!<DD>NOTE: Regrid assumes nnew<nold but doesn't check it. Do we need to?
! This only packs the new (splined) data into the old array, it
! doesn't actually resize the array. This resizing currently takes
! place during finish_init call (look for eik_save). Would be safer
! if we could make regrid actually reallocate/resize the array.
!<DD>NOTE: We only resize the arrays internal to theta_grid. This is what should be used
! by the rest of the code, but anywhere where the geometry arrays are used directly
! could lead to an error if these arrays are resized as we don't resize the geometry arrays.
call regrid (ntgrid_old, thetasave, gradpar, ntgrid, theta)
call regrid (ntgrid_old, thetasave, gbdrift, ntgrid, theta)
call regrid (ntgrid_old, thetasave, gbdrift0, ntgrid, theta)
call regrid (ntgrid_old, thetasave, cvdrift, ntgrid, theta)
call regrid (ntgrid_old, thetasave, cvdrift0, ntgrid, theta)
call regrid (ntgrid_old, thetasave, cdrift, ntgrid, theta)
call regrid (ntgrid_old, thetasave, cdrift0, ntgrid, theta)
call regrid (ntgrid_old, thetasave, gds2, ntgrid, theta)
call regrid (ntgrid_old, thetasave, gds21, ntgrid, theta)
call regrid (ntgrid_old, thetasave, gds22, ntgrid, theta)
call regrid (ntgrid_old, thetasave, gds23, ntgrid, theta)
call regrid (ntgrid_old, thetasave, gds24, ntgrid, theta)
call regrid (ntgrid_old, thetasave, gds24_noq, ntgrid, theta)
call regrid (ntgrid_old, thetasave, grho, ntgrid, theta)
call regrid (ntgrid_old, thetasave, Rplot, ntgrid, theta)
call regrid (ntgrid_old, thetasave, Zplot, ntgrid, theta)
call regrid (ntgrid_old, thetasave, aplot, ntgrid, theta)
call regrid (ntgrid_old, thetasave, Rprime, ntgrid, theta)
call regrid (ntgrid_old, thetasave, Zprime, ntgrid, theta)
call regrid (ntgrid_old, thetasave, aprime, ntgrid, theta)
call regrid (ntgrid_old, thetasave, Bpol, ntgrid, theta)
if (debug) write(6,*) 'gridgen_get_grids: end'
end subroutine gridgen_get_grids