VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
scalpot.f90
Go to the documentation of this file.
1
3
13SUBROUTINE scalpot(bvec, amatrix, wint, ivacskip, lasym, m_map, n_map)
14 USE vacmod, vm_amatrix => amatrix
15
16 use dbgout
18
19 IMPLICIT NONE
20
21 INTEGER, INTENT(in) :: ivacskip
22 REAL(rprec), INTENT(out) :: bvec(mnpd2), amatrix(mnpd2*mnpd2), m_map(mnpd2), n_map(mnpd2)
23 REAL(rprec), dimension(nuv2), INTENT(in) :: wint
24 logical, intent(in) :: lasym
25
26 INTEGER :: ip, istat
27
28 IF (.not.ALLOCATED(amatsav)) then
29 stop 'AMATSAV not allocated in scalpot'
30 end if
31
32 ! COMPUTE TRANFORM OF ANALYTIC SOURCE AND KERNEL.
33 ! ON EXIT:
34 ! BVEC CONTAINS THE TRANSFORM OF THE ANALYTIC SOURCE AND
35 ! GRPMN CONTAINS THE TRANSFORM OF THE NORMAL DERIVATIVE OF THE GREENS FUNCTION [PKM, EQ.(2.15)]
36 ! GReen's function Primed (normal derivative...) and Fourier-transformed to MN mode numbers --> "GR P MN"
37 CALL analyt (grpmn, bvec, ivacskip, lasym, m_map, n_map, grpmn_m_map_wrt, grpmn_n_map_wrt)
38
39 IF (ivacskip .ne. 0) THEN
40 ! FOR ivacskip != 0, USE PREVIOUSLY COMPUTED bvecsav FOR SPEED
41
42 ! Here, bvecsav contains the previous non-singular contribution to the "final" bvec from fouri.
43 ! For ivacskip != 0, this contribution is used from the cache in bvecsav.
44 bvec = bvec + bvecsav
45 ELSE
46 ! Here, bvecsav stores the singular part of bvec from analyt
47 ! to be subtracted from the "final" bvec computed below by fouri
48 bvecsav = bvec
49
50 ! COMPUTE SURFACE INTEGRALS OF SOURCE AND GREENS FUNCTION NEEDED
51 ! FOR SPECTRAL DECOMPOSITION OF POTENTIAL INTEGRAL EQUATION
52 ! NOTE: SOURCE IS THE RHS OF EQ.(3.2), KERNEL IS THE LHS OF EQ (3.2).
53 ! IP IS THE INDEX OF THE PRIMED VARIABLE MESH.
54 gstore = 0
55 DO ip = 1, nuv2
56
57 ! COMPUTE DIFFERENCE BETWEEN THE EXACT AND ANALYTIC GREENS FUNCTION AND GRADIENT
58 ! [FIRST TERMS IN EQ.(2.14, 2.16)].
59 CALL greenf (green(1,ip), greenp(1,ip), ip)
60
61! ! debugging: need to fix greenf for Tokamak first...
62! stop
63
64 ! PERFORM INTEGRAL (SUM) OVER PRIMED MESH OF NON-SINGULAR SOURCE TERM
65 ! [(h-hsing)(u,v,u',v') == bexni(ip)*green(u,v; ip) in Eq. 2.16]
66 ! AND STORE IT - FOR UNPRIMED MESH VALUES - IN GSTORE
67 gstore = gstore + bexni(ip)*green(:,ip)
68 END DO
69
70 if (open_dbg_context("vac1n_greenf", num_eqsolve_retries)) then
71
72 call add_real_4d("green", nv, nu, nv, nu3, green)
73 call add_real_4d("greenp", nv, nu, nv, nu3, greenp)
74
75 call add_real_2d("gstore", nv, nu, gstore)
76
77 call close_dbg_out()
78 end if
79
80 ! PERFORM FOURIER INTEGRAL OF GRADIENT KERNEL (GREENP) OVER THE UNPRIMED MESH
81 ! AND STORE IN GRPMN (NOTE THAT GRPMN IS ADDED TO THE ANALYTIC PIECE IN EQ. 2.14,
82 ! - COMPUTED IN ANALYT - WHICH HAS THE APPROPRIATE SIN, COS FACTORS ALREADY)
83 CALL fourp (grpmn, greenp)
84
85 ! COMPUTE FOURIER INTEGRAL OF GRADIENT (GRPMN) OVER PRIMED MESH IN EQ. 2.14
86 ! AND SOURCE (GSTORE) OVER UNPRIMED MESH IN EQ. 2.16
87 CALL fouri (grpmn, gstore, amatrix, amatsav, bvec, wint, lasym)
88
89 ! debugging: focus on Fourier transforms in fouri for now
90 ! return
91
92 ! SAVE NON-SINGULAR CONTRIBUTION TO BVEC (IN BVECSAV)
93 bvecsav(:mnpd2) = bvec - bvecsav(:mnpd2)
94
95 ENDIF
96
97 amatrix = amatsav
98
99END SUBROUTINE scalpot
subroutine analyt(grpmn, bvec, ivacskip, lasym, m_map, n_map, grpmn_m_map, grpmn_n_map)
Compute the analytical-and-numerical 4D Fourier integrals over the equivalently-singular functions.
Definition analyt.f90:15
subroutine fouri(grpmn, gsource, amatrix, amatsq, bvec, wint, lasym)
Compute Fourier integrals and build amatrix.
Definition fouri.f90:14
subroutine fourp(grpmn, grp)
Perform Fourier integrals of Green's function kernel.
Definition fourp.f90:9
subroutine greenf(delgr, delgrp, ip)
Compute the regularized evaluation of the Green's function and the source term.
Definition greenf.f90:10
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 bvecsav
Definition vacmod.f90:34
real(rprec), dimension(:,:), allocatable greenp
Definition vacmod.f90:108
real(rprec), dimension(:), allocatable grpmn_m_map_wrt
Definition vacmod.f90:103
real(rprec), dimension(:), allocatable bexni
Definition vacmod.f90:37
real(rprec), dimension(:), allocatable amatsav
Definition vacmod.f90:35
real(rprec), dimension(:), allocatable grpmn
Definition vacmod.f90:102
real(rprec), dimension(:), allocatable gstore
Definition vacmod.f90:106
real(rprec), dimension(:), allocatable grpmn_n_map_wrt
Definition vacmod.f90:104
real(rprec), dimension(:,:), allocatable green
Definition vacmod.f90:107
real(rprec), dimension(:), allocatable amatrix
Definition vacmod.f90:83
integer num_eqsolve_retries
subroutine scalpot(bvec, amatrix, wint, ivacskip, lasym, m_map, n_map)
Compute all required terms for solving for the scalar magnetic potential.
Definition scalpot.f90:14