V3FIT
othersums.f
1  SUBROUTINE othersums(irho)
2 c--
3 c calculates other1
4 c of integral of W(lambda) which is not dependant on lambda
5 c--
6 C-----------------------------------------------
7 C M o d u l e s
8 C-----------------------------------------------
9  USE parambs
10  USE vmec0
11  IMPLICIT NONE
12 C-----------------------------------------------
13 C D u m m y A r g u m e n t s
14 C-----------------------------------------------
15  INTEGER :: irho
16 C-----------------------------------------------
17 C L o c a l P a r a m e t e r s
18 C-----------------------------------------------
19  REAL(rprec), PARAMETER :: zero = 0, one = 1
20 C-----------------------------------------------
21 C L o c a l V a r i a b l e s
22 C-----------------------------------------------
23  INTEGER :: n, m
24  REAL(rprec) :: denom, qn
25 C-----------------------------------------------
26 C E x t e r n a l F u n c t i o n s
27 C-----------------------------------------------
28  REAL(rprec) , EXTERNAL :: sumit
29 C-----------------------------------------------
30 c
31 c- m - poloidal, n - toroidal
32 c
33  IF (isymm0 .ne. 0) THEN
34  other1(irho) = zero
35  RETURN
36  ENDIF
37 c
38 c- Form the "other" SUMs. The first USEs alpha1(m,n), calculated in WOFLAM,
39 c and d(m,n) from DENM.
40 c
41 c- Load rfmn with
42 c
43 c (m*R+n*periods*S)/(m-n*periods*q) *
44 c EXP(m*thetamax-n*zetahmax) * (1.5*alpha1(m,n)+d(m,n))
45 c
46 c- for only those harmonics that are going to be used in the sum.
47 c
48  qn = periods*qsafety(irho)*zetasign
49  DO m = -mbuse, mbuse
50  DO n = 0, nbuse
51  denom = m + n*qn
52  IF (n.ne.0 .or. m.ne.0) THEN
53  denom = denom/(denom**2 + (damp_bs*m)**2)
54  rfmn(m,n) = (m*capr(irho)+n*periods*caps(irho))*denom*(
55  1 cos(m*thetamax(irho)-n*zetahmax(irho))*real(1.5_dp*
56  2 alpha1mn(m,n)+dmn(m,n))-sin(m*thetamax(irho)-n*
57  3 zetahmax(irho))*aimag(1.5_dp*alpha1mn(m,n)+dmn(m,n)))
58  ELSE
59  rfmn(m,n) = zero
60  ENDIF
61  END DO
62  END DO
63 
64 c First SUM,
65 
66  other1(irho) = sumit(rfmn,mbuse,nbuse)
67 c
68 c- Then multiply by ALL the stuff out front.
69 c
70  other1(irho) = -other1(irho)*qsafety(irho)/ftrapped(irho)*(one +
71  1 aiogar(irho)/qsafety(irho))
72 
73 
74  END SUBROUTINE othersums