VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
allocate_ns.f90
Go to the documentation of this file.
1
3
8SUBROUTINE allocate_ns (linterp, neqs_old)
9 USE vmec_main
10 USE vmec_params, ONLY: ntmax
11 USE realspace
12 USE vforces
13 USE xstuff
14 USE mgrid_mod
15
16 IMPLICIT NONE
17
18 LOGICAL, INTENT(in) :: linterp
19 INTEGER, INTENT(in) :: neqs_old
20
21 INTEGER :: ndim, nsp1, istat1
22 REAL(rprec), DIMENSION(:), ALLOCATABLE :: xc_old, scalxc_old
23
24 ndim = 1 + nrzt ! TODO: why +1? some magical hidden storage at the end of the array ?
25 nsp1 = 1 + ns ! TODO: why +1? some magical hidden storage at the end of the array ?
26
27 IF (neqs_old .gt. 0 .and. ALLOCATED(scalxc) .and. linterp) THEN
28 ! Save old xc, scalxc for possible interpolation or IF iterations restarted on same mesh...
29 ALLOCATE(xc_old(neqs_old), scalxc_old(neqs_old), stat=istat1)
30 IF (istat1.ne.0) stop 'allocation error #1 in allocate_ns'
31 xc_old(:neqs_old) = xc(:neqs_old)
32 scalxc_old(:neqs_old) = scalxc(:neqs_old)
33 END IF
34
35 ! ALLOCATES MEMORY FOR NS-DEPENDENT ARRAYS
36 ! FIRST BE SURE TO FREE MEMORY PREVIOUSLY ALLOCATED
37 CALL free_mem_ns
38
39 ALLOCATE (phip(ndim), chip(ndim), shalf(ndim), sqrts(ndim), wint(ndim), stat=istat1)
40 IF (istat1.ne.0) stop 'allocation error #2 in allocate_ns'
41 phip=0; chip=0; shalf=0; sqrts=0; wint=0
42
43 ALLOCATE( ireflect(ns*nzeta), stat=istat1)
44 IF (istat1.ne.0) stop 'allocation error #3 in allocate_ns'
45
46 ALLOCATE( ard(nsp1,2),arm(nsp1,2),brd(nsp1,2),brm(nsp1,2), &
47 azd(nsp1,2),azm(nsp1,2),bzd(nsp1,2),bzm(nsp1,2), &
48 sm(ns), sp(0:ns), bmin(ntheta2,ns), bmax(ntheta2,ns), stat=istat1)
49 IF (istat1.ne.0) stop 'allocation error #6 in allocate_ns'
50
51 ALLOCATE( iotaf(nsp1), crd(nsp1), mass(ns), phi(ns), presf(ns), &
52 jcuru(ns), jcurv(ns), jdotb(ns), buco(ns), bvco(ns), &
53 bucof(ns), bvcof(ns), chi(ns), &
54 bdotgradv(ns), equif(ns), specw(ns), tcon(ns), &
55 psi(ns),yellip(2,ns),yinden(2,ns), ytrian(2,ns),yshift(2,ns), &
56 ygeo(2,ns),overr(ns), faclam(ns,0:ntor,0:mpol1,ntmax), &
57 iotas(nsp1), phips(nsp1), chips(nsp1), pres(nsp1), &
58 beta_vol(ns), jperp2(ns), jpar2(ns), bdotb(ns), &
59 phipf(ns), chipf(ns), blam(nsp1), clam(nsp1), &
60 dlam(nsp1), icurv(ns+1), vpphi(ns), bdamp(ns), &
61 presgrad(ns), vp(nsp1), stat=istat1)
62 IF (istat1.ne.0) stop 'allocation error #7 in allocate_ns'
63
64 iotaf(nsp1) = 0 ! TODO: why explicitly zero out only the last entry? hidden storage?
65
66 ALLOCATE (gc(neqs), gc_con(neqs), gc_mhd(neqs), xcdot(neqs), xsave(neqs), xstore(neqs), stat=istat1)
67 IF (istat1.ne.0) stop 'allocation error #9 in allocate_ns'
68 xstore = zero
69
70 IF (.not.ALLOCATED(xc)) THEN
71 ALLOCATE (xc(neqs), scalxc(neqs), stat=istat1)
72 IF (istat1.ne.0) stop 'allocation error #10 in allocate_ns'
73 xc = zero
74 END IF
75
76 ! FIRST STORE COARSE-MESH XC FOR INTERPOLATION
77 IF (ALLOCATED(xc_old)) THEN
78 xstore(1:neqs_old) = xc_old(1:neqs_old)
79 scalxc(1:neqs_old) = scalxc_old(1:neqs_old)
80 DEALLOCATE (xc_old, scalxc_old)
81 END IF
82
83 ! Allocate nrzt-dependent arrays (persistent) for funct3d
85
86END SUBROUTINE allocate_ns
subroutine allocate_funct3d
allocate arrays required in funct3d()
subroutine allocate_ns(linterp, neqs_old)
allocate arrays depending on the number of flux surfaces ns
subroutine free_mem_ns
Free memory depending on the number of flux surfaces ns.
real(rprec), dimension(:), allocatable wint
two-dimensional array for normalizing angle integrations
Definition realspace.f90:34
real(rprec), dimension(:), allocatable sqrts
sqrt(s), two-dimensional array on full-grid
Definition realspace.f90:32
real(rprec), dimension(:), allocatable chip
radial derivative of chi/(2*pi) on half-grid
Definition realspace.f90:30
real(rprec), dimension(:), allocatable shalf
sqrt(s) ,two-dimensional array on half-grid
Definition realspace.f90:31
real(rprec), dimension(:), allocatable phip
radial derivative of phi/(2*pi) on half-grid
Definition realspace.f90:29
real(rprec), dimension(:), allocatable dlam
Definition vmec_main.f90:15
real(rprec), dimension(:), allocatable equif
radial force balance error: grad(p) - <j x B>
Definition vmec_main.f90:45
real(rprec), dimension(:,:), allocatable ygeo
Definition vmec_main.f90:53
real(rprec), dimension(:), allocatable vp
radial derivative of enclosed volume
Definition vmec_main.f90:56
real(rprec), dimension(:), allocatable bvco
enclosed poloidal current profile
Definition vmec_main.f90:43
real(rprec), dimension(:), allocatable buco
enclosed toroidal current profile
Definition vmec_main.f90:42
real(rprec), dimension(:), allocatable crd
Definition vmec_main.f90:24
real(rprec), dimension(:), allocatable sp
shalf(i+1)/sfull(i)
Definition vmec_main.f90:26
real(rprec), dimension(:,:), allocatable brd
Definition vmec_main.f90:18
real(rprec), dimension(:), allocatable jcuru
poloidal current density
Definition vmec_main.f90:39
real(rprec), dimension(:,:), allocatable azd
Definition vmec_main.f90:20
real(rprec), dimension(:,:), allocatable ytrian
Definition vmec_main.f90:51
real(rprec), dimension(:,:,:,:), allocatable faclam
Definition vmec_main.f90:28
real(rprec), dimension(:,:), allocatable bmax
Definition vmec_main.f90:32
real(rprec), dimension(:), allocatable chips
poloidal flux (same as chip), one-dimensional array
Definition vmec_main.f90:67
real(rprec), dimension(:), allocatable presf
pressure profile on full-grid, mass/phip**gamma
Definition vmec_main.f90:66
real(rprec), dimension(:), allocatable bdamp
radial mesh-blending factor
Definition vmec_main.f90:27
real(rprec), dimension(:), allocatable phi
toroidal magnetic flux
Definition vmec_main.f90:37
integer neqs
total number of equations to evolve (size of xc)
real(rprec), dimension(:), allocatable overr
Definition vmec_main.f90:54
real(rprec), dimension(:), allocatable sm
shalf(i)/sfull(i)
Definition vmec_main.f90:25
real(rprec), dimension(:,:), allocatable bmin
Definition vmec_main.f90:31
real(rprec), dimension(:,:), allocatable brm
Definition vmec_main.f90:19
real(rprec), dimension(:), allocatable jdotb
Definition vmec_main.f90:41
real(rprec), dimension(:,:), allocatable bzd
Definition vmec_main.f90:22
real(rprec), dimension(:,:), allocatable bzm
Definition vmec_main.f90:23
real(rprec), dimension(:,:), allocatable yinden
Definition vmec_main.f90:50
real(rprec), dimension(:), allocatable bdotgradv
Definition vmec_main.f90:44
real(rprec), dimension(:), allocatable clam
Definition vmec_main.f90:14
real(rprec), dimension(:), allocatable specw
spectral width (diagnostic)
Definition vmec_main.f90:46
real(rprec), dimension(:), allocatable iotaf
rotational transform (full grid)
Definition vmec_main.f90:34
real(rprec), dimension(:,:), allocatable yshift
Definition vmec_main.f90:52
real(rprec), dimension(:), allocatable psi
Definition vmec_main.f90:48
real(rprec), dimension(:,:), allocatable ard
Definition vmec_main.f90:16
real(rprec), dimension(:), allocatable pres
pressure profile
Definition vmec_main.f90:55
real(rprec), dimension(:), allocatable chipf
radial derivative of poloidal magnetic flux (full grid)
Definition vmec_main.f90:36
real(rprec), dimension(:), allocatable jpar2
Definition vmec_main.f90:57
real(rprec), dimension(:), allocatable presgrad
pressure gradient: dp/ds
Definition vmec_main.f90:61
integer, dimension(:), allocatable ireflect
two-dimensional array for computing 2pi-v angle
real(rprec), dimension(:,:), allocatable arm
Definition vmec_main.f90:17
real(rprec), dimension(:), allocatable bvcof
Definition vmec_main.f90:63
real(rprec), dimension(:), allocatable blam
Definition vmec_main.f90:13
real(rprec), dimension(:), allocatable chi
poloidal magnetic flux
Definition vmec_main.f90:64
real(rprec), dimension(:), allocatable phips
toroidal flux (same as phip), one-dimensional array
Definition vmec_main.f90:68
real(rprec), dimension(:), allocatable mass
mass profile on half-grid
Definition vmec_main.f90:71
real(rprec), dimension(:), allocatable bdotb
Definition vmec_main.f90:59
real(rprec), dimension(:), allocatable bucof
Definition vmec_main.f90:62
real(rprec), dimension(:), allocatable beta_vol
Definition vmec_main.f90:38
real(rprec), dimension(:), allocatable iotas
rotational transform , on half radial mesh
Definition vmec_main.f90:69
real(rprec), dimension(:,:), allocatable azm
Definition vmec_main.f90:21
real(rprec), dimension(:), allocatable jperp2
Definition vmec_main.f90:58
real(rprec), dimension(:), allocatable phipf
radial derivative of toroidal magnetic flux (full grid)
Definition vmec_main.f90:35
real(rprec), dimension(:), allocatable tcon
constraint-force multiplier
Definition vmec_main.f90:47
real(rprec), dimension(:,:), allocatable yellip
Definition vmec_main.f90:49
real(rprec), dimension(:), allocatable icurv
(-)toroidal current inside flux surface (vanishes like s)
Definition vmec_main.f90:70
real(rprec), dimension(:), allocatable vpphi
Definition vmec_main.f90:60
real(rprec), dimension(:), allocatable jcurv
toroidal current density
Definition vmec_main.f90:40
integer ntmax
number of contributing Fourier basis function (can be 1, 2 or 4); assigned in read_indata()
real(rprec), dimension(:), allocatable gc_mhd
Definition xstuff.f90:37
real(rprec), dimension(:), allocatable gc_con
Definition xstuff.f90:37
real(rprec), dimension(:), allocatable gc
stacked array of R, Z, Lambda Spectral force coefficients (see above for stack order)
Definition xstuff.f90:37
real(rprec), dimension(:), allocatable, target xc
stacked array of scaled R, Z, Lambda Fourier coefficients (see above for stack order)
Definition xstuff.f90:40
real(rprec), dimension(:), allocatable xsave
Definition xstuff.f90:45
real(rprec), dimension(:), allocatable scalxc
Definition xstuff.f90:50
real(rprec), dimension(:), allocatable xcdot
"velocity": change of Fourier coefficients per time step
Definition xstuff.f90:43
real(rprec), dimension(:), allocatable xstore
backup copy of last-known-good xc
Definition xstuff.f90:48