V3FIT
vmec_params.f
1  MODULE vmec_params
2  USE stel_kinds, ONLY: rprec, dp
3  USE vparams, ONLY: mpold
4 C-----------------------------------------------
5 C L o c a l P a r a m e t e r s
6 C-----------------------------------------------
7  INTEGER, PARAMETER :: meven = 0, modd = 1
8  INTEGER, PARAMETER :: ndamp = 10
9  INTEGER, PARAMETER :: ns4 = 25
10 
11  INTEGER, PRIVATE :: ink
12  INTEGER, PARAMETER, DIMENSION(0:mpold) ::
13  1 jmin1 = (/ 1,1,(2,ink=2,mpold) /), !starting js(m) values where R,Z are non-zero
14  2 jmin2 = (/ 1,2,(2,ink=2,mpold) /), !starting js(m) values for which R,Z are evolved
15  3 jlam = (/ 2,2,(2,ink=2,mpold) /) !starting js(m) values for which Lambda is evolved
16 
17 ! Besure to update werror in fileout.f when adding more error flags.
18  INTEGER, PARAMETER :: norm_term_flag=0, bad_jacobian_flag=1,
19  1 more_iter_flag=2,
20  2 jac75_flag=4, input_error_flag=5,
21  3 phiedge_error_flag=7,
22  4 ns_error_flag=8,
23  5 misc_error_flag=9,
24  6 successful_term_flag=11, !ftol force criterion has been met
25  7 bsub_bad_js1_flag=12,
26  8 r01_bad_value_flag=13,
27  9 arz_bad_value_flag=14
28  INTEGER, PARAMETER :: restart_flag=1, readin_flag=2,
29  1 timestep_flag=4,output_flag=8,
30  2 cleanup_flag=16, reset_jacdt_flag=32
31 
32  REAL(rprec), PARAMETER :: pdamp = 0.05_dp
33  CHARACTER(LEN=*), PARAMETER :: version_ = '9.0'
34 !-----------------------------------------------
35 ! L o c a l V a r i a b l e s
36 !-----------------------------------------------
37  INTEGER :: ntmax, rcc, rss, rsc, rcs, zsc, zcs, zcc, zss
38  INTEGER :: mnyq, nnyq
39  INTEGER, ALLOCATABLE :: uminus(:)
40  REAL(rprec), ALLOCATABLE :: mscale(:), nscale(:)
41  REAL(rprec) :: signgs, lamscale
42 !-----------------------------------------------
43 !
44 ! VERSION INFORMATION HISTORY
45 !
46 ! 8.00
47 ! a) added lforbal logical to fbal module to control whether to compute the flux-averaged
48 ! force balance equation printed in the threed1 file. This requires a modification of
49 ! the m=1,n=0 forces for R,Z in tomnsps subroutine. This works well, generally, and
50 ! yields an improved <EQUIF> in threed1 file. However, there have been some cases where
51 ! this non-variational departure fails to converge.
52 ! b) added "bias" to iotas in bcovar when determining preconditioner for very small iota
53 ! values. Seems to need this for improving convergence of preconditioned current-hole cases.
54 ! Eliminated in v8.20.
55 ! c) added "totzsps,a_hess" to recompute r,z,l rapidly for only those modes that are jogged during
56 ! Hessian calculation. NOTE: need to do this for lasym=true case, as well, eventually
57 ! 8.20 (August, 2004)
58 ! a) removed 2-pt tie at origin for m=1 modes, to preserve tri-diagonal structure of Hessian.
59 ! This is needed for preconditioning, which assumes block-tridi structure of equations
60 ! b) fixed problem with free-boundary preconditioner, namely, ctor can not be extrapolated
61 ! at edge when computing preconditioner, because this breaks tri-diagonal structure
62 ! c) added new variables to input file to control preconditioning:
63 ! 1) PRECON_TYPE: = 'default', default tri-di (block size = 1)
64 ! = 'cg', block tri-di, conjugate-gradient time-stepper
65 ! = 'gmres', " ", gmres time-stepper
66 ! = 'tfqmr', " ", transpose free qmr
67 ! 2) PREC2D_THRESHOLD: value of (unpreconditioned) forces at which block (2D) preconditioner
68 ! is turned on (=0 block preconditioner never turned on); recommended
69 ! (default) value ~ 1.E-10, or smaller, if convergence is poor
70 ! 3) LFORBAL: logical variable (default = .true.); when true, the force balance
71 ! used in the threed1 file is used to evolve the m=1 R,Z components. This
72 ! is a non-variational departure from the force equations for these modes,
73 ! but generally does not have an unfavorable impact on convergence.
74 ! d) added new internal variable, ICTRL_PREC2D, to precon2d module. Replaces previous lprec2d
75 ! and iequi>1 variables.
76 ! e) removed lsweep_fast option from module precon2d. This slows the computation of the Hessian
77 ! by about 2/3, but is more accurate (includes pdamp, liota, lforbal correctly)
78 ! f) removed lflam logicals from bcovar and tomnsps, since now we must compute dFlam/dR,Z by
79 ! jogging
80 ! g) removed Compute_Hess_Flam_RZ from lamblks; this is now computed via jogging
81 ! (also removed Get_dFlam_dRZ, FFT2Hessian, Forbal_avg, GetGsqrtVar supporting routines)
82 ! h) removed internal liota logic, used to push iota profile rather than solving for it. Had
83 ! needed this for symmetric Hessian (lsweep_fast=true option), but no longer required. Also,
84 ! it was not implemented entirely correctly for lforbal=true case
85 ! i) for lasym m=1 constraint rsc = zcc, changed xc array so that R+ = .5*(rsc + zcc) is stored at
86 ! xc(rsc,m=1) and R- = .5*(rsc - zcc) is stored at xc(zcc,m=1). In residue, gcz(R-) == gcz(zcc)
87 ! is zeroed by "evolving" gcr(zcc) = azd*[xc(zcc)-xcint], and gcr(rsc) => .5*[gcr(rsc) + gcz(zcc)]
88 ! is evolved. In totzspa, the real rsc and zcc are computed from the internal representations
89 ! (check convert call, too) by calling a new routine convert_asym (also called from wrout before
90 ! writing out xc info). In readin, the original R+,R- are stored, so that for external "jogs",
91 ! there will be no change in forces. All these changes are needed to obtain an invertible Hessian.
92 ! j) added m=1 constraint for 3D case (similar to (i)), rss(n) = zcs(n), for n != 0. Imposed this
93 ! on forces by adding routine constrain_m1 in residue. Added convert_sym routine to totzsp to convert
94 ! from internal xc representation TO internal one.
95 ! k) Decreased exponent on pdamp factor r2 (in bcovar) from 2 to 1, to give better conditioning
96 ! especially for current hole cases
97 ! l) Eliminated iotas bias for determining preconditioner, previously added in v8.00 for stabilizing
98 ! current hole cases (not needed with corrected preconditioner)
99 ! 8.30 (October, 2004)
100 ! a) Implemented flags for "reverse-communication" mode of vmec
101 ! 8.40 a) Converted the m=1 constraints for 3D and asym back to old way; did not always
102 ! converge well with the new constraints introduced in 8.20 (i-j)
103 ! 8.45 (December, 2005)
104 ! a) Added the lconm1 logical. If = True, new constraint; if = False, old m=1 constraint used
105 ! b) Added "perturbation" computation for lasym=TRUE case (totzspa_hess)
106 ! 8.46 (June, 2009)
107 ! a) Added LRFP logical to allow easy switching of profiles between Stellarator/tokamak (PHIP=1, LRFP=F)
108 ! and RFP (CHIP=1, LRFP=T). When LRFP=T, AI coefficients are expansion of q = 1/iota. Added lrfp to
109 ! LIBSTELL/vmec_input module.
110 ! 8.47 (July, 2010)
111 ! a) Rewrote magnetic field representation so that phip*lambda = new internal lambda. This greatly improves
112 ! the conditioning of the lambda equations which otherwise become singular at the RFP reversal point
113 ! 8.48 (March 2012 - JDH)
114 ! a) Accumulated small changes from SPH & JDH
115 ! b) Modifications from J Geiger, March 2012
116 ! - to be able to get additional main iterations if the force tolerance is
117 ! not met. Parameter MAX_MAIN_ITERATIONS specifies how many main iteration
118 ! cycles should be run.
119 ! - to get a full output in the threed1-file if the force tolerance is not
120 ! met. Specify the logical LFULL3D1OUT to true for this.
121 ! - if vmec2000 is compiled with netcdf, you can still get the ascii-output
122 ! if you specify the logical LWOUTTXT as true.
123 ! - you get the output for diagno 1.0 and 1.5 if the logical LDIAGNO set true.
124 ! - you get a rather old fort.8-output if you specify LOLDOUT as true.
125 !
126 ! If none of these new variables is set, the behavior of vmec2000 is as
127 ! expected from the version without the changes.
128 ! 8.49 (June, 2012)
129 ! a) Fixed bug in bcovar when averaging half-grid covariant components onto full grid: did not
130 ! zero components at (phantom) js=1 point, so edge force averages were incorrect
131 ! b) Added lamscale factor to scale lambda in contravariant B-components. Modify wrout to maintain
132 ! old-style lambda output
133 ! c) Set lbsubs=F in jxbforce by default to capture current sheets
134 ! d) Added lmove_axis INPUT logical (=T by default) so user can control whether or not the magnetic
135 ! axis can be initially shifted to improve the initial force residuals. It is important NOT to move
136 ! the helical axis for RFP equilibria requiring a helical seed (set l_moveaxis=F for this case!)
137 !
138 ! 8.50 (Jan, 2013)
139 ! a) Improved scaling of lambda forces with respect to lamscale
140 ! b) Fixed fnorm1 scaling (remove hs dependence)
141 ! c) Added lgiveup logical (M. Drevlak/J. Geiger)
142 !-----------------------------------------------
143  END MODULE vmec_params