VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
read_indata.f90
Go to the documentation of this file.
1
3
9SUBROUTINE read_indata(in_file, iunit, ier_flag)
10 USE vmec_main
11 USE vmec_input, ONLY: bloat, ncurr
12 USE vmec_params
13 USE vacmod0, only: set_nestor_sizes
16 IMPLICIT NONE
17
18 INTEGER ier_flag, iunit
19 CHARACTER(LEN=*) :: in_file
20
21 INTEGER :: ireadseq, iosnml = 0
22
23 iunit = indata0
24 CALL safe_open (iunit, ireadseq, in_file, 'old', 'formatted')
25 IF (ireadseq .ne. 0) THEN
26 WRITE (6, '(3a,i4)') ' In VMEC, error opening input file: ',trim(in_file),'. Iostat = ', ireadseq
27 ier_flag = input_error_flag
28 RETURN
29 ENDIF
30
31 ! set indata parameters to default values and
32 ! overwrite with whatever is declared in the input file in namelist /indata/
33 iosnml = 0
34 rewind(iunit)
35 CALL read_indata_namelist (iunit, iosnml)
36
37 IF (iosnml .ne. 0) THEN
38 WRITE (6, '(a,i4)') ' In VMEC, indata NAMELIST error: iostat = ', iosnml
39 ier_flag = input_error_flag
40 RETURN
41 ENDIF
42
43 IF (lfreeb .and. mgrid_file.eq.'NONE') then
44 ! disable free-boundary mode if mgrid file is not specified
45 lfreeb = .false.
46 end if
47
48 IF (bloat .eq. zero) bloat = one
49 IF ((bloat.ne.one) .and. (ncurr.ne.1)) THEN
50 ! bloat != 1 is only allowed when ncurr == 1 (constrained toroidal current)
51 ier_flag = 3 ! 'VMEC INDATA ERROR: NCURR.ne.1 but BLOAT.ne.1.'
52 RETURN
53 ENDIF
54
55 ! fixup current profile
56 IF (ncurr.eq.1 .and. all(ac.eq.cbig)) then
57 ! previous version input of current profile: via ai (iota profile coeffs)
58 ! Old FORMAT: may not be reading in ac
59 ac = ai
60 end if
61 WHERE (ac .eq. cbig) ac = zero
62
63 ! COMPUTE NTHETA, NZETA VALUES
64 mpol = abs(mpol)
65 ntor = abs(ntor)
66 IF (mpol .gt. mpold) stop 'mpol>mpold: lower mpol'
67 IF (ntor .gt. ntord) stop 'ntor>ntord: lower ntor'
68 mpol1 = mpol - 1
69 ntor1 = ntor + 1
70
71 IF (ntheta .lt. 2*mpol+6 ) THEN
72 ! number of theta grid points (>=2*mpol+6)
73 ntheta = 2*mpol+6
74 ENDIF
75
76 ntheta1 = 2*(ntheta/2) ! even (rounded down) ntheta
77 ! u = pi
78 ntheta2 = 1 + ntheta1/2 ! odd stellarator-symmetric little-more-than-half of ntheta
79
80 lthreed = (ntor .gt. 0)
81
82 IF (ntor.eq.0 .and. nzeta.eq.0) then
83 ! Tokamak (ntor=0) needs (at least) nzeta=1
84 ! I think this implies that in principle one could do an axisymmetric run with nzeta>1...
85 nzeta = 1
86 end if
87
88 IF (ntor.gt.0)then
89 ! Stellarator case needs Nyquist criterion fulfilled for nzeta wrt. ntor
90 IF (nzeta .lt. 2*ntor+4) THEN
91 nzeta = 2*ntor+4 !number of zeta grid points (=1 IF ntor=0)
92 ENDIF
93 ENDIF
94
95 ! SIZE of rmnc, rmns, ...
96 mnmax = ntor1 + mpol1*(1 + 2*ntor)
97
98 ! SIZE of rmncc, rmnss, ...
99 ! --> m = 0, 1, ..., (mpol-1); n = 0, 1, ..., ntor
100 mnsize = mpol*ntor1
101
102 ! INDEXING FOR PACKED-ARRAY STRUCTURE OF XC, GC
103 ! The result of this can be seen in the comment section at the top of data/xstuff.f90 .
104 rcc = 1; zsc = 1
105 rss = 0; rsc = 0; rcs = 0
106 zcc = 0; zss = 0; zcs = 0
107 IF (.NOT.lasym) THEN
108 ! can make use of Stellarator symmetry
109 ntheta3 = ntheta2
110 IF (lthreed) THEN
111 ntmax = 2
112 rss = 2; zcs = 2
113 ELSE ! lthreed = F
114 ntmax = 1
115 END IF
116 ELSE ! lasym = T
117 ntheta3 = ntheta1
118 IF (lthreed) THEN
119 ntmax = 4
120 rss = 2; rsc = 3; rcs = 4
121 zcs = 2; zcc = 3; zss = 4
122 ELSE ! lthreed = F
123 ntmax = 2
124 rsc = 2; zcc = 2
125 END IF
126 END IF
127
128 nznt = nzeta*ntheta3
129
131
132END SUBROUTINE read_indata
fault-tolerant file opening routines
subroutine safe_open(iunit, istat, filename, filestat, fileform, record_in, access_in, delim_in)
subroutine set_nestor_sizes(nfp, ntor, mpol, nzeta, ntheta, lasym)
Definition vacmod0.f90:28
subroutine read_indata_namelist(iunit, istat)
real(rprec), dimension(0:20) ac
array of coefficients in phi-series for the quantity d(Icurv)/ds = toroidal current density * Vprime,...
logical lfreeb
integer ntheta
real(rprec) bloat
character(len=200) mgrid_file
logical lasym
real(rprec), dimension(0:20) ai
array of coefficients in phi-series for iota (ncurr=0)
integer nfp
integer ntor
integer nzeta
integer mpol
integer ncurr
logical lthreed
integer, parameter input_error_flag
integer ntmax
number of contributing Fourier basis function (can be 1, 2 or 4); assigned in read_indata()
subroutine read_indata(in_file, iunit, ier_flag)
Read the INDATA namelist from a given input file.