V3FIT
do_fft.f
1  SUBROUTINE do_fft(a11, answer_mn, trigsu, trigsv, ifaxu, ifaxv,
2  1 ntheta, nzeta, mbuse, nbuse)
3 C-----------------------------------------------
4 C M o d u l e s
5 C-----------------------------------------------
6  USE stel_kinds
7  IMPLICIT NONE
8 C-----------------------------------------------
9 C D u m m y A r g u m e n t s
10 C-----------------------------------------------
11  INTEGER ntheta, nzeta, mbuse, nbuse
12  INTEGER, DIMENSION(*) :: ifaxu, ifaxv
13  REAL(rprec), DIMENSION(ntheta + 2,nzeta) :: a11
14  REAL(rprec), DIMENSION(3*ntheta/2 + 1) :: trigsu
15  REAL(rprec), DIMENSION(2*nzeta) :: trigsv
16  complex(rprec), DIMENSION(-mbuse:mbuse,0:nbuse) :: answer_mn
17 C-----------------------------------------------
18 C L o c a l P a r a m e t e r s
19 C-----------------------------------------------
20  REAL(rprec), PARAMETER :: one = 1
21 C-----------------------------------------------
22 C L o c a l V a r i a b l e s
23 C-----------------------------------------------
24  INTEGER :: inc, jump, isign, jumpv, incv
25  REAL(rprec), DIMENSION(:), ALLOCATABLE :: work11
26  REAL(rprec) :: factor
27 C-----------------------------------------------
28 
29  ALLOCATE (work11(nzeta*(ntheta+2)))
30 c
31 c- Forward REAL to complex transform in the theta direction with INDEX n.
32 c i.e., integral of EXP(-i*n*theta) * f(theta,zetah).
33 c
34  inc = 1
35  jump = ntheta + 2
36  isign = -1
37 
38  CALL fft991(a11,work11,trigsu,ifaxu,inc,jump,ntheta,nzeta,isign)
39 
40 c
41 c- now forward transform in the zetah direction with INDEX m.
42 c i.e., integral of EXP(-i*m*zetah) * [theta transform of f(theta,zetah)]
43 c
44  jumpv = 1
45  incv = jump/2
46  CALL cfft99(a11,work11,trigsv,ifaxv,incv,jumpv,nzeta,incv,isign)
47 
48  DEALLOCATE (work11)
49 
50 c
51 c- Now reorganize and scale these to get the complex d(n,m)
52 c factor = 1 / (number of points used in the forward transform direction).
53 c because of (anti)symmetry, only nonnegative m values are needed. we also
54 c only fill to n = mbuse and m = nbuse since this is all that will be
55 c used in the sums over n and m.
56 c
57  factor = one/nzeta
58 c store a11 in answer_mn array
59  CALL reorganz (answer_mn, mbuse, nbuse, factor, a11, ntheta,
60  1 nzeta)
61 
62  END SUBROUTINE do_fft