2015-06-10 15:22:01 +02:00
|
|
|
module interp_eqprof
|
|
|
|
use const_and_precisions, only : wp_
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
! equidata
|
|
|
|
INTEGER, SAVE :: nlim,nr,nz,nbbbs,nsrt,nszt,nsft
|
|
|
|
REAL(wp_), SAVE :: psia,psiant,psinop,btrcen,rcen
|
|
|
|
REAL(wp_), SAVE :: btaxis,rmaxis,zmaxis,rmnm,rmxm,zmnm,zmxm,dr,dz
|
|
|
|
REAL(wp_), SAVE :: zbmin,zbmax,fpolas,phitedge,rrtor,rup,zup,rlw,zlw !rrtor non usato, solo in equidata
|
|
|
|
REAL(wp_), DIMENSION(:), ALLOCATABLE, SAVE :: tr,tz,tfp
|
|
|
|
REAL(wp_), DIMENSION(:), ALLOCATABLE, SAVE :: cceq,cfp
|
|
|
|
REAL(wp_), DIMENSION(:), ALLOCATABLE, SAVE :: cceq01,cceq10,cceq20,cceq02,cceq11
|
2015-06-19 12:22:49 +02:00
|
|
|
REAL(wp_), DIMENSION(:), ALLOCATABLE, SAVE :: psinr,rhopnr,qpsi,rv,zv
|
2015-06-10 15:22:01 +02:00
|
|
|
REAL(wp_), DIMENSION(:,:), ALLOCATABLE, SAVE :: psin,psi,btotal,crhot,cq
|
|
|
|
REAL(wp_), DIMENSION(:), ALLOCATABLE, SAVE :: rlim,zlim,rbbbs,zbbbs
|
|
|
|
|
|
|
|
! profdata
|
|
|
|
INTEGER, SAVE :: npp,nsfd
|
2015-07-10 17:29:44 +02:00
|
|
|
REAL(wp_), SAVE :: psnpp,denpp,ddenpp,d2denpp
|
2015-06-10 15:22:01 +02:00
|
|
|
REAL(wp_), DIMENSION(:), ALLOCATABLE, SAVE :: psrad,derad,terad,zfc,tfn,cfn
|
|
|
|
REAL(wp_), DIMENSION(:,:), ALLOCATABLE, SAVE :: ct,cz
|
|
|
|
|
|
|
|
contains
|
|
|
|
|
|
|
|
subroutine alloc_equilvec(ier)
|
|
|
|
implicit none
|
|
|
|
integer, intent(out) :: ier
|
|
|
|
integer :: nrest,nzest,lw10,lw01,lw20,lw02,lw11
|
|
|
|
|
|
|
|
if(nr.le.0.or.nz.le.0) then
|
|
|
|
ier = -1
|
|
|
|
return
|
|
|
|
end if
|
|
|
|
|
|
|
|
nrest=nr+4
|
|
|
|
nzest=nz+4
|
|
|
|
lw10=nr*3+nz*4+nr*nz
|
|
|
|
lw01=nr*4+nz*3+nr*nz
|
|
|
|
lw20=nr*2+nz*4+nr*nz
|
|
|
|
lw02=nr*4+nz*2+nr*nz
|
|
|
|
lw11=nr*3+nz*3+nr*nz
|
|
|
|
|
|
|
|
call dealloc_equilvec
|
|
|
|
allocate(rv(nr),zv(nz),tr(nrest),tz(nzest),tfp(nrest),cfp(nrest), &
|
|
|
|
btotal(nr,nz),cceq(nr*nz),cceq01(lw01),cceq10(lw10),cceq02(lw02), &
|
2015-06-19 12:22:49 +02:00
|
|
|
cceq20(lw20),cceq11(lw11),psi(nr,nz),psin(nr,nz),psinr(nr),rhopnr(nr), &
|
|
|
|
qpsi(nr), stat=ier)
|
2015-06-10 15:22:01 +02:00
|
|
|
if (ier/=0) call dealloc_equilvec
|
|
|
|
end subroutine alloc_equilvec
|
|
|
|
|
|
|
|
subroutine dealloc_equilvec
|
|
|
|
implicit none
|
|
|
|
if(allocated(rv)) deallocate(rv)
|
|
|
|
if(allocated(zv)) deallocate(zv)
|
|
|
|
if(allocated(tr)) deallocate(tr)
|
|
|
|
if(allocated(tz)) deallocate(tz)
|
|
|
|
if(allocated(tfp)) deallocate(tfp)
|
|
|
|
if(allocated(cfp)) deallocate(cfp)
|
|
|
|
if(allocated(btotal)) deallocate(btotal)
|
|
|
|
if(allocated(cceq)) deallocate(cceq)
|
|
|
|
if(allocated(cceq01)) deallocate(cceq01)
|
|
|
|
if(allocated(cceq10)) deallocate(cceq10)
|
|
|
|
if(allocated(cceq02)) deallocate(cceq02)
|
|
|
|
if(allocated(cceq20)) deallocate(cceq20)
|
|
|
|
if(allocated(cceq11)) deallocate(cceq11)
|
|
|
|
if(allocated(psi)) deallocate(psi)
|
|
|
|
if(allocated(psin)) deallocate(psin)
|
|
|
|
if(allocated(psinr)) deallocate(psinr)
|
2015-06-19 12:22:49 +02:00
|
|
|
if(allocated(rhopnr)) deallocate(rhopnr)
|
2015-06-10 15:22:01 +02:00
|
|
|
if(allocated(qpsi)) deallocate(qpsi)
|
|
|
|
|
|
|
|
end subroutine dealloc_equilvec
|
|
|
|
|
|
|
|
|
|
|
|
subroutine alloc_bnd(ier)
|
|
|
|
implicit none
|
|
|
|
integer, intent(out) :: ier
|
|
|
|
|
|
|
|
if(nlim.lt.0.or.nbbbs.lt.0) then
|
|
|
|
ier = -1
|
|
|
|
return
|
|
|
|
end if
|
|
|
|
|
|
|
|
call dealloc_bnd
|
|
|
|
allocate(rlim(nlim),zlim(nlim),rbbbs(nbbbs),zbbbs(nbbbs), &
|
|
|
|
stat=ier)
|
|
|
|
if (ier/=0) call dealloc_bnd
|
|
|
|
end subroutine alloc_bnd
|
|
|
|
|
|
|
|
subroutine dealloc_bnd
|
|
|
|
implicit none
|
|
|
|
if(allocated(rlim)) deallocate(rlim)
|
|
|
|
if(allocated(zlim)) deallocate(zlim)
|
|
|
|
if(allocated(rbbbs)) deallocate(rbbbs)
|
|
|
|
if(allocated(zbbbs)) deallocate(zbbbs)
|
|
|
|
end subroutine dealloc_bnd
|
|
|
|
|
|
|
|
|
|
|
|
subroutine alloc_lim(ier)
|
|
|
|
implicit none
|
|
|
|
integer, intent(out) :: ier
|
|
|
|
|
|
|
|
if(nlim.lt.0) then
|
|
|
|
ier = -1
|
|
|
|
return
|
|
|
|
end if
|
|
|
|
|
|
|
|
call dealloc_lim
|
|
|
|
allocate(rlim(nlim),zlim(nlim), &
|
|
|
|
stat=ier)
|
|
|
|
if (ier/=0) call dealloc_lim
|
|
|
|
end subroutine alloc_lim
|
|
|
|
|
|
|
|
subroutine dealloc_lim
|
|
|
|
implicit none
|
|
|
|
if(allocated(rlim)) deallocate(rlim)
|
|
|
|
if(allocated(zlim)) deallocate(zlim)
|
|
|
|
end subroutine dealloc_lim
|
|
|
|
|
|
|
|
|
|
|
|
subroutine alloc_profvec(ier)
|
|
|
|
implicit none
|
|
|
|
integer, intent(out) :: ier
|
|
|
|
integer :: npest
|
|
|
|
|
|
|
|
ier=0
|
|
|
|
if(npp.le.0) then
|
|
|
|
ier = -1
|
|
|
|
return
|
|
|
|
end if
|
|
|
|
|
|
|
|
npest=npp+4
|
|
|
|
|
|
|
|
call dealloc_profvec
|
|
|
|
allocate(psrad(npp),terad(npp),derad(npp),zfc(npp),ct(npp,4), &
|
|
|
|
cz(npp,4),tfn(npest),cfn(npest), &
|
|
|
|
stat=ier)
|
|
|
|
if (ier/=0) call dealloc_profvec
|
|
|
|
end subroutine alloc_profvec
|
|
|
|
|
|
|
|
subroutine dealloc_profvec
|
|
|
|
implicit none
|
|
|
|
if(allocated(psrad)) deallocate(psrad)
|
|
|
|
if(allocated(terad)) deallocate(terad)
|
|
|
|
if(allocated(derad)) deallocate(derad)
|
|
|
|
if(allocated(zfc)) deallocate(zfc)
|
|
|
|
if(allocated(ct)) deallocate(ct)
|
|
|
|
if(allocated(cz)) deallocate(cz)
|
|
|
|
if(allocated(tfn)) deallocate(tfn)
|
|
|
|
if(allocated(cfn)) deallocate(cfn)
|
|
|
|
|
|
|
|
end subroutine dealloc_profvec
|
|
|
|
|
|
|
|
end module interp_eqprof
|