11SUBROUTINE interp(xnew, xold, scalxc, nsnew, nsold)
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
27 REAL(rprec),
PARAMETER :: zero=0.0_dp, one=1.0_dp
30 integer,
dimension(nsnew) :: js1, js2
32 real(rprec),
dimension(nsnew) :: sj, s1, xint
34 IF (nsold .le. 0)
RETURN
36 hsold = one/(nsold - 1.0_dp)
46 xold(1,:,ntype) = 2.0_dp*xold(2,:,ntype) - xold(3,:,ntype)
51 sj(js) = real(js - 1, rprec)/(nsnew - 1.0_dp)
53 js1(js) = 1 + ((js - 1)*(nsold - 1))/(nsnew - 1)
54 js2(js) = min(js1(js) + 1, nsold)
56 s1(js) = (js1(js) - 1.0_dp)*hsold
58 xint(js) = (sj(js) - s1(js))/hsold
59 xint(js) = min(one, xint(js))
60 xint(js) = max(zero,xint(js))
62 xnew(js,:,ntype) = ( (one - xint(js))*xold(js1(js),:,ntype) &
63 + xint(js) *xold(js2(js),:,ntype) )/scalxc(js,:,1)
69 xnew(1,:,ntype) = 0.0_dp
75 call add_real_1d(
"sj", nsnew, sj)
76 call add_int_1d(
"js1", nsnew, js1-1)
77 call add_int_1d(
"js2", nsnew, js2-1)
78 call add_real_1d(
"s1", nsnew, s1)
79 call add_real_1d(
"xint", nsnew, xint)
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 /) )
subroutine interp(xnew, xold, scalxc, nsnew, nsold)
Interpolate , and on full grid.
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...