NAME

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

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

F95 INTERFACE

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

C INTERFACE

#include <sunperf.h>

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

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


PURPOSE

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

                   N1-1  N2-1

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

                   j1=0  j2=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

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

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

In complex-to-real transform of length N1, the (N1/2+1) complex input data points stored are the positive-frequency half of the spectrum of the Discrete Fourier Transform. The other half can be obtained through complex conjugation and therefore is not stored.


ARGUMENTS


SEE ALSO

fft


CAUTIONS

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