VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
bextern.f90
Go to the documentation of this file.
1
3
8SUBROUTINE bextern(plascur, wint)
9 USE vacmod
10 USE mgrid_mod, ONLY: bvac
11
12 use dbgout
14
15 IMPLICIT NONE
16
17 REAL(rprec), INTENT(in) :: plascur
18 REAL(rprec), DIMENSION(nuv2), INTENT(in) :: wint
19
20 INTEGER :: i
21 logical :: dbgout_active
22
23 ! exterior Neumann problem
24
25 IF (.not.ALLOCATED(bvac)) stop 'BVAC unallocated in bextern'
26
27 ! THIS ROUTINE COMPUTES THE B DOT DS ARISING FROM EXTERNAL COILS AND INTERNAL PLASMA CURRENT
28 ! NOTE THAT BEXN = - BEX * DS IS THE EFFECTIVE SOURCE TERM
29 !
30 ! COMPUTE B FROM COILS ON THE PLASMA BOUNDARY
31 ! This sets brad, bphi and bz to the interpolated field from the mgrid.
32 CALL becoil(r1b, z1b, bvac(1,1), bvac(1,2), bvac(1,3))
33
34 dbgout_active = open_dbg_context("vac1n_bextern", num_eqsolve_retries)
35 if (dbgout_active) then
36
37 ! these are only from the mgrid at this point
38 call add_real_2d("mgrid_brad", nv, nu3, brad)
39 call add_real_2d("mgrid_bphi", nv, nu3, bphi)
40 call add_real_2d("mgrid_bz", nv, nu3, bz)
41
42 ! This should be in Amperes.
43 call add_real("axis_current", plascur/mu0)
44
45 end if ! dbgout_active
46
47 ! COMPUTE B (ON PLASMA BOUNDARY) FROM NET TOROIDAL PLASMA CURRENT
48 ! THE NET CURRENT IS MODELLED AS A WIRE AT THE MAGNETIC AXIS, AND THE
49 ! BIOT-SAVART LAW IS USED TO COMPUTE THE FIELD AT THE PLASMA SURFACE
50 !
51 ! USE BEXU, BEXV, BEXN AS TEMPORARY STORAGE FOR BX, BY, BZ
52 ! --> add to interpolated field from mgrid
53 CALL belicu (plascur, bexu, bexv, bexn, cosuv, sinuv, r1b, z1b)
54 DO i = 1, nuv2
55 brad(i) = brad(i) + bexu(i)*cosuv(i) + bexv(i)*sinuv(i)
56 bphi(i) = bphi(i) - bexu(i)*sinuv(i) + bexv(i)*cosuv(i)
57 bz(i) = bz(i) + bexn(i)
58 END DO
59
60 ! COMPUTE COVARIANT COMPONENTS OF EXTERNAL FIELD: BEXU = B0 dot dx/du,
61 ! BEXV = B0 dot dx/dv. HERE, BEXN = -B0*SURF_NORM CORRESPONDS TO THE
62 ! "exterior Neumann problem" convention of PKM (sign flipped as noted in PKM)
63 ! THUS, THE UNIT NORMAL SHOULD POINT INTO THE PLASMA (OUTWARD FROM VACUUM),
64 ! WHICH IT DOES FOR A NEGATIVE JACOBIAN (SIGNGS) SYSTEM
65 DO i = 1, nuv2
66 bexu(i) = rub(i)*brad(i) + zub(i)*bz(i)
67 bexv(i) = rvb(i)*brad(i) + zvb(i)*bz(i) + r1b(i)*bphi(i)
68 bexn(i) =-(brad(i)*snr(i) + bphi(i)*snv(i) + bz(i)*snz(i))
69 END DO
70
71 ! COMPUTE NORMALIZED [(2*pi)**2], READY-TO-INTEGRATE (WINT FACTOR) SOURCE TERM
72 ! NOTE: BEXN == NP*F = -B0 dot [Xu cross Xv] NP (see PKM, Eq. 2.13)
73 bexni(:nuv2) = wint(:nuv2)*bexn(:nuv2)*pi2*pi2
74
75 if (dbgout_active) then
76
77 ! axis geometry used in belicu
78 call add_real_2d("xpts_axis", 3, nvper * nv + 1, xpts)
79
80 ! these are now mgrid + axis-current
81 call add_real_2d("brad", nv, nu3, brad)
82 call add_real_2d("bphi", nv, nu3, bphi)
83 call add_real_2d("bz", nv, nu3, bz)
84
85 call add_real_2d("bexu", nv, nu3, bexu)
86 call add_real_2d("bexv", nv, nu3, bexv)
87 call add_real_2d("bexn", nv, nu3, bexn)
88
89 call add_real_2d("bexni", nv, nu3, bexni(:nuv2))
90
91 call close_dbg_out()
92 end if
93
94END SUBROUTINE bextern
subroutine becoil(rad, zee, brvac, bpvac, bzvac)
Compute the cylindrical components of the magnetic field due to external coils. by bi-linear interpol...
Definition becoil.f90:14
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
subroutine bextern(plascur, wint)
Compute the total magnetic field due to external coils and the net toroidal plasma current.
Definition bextern.f90:9
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), dimension(:,:), allocatable, target bvac
Definition mgrid_mod.f:86
real(rprec), dimension(:), allocatable zvb
Definition vacmod.f90:50
real(rprec), dimension(:), allocatable r1b
Definition vacmod.f90:45
real(rprec), dimension(:), allocatable zub
Definition vacmod.f90:49
real(rprec), dimension(:), allocatable bphi
Definition vacmod.f90:95
real(rprec), dimension(:), allocatable z1b
Definition vacmod.f90:48
real(rprec), dimension(:), allocatable bexni
Definition vacmod.f90:37
real(rprec), dimension(:), allocatable snz
Definition vacmod.f90:62
real(rprec), dimension(:,:), allocatable xpts
Definition vacmod.f90:99
real(rprec), dimension(:), allocatable snr
Definition vacmod.f90:60
real(rprec), dimension(:), allocatable rub
Definition vacmod.f90:46
real(rprec), dimension(:), allocatable rvb
Definition vacmod.f90:47
real(rprec), dimension(:), allocatable snv
Definition vacmod.f90:61
real(rprec), dimension(:), allocatable bexv
Definition vacmod.f90:53
real(rprec) pi2
Definition vacmod.f90:17
real(rprec), dimension(:), allocatable bz
Definition vacmod.f90:96
real(rprec), dimension(:), allocatable brad
Definition vacmod.f90:94
real(rprec), dimension(:), allocatable bexu
Definition vacmod.f90:52
real(rprec), dimension(:), allocatable bexn
Definition vacmod.f90:54
integer num_eqsolve_retries