9 real(r8),
public :: cscale
13 real(r8),
allocatable :: j_tor_hat(:)
14 real(r8),
allocatable :: j_tor_hat_av(:), I_tor_hat(:)
16 real(r8),
allocatable,
public :: j_tor_loc(:), j_tor_av(:), I_tor(:)
32 integer(itm_i4),
intent(in) :: nr, np
34 allocate(j_tor_hat((nr - 1) * (np - 1)))
35 allocate(j_tor_hat_av(nr))
36 allocate(i_tor_hat(nr))
37 allocate(j_tor_loc((nr - 1) * (np - 1)))
38 allocate(j_tor_av(nr))
52 deallocate(j_tor_hat, j_tor_hat_av)
53 deallocate(j_tor_loc, j_tor_av)
54 deallocate(i_tor_hat, i_tor)
77 real(r8),
intent(in) :: a, xaxis
78 character(len = *),
intent(in) :: type
80 real(r8) :: dl(np - 1), df(np - 1)
81 integer(itm_i4) :: i, j, n
94 j_tor_hat(n) = -eps * df(j)
114 use mod_dat, only : rvac, bvac, eps
124 character(len = 6),
parameter :: type =
'area '
126 real(r8),
intent(in) :: a, xaxis
127 real(r8),
intent(out) :: toroidal_current
129 real(r8) :: df(np - 1), da(np - 1)
130 real(r8) :: da_sum, i_sum, factas
131 integer(itm_i4) :: i, j
140 if (ias == 1) factas = 1._r8
147 da_sum = da_sum + da(j)
149 i_sum = i_sum + factas * j_tor_hat_av(i) * da_sum
153 toroidal_current = i_tor_hat(nr) * rvac * bvac * eps / (4.e-7_r8 * pi)
155 if (standard_output) &
156 write(out_he, 4) toroidal_current
157 4
format(
' total current (alfa = 1) : ', e12.4)
176 j0 = bvac / (mu0 * eps * rvac * alfa)
177 i0 = j0 * (eps * rvac)**2
180 j_tor_loc = j0 * j_tor_hat
181 j_tor_av = j0 * j_tor_hat_av
183 i_tor = i_tor_hat * i0
203 real(r8),
intent(in) :: xaxis, cx, cy
204 real(r8),
intent(in) :: a
205 real(r8),
intent(inout) :: q(nr)
209 real(r8) :: x, xr, xs, xrs, xrr, xss
210 real(r8) :: y, yr, ys, yrs, yrr, yss
211 real(r8) :: ps, psr, pss, psrs, psrr, psss
212 real(r8) :: jacobian, bigr, dl, grad_psi2
213 integer(itm_i4) :: i, j, ngs
214 integer(itm_i4) :: n1, n2, n3, n4
218 call
profiles(p0, rbphi, dp0, drbphi, a)
221 if (ias == 1) factas = 1._r8
228 n1 = (i - 1) * np + j
236 xx(1, n4), r, s, x, xr, xs, xrs, xrr, xss)
238 yy(1, n4), r, s, y, yr, ys, yrs, yrr, yss)
240 psi(4 * (n2 - 1) + 1), psi(4 * (n3 - 1) + 1), &
241 psi(4 * (n4 - 1) + 1), r, s, ps, psr, pss, psrs, psrr, psss)
242 jacobian = xr * ys - xs * yr
243 bigr = 1._r8 + eps * x
244 dl = sqrt(xs**2 + ys**2)
245 grad_psi2= psr**2 * (xs**2 + ys**2) / jacobian**2
246 sumq = sumq + wgauss(ngs) / (bigr * sqrt(grad_psi2)) * dl
249 q(nr - i + 1) = 0.5_r8 * factas * sumq * rbphi(nr - i + 1)
251 q(1) = rbphi(1) * pi / (2._r8 * sqrt(cx * cy) * (1. + eps * xaxis))
253 q(i) = q(i) * alfa / pi
subroutine profiles(p0, rbphi, dp0, drbphi, a)
subroutine, public q_calculation(xaxis, cx, cy, a, q)
subroutine interpolation(type_interp, xn1, xn2, xn3, xn4, r, s, x, xr, xs, xrs, xrr, xss, yn1, yn2, yn3, yn4, pn1, pn2, pn3, pn4, yr, ys, ps)
real(r8) function rh_side(a, x, xr, xs, yr, ys, psi, psir, F_dia)
real(r8) function, public flux_surface_average(i, xaxis, a, F_dia, type, func)
subroutine, public si_currents
subroutine, public current_densities(a, xaxis, type)
subroutine, public element_average(i, type, xaxis, a, F_dia, func, df, dl)
subroutine, public total_current(a, xaxis, toroidal_current)
real(r8) function identity(a, x, xr, xs, yr, ys, psi, psir, F_dia)
subroutine, public current_calculations_destructor
subroutine, public current_calculations_constructor(nr, np)