VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
belicu.f90
Go to the documentation of this file.
1
3
14SUBROUTINE belicu(torcur, bx, by, bz, cos1, sin1, rp, zp)
15
16 USE vacmod, vm_bz => bz
17
18 use abscab, only: magneticfieldpolygonfilament
19
20 IMPLICIT NONE
21
22 REAL(rprec), INTENT(in) :: torcur
23 REAL(rprec), DIMENSION(nuv2), INTENT(in) :: cos1, sin1, rp, zp
24 REAL(rprec), DIMENSION(nuv2), INTENT(out) :: bx, by, bz
25
26 REAL(rprec) :: current
27 INTEGER :: i, j, kper, kv
28
29 REAL(rprec) :: L, Ri, Rf, Ri_p_Rf, Bmag
30 REAL(rprec), dimension(3) :: dvec, xpt, Ri_vec
31
32 real(rprec), dimension(3, nuv2) :: eval_pos, magnetic_field
33
34 ! If .true., use ABSCAB for computing the magnetic field contribution
35 ! due to the net toridal current modeled as a filament along the magnetic axis.
36 logical, parameter :: use_abscab_for_axis_current = .false.
37
38 ! B_External due to LIne CUrrent
39
40 ! net toroidal plasma current in A
41 current = torcur/mu0
42
43 ! loops over source geometry
44 i = 0
45 DO kper = 1, nvper
46 DO kv = 1, nv
47 i = i + 1
48
49 ! xpts == xpt of _s_ource (current filament)
50 xpts(1, i) = raxis_nestor(kv)*(cosper(kper)*cosuv(kv) - sinper(kper)*sinuv(kv))
51 xpts(2, i) = raxis_nestor(kv)*(sinper(kper)*cosuv(kv) + cosper(kper)*sinuv(kv))
52 xpts(3, i) = zaxis_nestor(kv)
53 END DO
54 END DO
55
56 ! last point is equal to first point --> closed curve
57 xpts(1, nvp + 1) = xpts(1, 1)
58 xpts(2, nvp + 1) = xpts(2, 1)
59 xpts(3, nvp + 1) = xpts(3, 1)
60
61 if (use_abscab_for_axis_current) then
62
63 DO j = 1, nuv2
64 ! evaluation positions
65 eval_pos(1, j) = rp(j) * cos1(j)
66 eval_pos(2, j) = rp(j) * sin1(j)
67 eval_pos(3, j) = zp(j)
68 end do
69
70 ! initialize target array
71 magnetic_field = 0.0_dp
72
73 ! use ABSCAB to compute the line-current-along-axis magnetic field contribution
74 call magneticfieldpolygonfilament(nvper * nv + 1, xpts, current, &
75 nuv2, eval_pos, magnetic_field)
76
77 bx(:) = magnetic_field(1,:)
78 by(:) = magnetic_field(2,:)
79 bz(:) = magnetic_field(3,:)
80
81 else ! use_abscab_for_axis_current
82
83 ! initialize target array
84 bx = 0
85 by = 0
86 bz = 0
87
88 ! iterate over all wire segments that make up the axis;
89 ! the number of wire segments is one less than number of points of the closed loop
90 DO i = 1, nvper * nv
91
92 ! filament geometry: from current point (R_i == xpts(:,i)) to previous point (R_f == xpts(:,i-1))
93 dvec = xpts(:,i+1)-xpts(:,i)
94 l = norm2(dvec)
95
96 ! loop over evaluation points
97 DO j = 1,nuv2
98 ! xpt == evaluation position
99 xpt(1) = rp(j) * cos1(j)
100 xpt(2) = rp(j) * sin1(j)
101 xpt(3) = zp(j)
102
103 ri_vec = xpt - xpts(:,i)
104 ri = norm2(ri_vec)
105 rf = norm2(xpt - xpts(:,i + 1))
106 ri_p_rf = ri + rf
107
108 ! 1.0e-7 == mu0/4 pi
109 bmag = 1.0e-7_dp * current * 2.0_dp * ri_p_rf / ( ri * rf * (ri_p_rf*ri_p_rf - l*l) )
110
111 ! cross product of L*hat(eps)==dvec with Ri_vec, scaled by Bmag
112 bx(j) = bx(j) + bmag * (dvec(2)*ri_vec(3) - dvec(3)*ri_vec(2))
113 by(j) = by(j) + bmag * (dvec(3)*ri_vec(1) - dvec(1)*ri_vec(3))
114 bz(j) = bz(j) + bmag * (dvec(1)*ri_vec(2) - dvec(2)*ri_vec(1))
115 end do
116
117 END DO
118
119 end if ! use_abscab_for_axis_current
120
121END SUBROUTINE belicu
subroutine belicu(torcur, bx, by, bz, cos1, sin1, rp, zp)
Magnetic field due to net toroidal current modeled by a filament along the magnetic axis.
Definition belicu.f90:15
real(rprec), dimension(:,:), allocatable xpts
Definition vacmod.f90:99
real(rprec), dimension(:), allocatable raxis_nestor
Definition vacmod.f90:75
real(rprec), dimension(:), allocatable zaxis_nestor
Definition vacmod.f90:76
real(rprec), dimension(:), allocatable bz
Definition vacmod.f90:96