VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
eqsolve.f90
Go to the documentation of this file.
1
3
7SUBROUTINE eqsolve(ier_flag)
8
9 USE vmec_main
12 USE realspace
13 USE xstuff
14
16
17 IMPLICIT NONE
18
19 INTEGER, intent(inout) :: ier_flag
20
21 REAL(rprec), PARAMETER :: p98 = 0.98_dp
22 REAL(rprec), PARAMETER :: p96 = 0.96_dp
23
24 REAL(rprec) :: w0
25 LOGICAL :: liter_flag
26
27 ! TODO: initial value of lreset_internal was undefined! --> now set to false
28 LOGICAL :: lreset_internal
29
30! print *, " eqsolve"
31
32 ! need to do this before jump label 20 to allow restart_iter to do its magic
33 lreset_internal = .false.
34
35 liter_flag = iter2 .eq. 1 ! true at start of current multi-grid iteration
36
37 ! COMPUTE INITIAL R, Z AND MAGNETIC FLUX PROFILES
3820 CONTINUE ! try again
39
40 ! !!! THIS must be the ONLY place where this gets incremented !!!
42
43 ! print *, "goto 20, num_eqsolve_retries = ", num_eqsolve_retries
44
45 ! RECOMPUTE INITIAL PROFILE, BUT WITH IMPROVED AXIS
46 ! OR
47 ! RESTART FROM INITIAL PROFILE, BUT WITH A SMALLER TIME-STEP
48 IF (first .EQ. 2) THEN
49 xc = 0.0_dp
50
51 CALL profil3d (xc(1), xc(1+irzloff), lreset_internal)
52
53 first = 1 ! tells restart_iter to store current xc in xstore
54 IF (liter_flag) then
55 ! Note that at this point, liter_flag could also simply contain (iter2 .eq. 1) (see above).
56 ! (OFF IN v8.50)
58 end if
59 END IF
60
61 ! start normal iterations
62 liter_flag = .true.
63
64 ! reset error flag
65 ier_flag = norm_term_flag
66
67 ! FORCE ITERATION LOOP
68 iter_loop: DO WHILE (liter_flag)
69
70 ! ADVANCE FOURIER AMPLITUDES OF R, Z, AND LAMBDA
71 CALL evolve (delt0r, ier_flag, liter_flag)
72
73 ! check for bad jacobian and bad initial guess for axis
74 IF (ijacob.eq.0 .and. &
75 (ier_flag.eq.bad_jacobian_flag .or. first.eq.4) .and. &
76 ns.ge.3) THEN
77
78 IF (ier_flag .eq. bad_jacobian_flag) THEN
79 print *, ' INITIAL JACOBIAN CHANGED SIGN!'
80 END IF
81
82 print *, ' TRYING TO IMPROVE INITIAL MAGNETIC AXIS GUESS'
83
84 CALL guess_axis (r1, z1, ru0, zu0)
85 ijacob = 1
86
87 ! prepare parameters to functions that get called due to lreset_internal and first=2
88 lreset_internal = .true.
89 first = 2
90 GOTO 20 ! try again
91 ELSE IF (ier_flag.ne.norm_term_flag .and. &
92 ier_flag.ne.successful_term_flag) THEN
93 ! if something went totally wrong even in this initial stuff,
94 ! so do not continue
95 RETURN
96 ENDIF
97
98 ! compute MHD energy
99 w0 = wb + wp/(gamma - one)
100
101
102
103
104
105 ! ADDITIONAL STOPPING CRITERION (set liter_flag to FALSE)
106
107 ! the blocks for ijacob=25 or 50 are equal up to the point
108 ! that for 25, delt0r is reset to 0.98*delt (delt given by user)
109 ! and for 50, delt0r is reset to 0.96*delt (delt given by user)
110 IF (ijacob .eq. 25) THEN
111 ! jacobian changed sign 25 times: hmmm? :-/
112 first = 2
113 CALL restart_iter(delt0r)
114 delt0r = p98*delt
115 print 120, delt0r
116 first = 1 ! done by restart_iter already...
117 GOTO 20 ! try again
118 ELSE IF (ijacob .eq. 50) THEN
119 ! jacobian changed sign 50 times: what the hell? :-S
120 first = 2
121 CALL restart_iter(delt0r)
122 delt0r = p96*delt
123 print 120, delt0r
124 first = 1 ! done by restart_iter already...
125 GOTO 20 ! try again
126 ELSE IF (ijacob .ge. 75) THEN
127 ! jacobian changed sign at least 75 times: time to give up :-(
128 ier_flag = jac75_flag ! 'MORE THAN 75 JACOBIAN ITERATIONS (DECREASE DELT)'
129 liter_flag = .false.
130 ELSE IF (iter2.ge.niterv .and. liter_flag) THEN
131 ! allowed number of iterations exceeded
132 liter_flag = .false.
133 ENDIF
134
135 120 FORMAT(2x,'HAVING A CONVERGENCE PROBLEM: RESETTING DELT TO ',f8.3,&
136 /,2x,'If this does NOT resolve the problem, try changing ', &
137 '(decrease OR increase) the value of DELT')
138
139
140
141
142
143 ! TIME STEP CONTROL
144
145 IF (iter2.eq.iter1 .or. res0.eq.-1) then
146 ! if res0 has never been assigned (-1), give it the current value of fsq
147 res0 = fsq
148 end if
149
150 ! res0 is the best force residual we got so far
151 res0 = min(res0,fsq)
152
153 IF (fsq.le.res0 .and. iter2-iter1.gt.10) THEN
154 ! Store current state (first=1)
155 ! --> was able to reduce force consistenly over at least 10 iterations
156 CALL restart_iter(delt0r)
157 ELSE IF (fsq.gt.100*res0 .and. iter2.gt.iter1) THEN
158 ! Residuals are growing in time, reduce time step
159 first = 2
160 ELSE IF (iter2-iter1 .gt. ns4/2 .and. &
161 iter2 .gt. 2*ns4 .and. &
162 fsqr+fsqz .gt. c1pm2 ) THEN ! 1.0e-2
163
164 ! quite some iterations and quite large forces
165 ! --> restart with different timestep
166
167 ! TODO: maybe the threshold 0.01 is too large nowadays
168 ! --> this could help fix the cases where VMEC gets stuck immediately at ~2e-3
169 ! --> lower threshold, e.g. 1e-4 ?
170
171 first = 3
172 ENDIF
173
174
175
176
177
178 IF (first .ne. 1) THEN
179 ! Retrieve previous good state
180 CALL restart_iter(delt0r)
181 iter1 = iter2
182
183 ! This breaks the dbgout logic, in that the same iter2 and num_eqsolve_retries combination is touched twice.
184 ! Hence, allow ONCE to overwrite the output file.
185 skip_dbgout_collison = .true.
186 ELSE
187 ! Increment time step and printout every nstep iterations
188 ! status report due or
189 ! first iteration or
190 ! iterations cancelled already (last iteration)
191 IF (mod(iter2, nstep) .eq. 0 .or. &
192 iter2 .eq. 1 .or. &
193 .not.liter_flag) then
194
195 CALL printout(iter2, delt0r, w0)
196 end if
197
198 ! count iterations
199 iter2 = iter2 + 1
200
201 ! Disable again the temporary overwrite that was allowed above.
202 ! Trust on VMEC to reach this branch in the next iteration.
203 skip_dbgout_collison = .false.
204 ENDIF
205
206
207
208
209 ! ivac gets set to 1 in vacuum() of NESTOR
210 IF (ivac .eq. 1) THEN
211 ! vacuum pressure turned on at iter2 iterations (here)
212 print 110, iter2
213 WRITE (nthreed, 110) iter2
214110 FORMAT(/,2x,'VACUUM PRESSURE TURNED ON AT ',i4,' ITERATIONS'/)
215
216 ! this makes ivac=1 --> ivac=2
217 ivac = ivac + 1
218 ENDIF
219
220 END DO iter_loop
221
222 ! write MHD energy at end of iterations for current number of surfaces
223 WRITE (nthreed, 60) w0*twopi**2.0_dp
22460 FORMAT(/,' MHD Energy = ',1p,e12.6)
225
226END SUBROUTINE eqsolve
subroutine eqsolve(ier_flag)
Iteratively evolve the Fourier coefficients that specify the equilibrium.
Definition eqsolve.f90:8
subroutine evolve(time_step, ier_flag, liter_flag)
Take a single time step in Fourier space to evolve the Fourier coefficients describing the equilibriu...
Definition evolve.f90:12
subroutine guess_axis(r1, z1, ru0, zu0)
Computes guess for magnetic axis if user guess leads to initial sign change of Jacobian.
logical skip_dbgout_collison
Definition dbgout.f90:5
real(rprec), dimension(:), allocatable zu0
, even-m and odd-m added together appropriately
Definition realspace.f90:25
real(rprec), dimension(:), allocatable ru0
, even-m and odd-m added together appropriately
Definition realspace.f90:24
real(rprec), dimension(:,:), allocatable, target z1
Definition realspace.f90:11
real(rprec), dimension(:,:), allocatable r1
Definition realspace.f90:8
integer irzloff
offset in xc array between R,Z,L components
real(rprec) fsq
real(rprec) wp
kinetic/thermal energy (from pressure)
integer iter1
number of iterations at which the currently active evolution was branched off from
real(rprec) fsqr
Definition vmec_main.f90:94
real(rprec) fsqz
Definition vmec_main.f90:95
integer first
"counter" monitoring sign of jacobian; resets R, Z, and Lambda when jacobian changes sign and decreas...
real(rprec) delt0r
integer ivac
counts number of free-boundary iterations
integer niterv
max iterations for current multi-grid iteration
integer ijacob
counter for number of times jacobian changes sign
real(rprec) wb
magnetic energy: volume integral over B^2/2
integer num_eqsolve_retries
real(rprec) res0
integer iter2
total number of iterations
integer, parameter bad_jacobian_flag
integer, parameter jac75_flag
integer, parameter successful_term_flag
integer, parameter ns4
integer, parameter norm_term_flag
real(rprec), dimension(:), allocatable, target xc
stacked array of scaled R, Z, Lambda Fourier coefficients (see above for stack order)
Definition xstuff.f90:40
subroutine printout(i0, delt0, w0)
Print iteration progress to screen and threed1 output file.
Definition printout.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.