Previous Next Contents Generated Index Doc Set Home



Initialize Three-Dimensional Fourier Transform or Synthesis

The subroutines described in this section initialize the array xWSAVE, which is used in both xFFT3F and xFFT3B.

Calling Sequence

CALL RFFT3I
(M, N, K, RWSAVE)
CALL DFFT3I
(M, N, K, DWSAVE)
CALL CFFT3I
(M, N, K, CWSAVE)
CALL ZFFT3I
(M, N, K, ZWSAVE)






void rfft3i
(int m, int n, int k, float *wsave)
void dfft3i
(int m, int n, int k, double *wsave)
void cfft3i
(int m, int n, int k, complex *wsave)
void zfft3i
(int m, int n, int k, doublecomplex *wsave)

Arguments

M

Number of rows to be transformed. M 0.

N

Number of columns to be transformed. N 0.

K

Number of planes to be transformed. K 0.

xWSAVE

On entry, an array with dimension of at least (M + N + MAX(M,N,K) + 45). The same work array can be used for both xFFT3F and xFFT3B as long as M, N, and K remain unchanged. Different xWSAVE arrays are required for different values of M, N, or K. This initialization does not have to be repeated between calls to xFFT3F or xFFT3B as long as M, N, K, and xWSAVE remain unchanged, thus subsequent transforms can be obtained faster than the first.

Sample Program




      PROGRAM TEST
      IMPLICIT NONE
C
      INTEGER           LWORK, M, N, K
      PARAMETER        (K = 2)
      PARAMETER        (M = 2)
      PARAMETER        (N = 4)
      PARAMETER        (LWORK = 4 * (M + N + N) + 45)
C
      INTEGER           I, J, L
      REAL              PI, WSAVE(LWORK)
      REAL              X, Y
      COMPLEX           C(M,N,K)
C
      EXTERNAL          CFFT3B, CFFT3F, CFFT3I
      INTRINSIC         ACOS, CMPLX, COS, SIN
C
C     Initialize the array C to a complex sequence.
C
      PI = ACOS (-1.0)
      DO 120, L = 1, K
        DO 110, J = 1, N
          DO 100, I = 1, M
            X = SIN ((I - 1.0) * 2.0 * PI / N)
            Y = COS ((J - 1.0) * 2.0 * PI / M)
            C(I,J,L) = CMPLX (X, Y)
  100     CONTINUE
  110   CONTINUE
  120 CONTINUE
C
      PRINT 1000
      DO 210, L = 1, K
        PRINT 1010, L
        DO 200, I = 1, M
          PRINT 1020, (C(I,J,L), J = 1, N)
  200   CONTINUE
  210 CONTINUE
      CALL CFFT3I (M, N, K, WSAVE)
      CALL CFFT3F (M, N, K, C, M, N, WSAVE, LWORK)
      PRINT 1030
      DO 310, L = 1, K
        PRINT 1010, L
        DO 300, I = 1, M
          PRINT 1020, (C(I,J,L), J = 1, N)
  300   CONTINUE
  310 CONTINUE
      CALL CFFT3B (M, N, K, C, M, N, WSAVE, LWORK)
      PRINT 1040
      DO 410, L = 1, K
        PRINT 1010, L
        DO 400, I = 1, M
          PRINT 1020, (C(I,J,L), J = 1, N)
  400   CONTINUE
  410 CONTINUE
C
 1000 FORMAT (1X, 'Original Sequences:')
 1010 FORMAT (1X, '  Plane', I2)
 1020 FORMAT (5X, 100(F5.1' +',F5.1,'i  '))
 1030 FORMAT (/1X, 'Transformed Sequences:')
 1040 FORMAT (/1X, 'Recovered Sequences:')
C
      END



Sample Output

 
 Original Sequences:
   Plane 1
       0.0 +  1.0i    0.0 + -1.0i    0.0 +  1.0i    0.0 + -1.0i  
       1.0 +  1.0i    1.0 + -1.0i    1.0 +  1.0i    1.0 + -1.0i  
   Plane 2
       0.0 +  1.0i    0.0 + -1.0i    0.0 +  1.0i    0.0 + -1.0i  
       1.0 +  1.0i    1.0 + -1.0i    1.0 +  1.0i    1.0 + -1.0i  



 Transformed Sequences:
   Plane 1
       8.0 +  0.0i    0.0 +  0.0i    0.0 + 16.0i    0.0 +  0.0i  
      -8.0 +  0.0i    0.0 +  0.0i    0.0 +  0.0i    0.0 +  0.0i  
   Plane 2
       0.0 +  0.0i    0.0 +  0.0i    0.0 +  0.0i    0.0 +  0.0i  
       0.0 +  0.0i    0.0 +  0.0i    0.0 +  0.0i    0.0 +  0.0i  



 Recovered Sequences:
   Plane 1
       0.0 + 16.0i    0.0 +-16.0i    0.0 + 16.0i    0.0 +-16.0i  
      16.0 + 16.0i   16.0 +-16.0i   16.0 + 16.0i   16.0 +-16.0i  
   Plane 2
       0.0 + 16.0i    0.0 +-16.0i    0.0 + 16.0i    0.0 +-16.0i  
      16.0 + 16.0i   16.0 +-16.0i   16.0 + 16.0i   16.0 +-16.0i  






Previous Next Contents Generated Index Doc Set Home