VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
initialize_radial.f90
Go to the documentation of this file.
1
3
9SUBROUTINE initialize_radial(nsval, ns_old, delt0)
10 USE vmec_main
11 USE vmec_params, ONLY: ntmax
12 USE realspace
13 USE xstuff
14 IMPLICIT NONE
15
16 INTEGER, INTENT(in) :: nsval
17 INTEGER, INTENT(inout) :: ns_old
18 REAL(rprec), INTENT(out) :: delt0
19
20 INTEGER :: neqs_old = 0 ! note that this sets neqs_old to zero only once at program start!
21 LOGICAL :: lreset_internal, linterp
22
23 ! Allocates memory for radial arrays and initializes radial profiles
24 ! Loads data (if available) from a reset file
25
26 ! print *, "initialize_radial"
27
28 ! !!! THIS must be the ONLY place where this gets set to zero !!!
30
31 ! Set timestep control parameters
32 fsq = one
33
34 iter2 = 1
35 iter1 = iter2
36
37 ijacob = 0
38 first = 1
39 res0 = -1
40 delt0 = delt
41
42 ! start: INITIALIZE MESH-DEPENDENT SCALARS
43
44 ! radial grid: only depends on ns
45 ns = nsval
46 ns1 = ns-1.0_dp
47 hs = one/ns1
48 ohs = ns1 ! one/hs ! == ns1, but real-valued variant to avoid some kind of roundoff error ?
49
50 ! real-space grid on surfaces
51 nrzt = ns*nznt
52
53 ! Fourier-space resolution
54 mns = ns*mnsize ! number of flux surfaces * number of Fourier coeffs per surface --> total size of Fourier basis (n>=0)
55 irzloff = ntmax*mns ! total number of Fourier coeffs for each of R, Z and Lambda --> including (lasym, lthreed)-dependent ntmax
56 neqs = 3*irzloff ! degrees of freedom == total number of (R,Z,Lambda) Fourier coefficients
57
58 ! end: INITIALIZE MESH-DEPENDENT SCALARS
59
60 WRITE (nthreed, 10) ns, mnmax, ftolv, niterv
61 print 10, ns, mnmax, ftolv, niterv
6210 FORMAT(/' NS = ',i4,' NO. FOURIER MODES = ',i4,' FTOLV = ',1p,e10.3,' NITER = ',i6)
63
64 lreset_internal = .true.
65
66 ! check that interpolating from coarse to fine mesh
67 ! and that old solution is available
68 linterp = (ns_old.lt.ns .and. ns_old.ne.0)
69
70 IF (ns_old .ne. ns) then
71
72 ! ALLOCATE NS-DEPENDENT ARRAYS
73 CALL allocate_ns(linterp, neqs_old)
74
75 ! SAVE THIS FOR INTERPOLATION
76 ! gc is re-used here for old, scaled xc
77 IF (neqs_old.gt.0 .and. linterp) THEN
78 gc(1:neqs_old)=scalxc(1:neqs_old)*xstore(1:neqs_old)
79 END IF
80
81 ! reset Fourier coefficients vector if lreset was specified
82 xcdot = 0.0_dp
83 IF (lreset_internal) THEN
84 xc = 0.0_dp
85 END IF
86
87 ! COMPUTE INITIAL R, Z AND MAGNETIC FLUX PROFILES
88 CALL profil1d()
89
90 ! TODO: lreset .and. .not.linter?
91 ! If xc is overwritten by interp() anyway, why bother to initialize it in profil3d()?
92 ! I guess this also triggers computing the new scalxc...
93 CALL profil3d(xc(1), xc(1+irzloff), lreset_internal)
94
95 ! first.eq.1 at entry of restart_iter means to store xc in xstore
96 first = 1
97 CALL restart_iter(delt)
98
99 ! INTERPOLATE FROM COARSE (ns_old) TO NEXT FINER (ns) RADIAL GRID
100 IF (linterp) THEN
101 ! print *, "interpolate from previous solution"
102
103 CALL interp (xc, gc, scalxc, ns, ns_old)
104 END IF
105
106 ns_old = ns
107 neqs_old = neqs
108 end if
109
110END SUBROUTINE initialize_radial
subroutine allocate_ns(linterp, neqs_old)
allocate arrays depending on the number of flux surfaces ns
subroutine initialize_radial(nsval, ns_old, delt0)
Allocates memory for radial arrays and initializes radial profiles.
subroutine interp(xnew, xold, scalxc, nsnew, nsold)
Interpolate , and on full grid.
Definition interp.f90:12
integer irzloff
offset in xc array between R,Z,L components
real(rprec) fsq
real(rprec) hs
radial mesh size increment
Definition vmec_main.f90:84
real(rprec) ftolv
integer iter1
number of iterations at which the currently active evolution was branched off from
real(rprec) ohs
Definition vmec_main.f90:87
integer neqs
total number of equations to evolve (size of xc)
integer first
"counter" monitoring sign of jacobian; resets R, Z, and Lambda when jacobian changes sign and decreas...
integer niterv
max iterations for current multi-grid iteration
integer ijacob
counter for number of times jacobian changes sign
integer num_eqsolve_retries
real(rprec) res0
integer iter2
total number of iterations
integer ntmax
number of contributing Fourier basis function (can be 1, 2 or 4); assigned in read_indata()
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 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
subroutine profil1d()
Compute phip and iota profiles on full grid.
Definition profil1d.f90:10
subroutine profil3d(rmn, zmn, lreset)
Compute three-dimensional profiles of flux-surface geometry etc.
Definition profil3d.f90:10
subroutine restart_iter(time_step)
Save current or restore previous good state vector and reduce time step.