NAME

zfftz2 - initialize the trigonometric weight and factor tables or compute the two-dimensional Fast Fourier Transform (forward or inverse) of a two-dimensional double complex array. =head1 SYNOPSIS

  SUBROUTINE ZFFTZ2( IOPT, N1, N2, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, 
 *      WORK, LWORK, IERR)
  DOUBLE COMPLEX X(LDX,*), Y(LDY,*)
  INTEGER IOPT, N1, N2, LDX, LDY, LWORK, IERR
  INTEGER IFAC(*)
  DOUBLE PRECISION SCALE
  DOUBLE PRECISION TRIGS(*), WORK(*)
  SUBROUTINE ZFFTZ2_64( IOPT, N1, N2, SCALE, X, LDX, Y, LDY, TRIGS, 
 *      IFAC, WORK, LWORK, IERR)
  DOUBLE COMPLEX X(LDX,*), Y(LDY,*)
  INTEGER*8 IOPT, N1, N2, LDX, LDY, LWORK, IERR
  INTEGER*8 IFAC(*)
  DOUBLE PRECISION SCALE
  DOUBLE PRECISION TRIGS(*), WORK(*)

F95 INTERFACE

  SUBROUTINE FFT2( IOPT, [N1], [N2], [SCALE], X, [LDX], Y, [LDY], 
 *       TRIGS, IFAC, WORK, [LWORK], IERR)
  COMPLEX(8), DIMENSION(:,:) :: X, Y
  INTEGER :: IOPT, N1, N2, LDX, LDY, LWORK, IERR
  INTEGER, DIMENSION(:) :: IFAC
  REAL(8) :: SCALE
  REAL(8), DIMENSION(:) :: TRIGS, WORK
  SUBROUTINE FFT2_64( IOPT, [N1], [N2], [SCALE], X, [LDX], Y, [LDY], 
 *       TRIGS, IFAC, WORK, [LWORK], IERR)
  COMPLEX(8), DIMENSION(:,:) :: X, Y
  INTEGER(8) :: IOPT, N1, N2, LDX, LDY, LWORK, IERR
  INTEGER(8), DIMENSION(:) :: IFAC
  REAL(8) :: SCALE
  REAL(8), DIMENSION(:) :: TRIGS, WORK

C INTERFACE

#include <sunperf.h>

void zfftz2(int iopt, int n1, int n2, double scale, doublecomplex *x, int ldx, doublecomplex *y, int ldy, double *trigs, int *ifac, double *work, int lwork, int *ierr);

void zfftz2_64(long iopt, long n1, long n2, double scale, doublecomplex *x, long ldx, doublecomplex *y, long ldy, double *trigs, long *ifac, double *work, long lwork, long *ierr);


PURPOSE

zfftz2 initializes the trigonometric weight and factor tables or computes the two-dimensional Fast Fourier Transform (forward or inverse) of a two-dimensional double complex array. In computing the two-dimensional FFT, one-dimensional FFTs are computed along the columns of the input array. One-dimensional FFTs are then computed along the rows of the intermediate results. .Ve

                   N2-1  N1-1

Y(k1,k2) = scale * SUM SUM W2*W1*X(j1,j2)

                   j2=0  j1=0
.Ve

where

k1 ranges from 0 to N1-1 and k2 ranges from 0 to N2-1

i = sqrt(-1)

isign = 1 for inverse transform or -1 for forward transform

W1 = exp(isign*i*j1*k1*2*pi/N1)

W2 = exp(isign*i*j2*k2*2*pi/N2)


ARGUMENTS


SEE ALSO

fft


CAUTIONS

On exit, entire output array Y(1:LDY, 1:N2) is overwritten.