1 SUBROUTINE spectrum_par(rmn, zmn)
2 USE parallel_include_module
4 USE vmec_params,
ONLY: mscale, nscale, ntmax, rss, zcs, rsc, zcc
5 USE totzsp_mod,
ONLY: convert_sym, convert_asym
6 USE totzsp_mod,
ONLY: convert_sym_par, convert_asym_par
12 REAL(dp),
DIMENSION(0:ntor,0:mpol1,ns,ntmax),
13 1
INTENT(inout) :: rmn, zmn
17 INTEGER,
PARAMETER :: m1 = 1
18 INTEGER :: js, ntype, n, m, nsmin, nsmax
19 REAL(dp),
DIMENSION(ns) :: t1, dnumer, denom
26 nsmin=max(2,tlglob); nsmax=min(t1rglob,ns)
29 CALL convert_sym_par(rmn(:,m1,:,rss), zmn(:,m1,:,zcs),
33 CALL convert_asym_par(rmn(:,m1,:,rsc), zmn(:,m1,:,zcc),
37 dnumer(nsmin:nsmax) = zero
38 denom(nsmin:nsmax) = zero
42 scale = (mscale(m)*nscale(n))**2
44 t1(js) = (rmn(n,m,js,ntype)**2 +
45 & zmn(n,m,js,ntype)**2)*scale
47 dnumer(nsmin:nsmax) = dnumer(nsmin:nsmax)
48 & + t1(nsmin:nsmax)*xmpq(m,3)
49 denom(nsmin:nsmax) = denom(nsmin:nsmax)
50 & + t1(nsmin:nsmax)*xmpq(m,2)
55 specw(nsmin:nsmax) = dnumer(nsmin:nsmax)/denom(nsmin:nsmax)
57 END SUBROUTINE spectrum_par
59 SUBROUTINE spectrum(rmn, zmn)
61 USE vmec_params,
ONLY: mscale, nscale, ntmax, rss, zcs, rsc, zcc
62 USE totzsp_mod,
ONLY: convert_sym, convert_asym
63 USE parallel_include_module
68 REAL(dp),
DIMENSION(ns,0:ntor,0:mpol1,ntmax),
69 1
INTENT(inout) :: rmn, zmn
73 INTEGER,
PARAMETER :: m1 = 1
74 INTEGER :: js, ntype, n, m, nsmin, nsmax
75 REAL(dp),
DIMENSION(ns) :: t1, dnumer, denom
86 CALL convert_sym(rmn(:,:,m1,rss), zmn(:,:,m1,zcs))
89 CALL convert_asym(rmn(:,:,m1,rsc), zmn(:,:,m1,zcc))
97 scale = (mscale(m)*nscale(n))**2
99 t1(js) =(rmn(js,n,m,ntype)**2 +
100 & zmn(js,n,m,ntype)**2)*scale
102 dnumer(2:ns) = dnumer(2:ns) + t1(2:ns)*xmpq(m,3)
103 denom(2:ns) = denom(2:ns) + t1(2:ns)*xmpq(m,2)
108 specw(2:ns) = dnumer(2:ns)/denom(2:ns)
110 END SUBROUTINE spectrum