NAME

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

  SUBROUTINE CFFTS2( IOPT, N1, N2, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, 
 *      WORK, LWORK, IERR)
  COMPLEX X(LDX,*)
  INTEGER IOPT, N1, N2, LDX, LDY, LWORK, IERR
  INTEGER IFAC(*)
  REAL SCALE
  REAL Y(LDY,*), TRIGS(*), WORK(*)
  SUBROUTINE CFFTS2_64( IOPT, N1, N2, SCALE, X, LDX, Y, LDY, TRIGS, 
 *      IFAC, WORK, LWORK, IERR)
  COMPLEX X(LDX,*)
  INTEGER*8 IOPT, N1, N2, LDX, LDY, LWORK, IERR
  INTEGER*8 IFAC(*)
  REAL SCALE
  REAL Y(LDY,*), TRIGS(*), WORK(*)

F95 INTERFACE

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

C INTERFACE

#include <sunperf.h>

void cffts2(int iopt, int n1, int n2, float scale, complex *x, int ldx, float *y, int ldy, float *trigs, int *ifac, float *work, int lwork, int *ierr);

void cffts2_64(long iopt, long n1, long n2, float scale, complex *x, long ldx, float *y, long ldy, float *trigs, long *ifac, float *work, long lwork, long *ierr);


PURPOSE

cffts2 initializes the trigonometric weight and factor tables or computes the two-dimensional inverse Fast Fourier Transform of a two-dimensional 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 array Y(1:LDY, 1:N2) is overwritten.