VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
evolve.f90
Go to the documentation of this file.
1
4
11SUBROUTINE evolve(time_step, ier_flag, liter_flag)
12 USE vmec_main
15 USE xstuff
16
17 use dbgout
18
19 IMPLICIT NONE
20
21 REAL(rprec), intent(in) :: time_step
22 INTEGER, INTENT(inout) :: ier_flag
23 LOGICAL, INTENT(inout) :: liter_flag
24
25 integer :: i
26 CHARACTER(LEN=*), PARAMETER :: fcn_message = "External calls to FUNCT3D: "
27 REAL(rprec) :: fsq1, dtau, b1, fac
28 logical :: dbg_evolve
29
30 ! COMPUTE MHD FORCES
31 CALL funct3d (ier_flag)
32
33 ! COMPUTE ABSOLUTE STOPPING CRITERION
34 IF (iter2.eq.1 .and. first.eq.2) THEN
35 ! first iteration, jacobian was not computed correctly
36 ier_flag = bad_jacobian_flag
37 ELSE IF (fsqr.le.ftolv .and. fsqz.le.ftolv .and. fsql.le.ftolv) THEN
38 ! converged to desired tolerance
39 liter_flag = .false.
40 ier_flag = successful_term_flag
41 ENDIF
42
43 IF (ier_flag.ne.norm_term_flag .or. .not.liter_flag) then
44 ! errornous iteration or shall not iterate further
45 RETURN
46 end if
47 ! no error and not converged --> keep going...
48
49
50 ! COMPUTE DAMPING PARAMETER (DTAU) AND
51 ! EVOLVE R, Z, AND LAMBDA ARRAYS IN FOURIER SPACE
52
53 fsq1 = fsqr1 + fsqz1 + fsql1
54
55 IF (iter2 .eq. iter1) then
56 ! initialize all entries in otau to 0.15/time_step --> required for averaging
57 ! otau: "over" tau --> 1/tau ???
58 otau(:ndamp) = cp15/time_step
59 end if
60
61
62 IF (iter2 .gt. iter1 .and. fsq1 .ne. zero) then
63 ! fsq is 1 (first iteration) or fsq1 from previous iteration
64
65 ! fsq1/fsq is y_n assuming monotonic decrease of energy
66 ! dtau is temporarily re-used for something else here...
67 dtau = min(abs(log(fsq1/fsq)), cp15)
68 end if
69
70 ! update backup copy of fsq1
71 fsq = fsq1
72
73 ! shift array for averaging to the left to make space at end for new entry
74 otau(1:ndamp-1) = otau(2:ndamp)
75
76 IF (iter2 .gt. iter1) then
77 ! insert new 1/tau value at end of otau array
78 otau(ndamp) = dtau/time_step
79 end if
80
81 ! averaging over ndamp entries : 1/ndamp*sum(otau)
82 otav = sum(otau(:ndamp))/ndamp
83
84 dtau = time_step*otav/2.0_dp
85
86 b1 = one - dtau
87 fac = one/(one + dtau)
88
89 ! debugging output: xc, xcdot, gc before time step; xc and xcdot also after time step
90 dbg_evolve = open_dbg_context("evolve", num_eqsolve_retries)
91 if (dbg_evolve) then
92 call add_real_5d("xc_before", 3, ntmax, ns, ntor1, mpol, xc, order=(/ 3, 4, 5, 2, 1 /) )
93 call add_real_5d("xcdot_before", 3, ntmax, ns, ntor1, mpol, xcdot, order=(/ 3, 4, 5, 2, 1 /) )
94 call add_real_5d("gc", 3, ntmax, ns, ntor1, mpol, gc, order=(/ 3, 4, 5, 2, 1 /) )
95 end if
96
97 ! THIS IS THE TIME-STEP ALGORITHM. IT IS ESSENTIALLY A CONJUGATE
98 ! GRADIENT METHOD, WITHOUT THE LINE SEARCHES (FLETCHER-REEVES),
99 ! BASED ON A METHOD GIVEN BY P. GARABEDIAN
100 xcdot = fac*(b1*xcdot + time_step*gc) ! update velocity
101 xc = xc + time_step*xcdot ! advance xc by velocity given in xcdot
102
103 if (dbg_evolve) then
104 call add_real_5d("xc_after", 3, ntmax, ns, ntor1, mpol, xc, order=(/ 3, 4, 5, 2, 1 /) )
105 call add_real_5d("xcdot_after", 3, ntmax, ns, ntor1, mpol, xcdot, order=(/ 3, 4, 5, 2, 1 /) )
106
107 call close_dbg_out()
108 end if
109
110END SUBROUTINE evolve
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 funct3d(ier_flag)
Evaluate the three-dimensional MHD energy functional. Think of this as the "forward model" that tells...
Definition funct3d.f90:14
logical function open_dbg_context(context_name, repetition, id)
check if any output is desired for the current iteration check if the given context should be openend...
Definition dbgout.f90:17
real(rprec) fsqz1
real(rprec) fsql
Definition vmec_main.f90:96
real(rprec) fsq
real(rprec) ftolv
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), dimension(ndamp) otau
real(rprec) otav
time-step algorithm
real(rprec) fsqr1
Definition vmec_main.f90:99
integer num_eqsolve_retries
real(rprec) fsql1
integer iter2
total number of iterations
integer, parameter bad_jacobian_flag
integer, parameter successful_term_flag
integer ntmax
number of contributing Fourier basis function (can be 1, 2 or 4); assigned in read_indata()
integer, parameter norm_term_flag
integer, parameter ndamp
number of iterations over which damping is averaged
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 xcdot
"velocity": change of Fourier coefficients per time step
Definition xstuff.f90:43