Contents


NAME

     zfft3b - compute a periodic sequence from its Fourier  coef-
     ficients.  The FFT operations are unnormalized, so a call of
     ZFFT3F followed by a call of ZFFT3B will multiply the  input
     sequence by M*N*K.

SYNOPSIS

     SUBROUTINE ZFFT3B(M, N, K, A, LDA, LD2A, WORK, LWORK)

     DOUBLE COMPLEX A(LDA,LD2A,*)
     INTEGER M, N, K, LDA, LD2A, LWORK
     DOUBLE PRECISION WORK(*)

     SUBROUTINE ZFFT3B_64(M, N, K, A, LDA, LD2A, WORK, LWORK)

     DOUBLE COMPLEX A(LDA,LD2A,*)
     INTEGER*8 M, N, K, LDA, LD2A, LWORK
     DOUBLE PRECISION WORK(*)

  F95 INTERFACE
     SUBROUTINE FFT3B([M], [N], [K], A, [LDA], LD2A, WORK, LWORK)

     COMPLEX(8), DIMENSION(:,:,:) :: A
     INTEGER :: M, N, K, LDA, LD2A, LWORK
     REAL(8), DIMENSION(:) :: WORK

     SUBROUTINE FFT3B_64([M], [N], [K], A, [LDA], LD2A, WORK, LWORK)

     COMPLEX(8), DIMENSION(:,:,:) :: A
     INTEGER(8) :: M, N, K, LDA, LD2A, LWORK
     REAL(8), DIMENSION(:) :: WORK

  C INTERFACE
     #include <sunperf.h>

     void zfft3b(int m, int n, int k, doublecomplex *a, int  lda,
               int ld2a, double *work, int lwork);

     void zfft3b_64(long m, long n,  long  k,  doublecomplex  *a,
               long lda, long ld2a, double *work, long lwork);

ARGUMENTS

     M (input) Number of rows to be transformed.   These  subrou-
               tines  are  most  efficient when M is a product of
               small primes.  M >= 0.
     N (input) Number of columns to be transformed.   These  sub-
               routines are most efficient when N is a product of
               small primes.  N >= 0.

     K (input) Number of planes to be transformed.  These subrou-
               tines  are  most  efficient when K is a product of
               small primes.  K >= 0.

     A (input/output)
               On entry, a three-dimensional array  A(LDA,LD2A,K)
               that contains the sequences to be transformed.

     LDA (input)
               Leading dimension of the array containing the data
               to be transformed.  LDA >= M.

     LD2A (input)
               Second dimension of the array containing the  data
               to be transformed.  LD2A >= N.

     WORK (input)
               On input, workspace WORK must have  been  initial-
               ized by ZFFT3I.

     LWORK (input)
               The dimension of the array WORK.  LWORK >= (4*(M +
               N + K) + 45).