VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
interp.f90
Go to the documentation of this file.
1
3
11SUBROUTINE interp(xnew, xold, scalxc, nsnew, nsold)
12 USE vmec_main, ONLY: dp, rprec, mnsize
13 USE vmec_params, ONLY: ntmax
14 USE vmec_persistent, ONLY: ixm
15 use vmec_dim
16 use vmec_input
17
18 use dbgout
19
20 IMPLICIT NONE
21
22 INTEGER, intent(in) :: nsnew, nsold
23 REAL(rprec), DIMENSION(nsnew,mnsize,3*ntmax), INTENT(out) :: xnew
24 REAL(rprec), DIMENSION(nsnew,mnsize,3*ntmax), INTENT(in) :: scalxc
25 REAL(rprec), DIMENSION(nsold,mnsize,3*ntmax), intent(inout) :: xold
26
27 REAL(rprec), PARAMETER :: zero=0.0_dp, one=1.0_dp
28
29 INTEGER :: ntype, js
30 integer, dimension(nsnew) :: js1, js2
31 REAL(rprec) :: hsold
32 real(rprec), dimension(nsnew) :: sj, s1, xint
33
34 IF (nsold .le. 0) RETURN
35
36 hsold = one/(nsold - 1.0_dp)
37
38 ! INTERPOLATE R,Z AND LAMBDA ON FULL GRID
39 ! (EXTRAPOLATE M=1 MODES,OVER SQRT(S), TO ORIGIN)
40 ! ON ENTRY, XOLD = X(COARSE MESH) * SCALXC(COARSE MESH)
41 ! ON EXIT, XNEW = X(NEW MESH) [ NOT SCALED BY 1/SQRTS ]
42 DO ntype = 1, 3*ntmax
43
44 ! extrapolation to axis for odd-m modes (?)
45 WHERE (mod(ixm(:mnsize), 2) .eq. 1) &
46 xold(1,:,ntype) = 2.0_dp*xold(2,:,ntype) - xold(3,:,ntype)
47
48 ! radial interpolation from old, coarse state vector to new, finer state vector
49 DO js = 1, nsnew
50
51 sj(js) = real(js - 1, rprec)/(nsnew - 1.0_dp)
52
53 js1(js) = 1 + ((js - 1)*(nsold - 1))/(nsnew - 1)
54 js2(js) = min(js1(js) + 1, nsold)
55
56 s1(js) = (js1(js) - 1.0_dp)*hsold
57
58 xint(js) = (sj(js) - s1(js))/hsold
59 xint(js) = min(one, xint(js))
60 xint(js) = max(zero,xint(js))
61
62 xnew(js,:,ntype) = ( (one - xint(js))*xold(js1(js),:,ntype) &
63 + xint(js) *xold(js2(js),:,ntype) )/scalxc(js,:,1)
64 END DO
65
66 ! Zero M=1 modes at origin
67 ! Actually, all odd-m modes are zeroed!
68 WHERE (mod(ixm(:mnsize), 2) .eq. 1) &
69 xnew(1,:,ntype) = 0.0_dp
70
71 END DO
72
73 if (open_dbg_context("interp")) then
74
75 call add_real_1d("sj", nsnew, sj)
76 call add_int_1d("js1", nsnew, js1-1) ! index shift: Fortran starts at 1, Java at 0
77 call add_int_1d("js2", nsnew, js2-1) ! index shift: Fortran starts at 1, Java at 0
78 call add_real_1d("s1", nsnew, s1)
79 call add_real_1d("xint", nsnew, xint)
80
81 call add_real_5d("xold", 3, ntmax, nsold, ntor1, mpol, xold, order=(/ 3, 4, 5, 2, 1 /) )
82 call add_real_5d("xnew", 3, ntmax, nsnew, ntor1, mpol, xnew, order=(/ 3, 4, 5, 2, 1 /) )
83 call add_real_5d("scalxc", 3, ntmax, nsnew, ntor1, mpol, scalxc, order=(/ 3, 4, 5, 2, 1 /) )
84
85 call close_dbg_out()
86 end if
87
88END SUBROUTINE interp
subroutine interp(xnew, xold, scalxc, nsnew, nsold)
Interpolate , and on full grid.
Definition interp.f90:12
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
integer ntor1
ntor+1
Definition vmec_dim.f90:7
integer mnsize
Definition vmec_dim.f90:15
integer mpol
integer ntmax
number of contributing Fourier basis function (can be 1, 2 or 4); assigned in read_indata()
integer, dimension(:), allocatable ixm