VMEC 8.52
3D Equilibrium solver with nested flux surfaces.
Loading...
Searching...
No Matches
analysum2.f90
Go to the documentation of this file.
1
3
17SUBROUTINE analysum2(grpmn, bvec, m, n, l, ivacskip, lasym, m_map, n_map, &
18 grpmn_m_map, grpmn_n_map)
19 USE vacmod, vm_grpmn => grpmn
20 IMPLICIT NONE
21
22 INTEGER, INTENT(in) :: m, n, l, ivacskip
23 REAL(rprec), INTENT(inout) :: grpmn(0:mf,-nf:nf,nuv2,ndim)
24 REAL(rprec), INTENT(inout) :: bvec(0:mf,-nf:nf,ndim)
25 real(rprec), intent(inout) :: m_map(0:mf,-nf:nf)
26 real(rprec), intent(inout) :: n_map(0:mf,-nf:nf)
27 real(rprec), intent(inout) :: grpmn_m_map(0:mf,-nf:nf,nuv2)
28 real(rprec), intent(inout) :: grpmn_n_map(0:mf,-nf:nf,nuv2)
29 logical, intent(in) :: lasym
30
31 INTEGER :: i
32 REAL(rprec) :: sinp, sinm, cosp, cosm, temp
33
34 IF (n .LT. 0) stop 'error calling analysum2!'
35
36 m_map(m, n) = m
37 m_map(m, -n) = m
38
39 n_map(m, n) = n
40 n_map(m, -n) = -n
41
42! if (cmns(l,m,n) .eq. zero) then
43! ! no need to compute zeros...
44! return
45! end if
46
47 DO i = 1,nuv2
48
49 grpmn_m_map(m, n, i) = m
50 grpmn_m_map(m,-n, i) = m
51
52 grpmn_n_map(m, n, i) = n
53 grpmn_n_map(m,-n, i) = -n
54
55 sinp = sinu1(i,m)*cosv1(i,n) * cmns(l,m,n)
56 temp = -cosu1(i,m)*sinv1(i,n) * cmns(l,m,n)
57
58 ! SIN(mu + |n|v) * cmns (l,m,|n|)
59 sinm = sinp - temp
60
61 ! SIN(mu - |n|v) * cmns (l,m,|n|)
62 sinp = sinp + temp
63
64 bvec(m, n, 1) = bvec(m, n, 1) + tlp(i)*bexni(i)*sinp
65 bvec(m,-n, 1) = bvec(m,-n, 1) + tlm(i)*bexni(i)*sinm
66
67 IF (ivacskip .EQ. 0) THEN
68 grpmn(m, n,i,1) = grpmn(m, n,i,1) + slp(i) *sinp
69 grpmn(m,-n,i,1) = grpmn(m,-n,i,1) + slm(i) *sinm
70 END IF
71
72 IF (lasym) THEN
73 cosp = cosu1(i,m)*cosv1(i,n) * cmns(l,m,n)
74 temp = sinu1(i,m)*sinv1(i,n) * cmns(l,m,n)
75
76 ! COS(mu + |n|v) * cmns (l,m,|n|)
77 cosm = cosp - temp
78
79 ! COS(mu - |n|v) * cmns (l,m,|n|)
80 cosp = cosp + temp
81
82 bvec(m, n,2) = bvec(m, n,2) + tlp(i)*bexni(i)*cosp
83 bvec(m,-n,2) = bvec(m,-n,2) + tlm(i)*bexni(i)*cosm
84
85 IF (ivacskip .EQ. 0) THEN
86 grpmn(m, n,i,2) = grpmn(m, n,i,2) + slp(i)*cosp
87 grpmn(m,-n,i,2) = grpmn(m,-n,i,2) + slm(i)*cosm
88 END IF
89 END IF
90 END DO
91
92END SUBROUTINE analysum2
subroutine analysum2(grpmn, bvec, m, n, l, ivacskip, lasym, m_map, n_map, grpmn_m_map, grpmn_n_map)
Compute the (m>0 and n>0) part of the DFT of the analytical Fourier transforms of the equivalently-si...
Definition analysum2.f90:19
real(rprec), dimension(:), allocatable tlp
Definition vacmod.f90:119
real(rprec), dimension(:), allocatable bexni
Definition vacmod.f90:37
real(rprec), dimension(:), allocatable grpmn
Definition vacmod.f90:102
real(rprec), dimension(:), allocatable slp
Definition vacmod.f90:129
real(rprec), dimension(:), allocatable tlm
Definition vacmod.f90:122
real(rprec), dimension(:), allocatable slm
Definition vacmod.f90:128