NAME

zfftdm - initialize the trigonometric weight and factor tables or compute the one-dimensional inverse Fast Fourier Transform of a set of double complex data sequences stored in a two-dimensional array. =head1 SYNOPSIS

  SUBROUTINE ZFFTDM( IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, 
 *      WORK, LWORK, IERR)
  DOUBLE COMPLEX X(LDX,*)
  INTEGER IOPT, M, N, LDX, LDY, LWORK, IERR
  INTEGER IFAC(*)
  DOUBLE PRECISION SCALE
  DOUBLE PRECISION Y(LDY,*), TRIGS(*), WORK(*)
  SUBROUTINE ZFFTDM_64( IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, 
 *      IFAC, WORK, LWORK, IERR)
  DOUBLE COMPLEX X(LDX,*)
  INTEGER*8 IOPT, M, N, LDX, LDY, LWORK, IERR
  INTEGER*8 IFAC(*)
  DOUBLE PRECISION SCALE
  DOUBLE PRECISION Y(LDY,*), TRIGS(*), WORK(*)

F95 INTERFACE

  SUBROUTINE FFTM( IOPT, M, [N], [SCALE], X, [LDX], Y, [LDY], TRIGS, 
 *       IFAC, WORK, [LWORK], IERR)
  COMPLEX(8), DIMENSION(:,:) :: X
  INTEGER :: IOPT, M, N, LDX, LDY, LWORK, IERR
  INTEGER, DIMENSION(:) :: IFAC
  REAL(8) :: SCALE
  REAL(8), DIMENSION(:) :: TRIGS, WORK
  REAL(8), DIMENSION(:,:) :: Y
  SUBROUTINE FFTM_64( IOPT, M, [N], [SCALE], X, [LDX], Y, [LDY], 
 *       TRIGS, IFAC, WORK, [LWORK], IERR)
  COMPLEX(8), DIMENSION(:,:) :: X
  INTEGER(8) :: IOPT, M, N, 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 zfftdm(int iopt, int m, int n, double scale, doublecomplex *x, int ldx, double *y, int ldy, double *trigs, int *ifac, double *work, int lwork, int *ierr);

void zfftdm_64(long iopt, long m, long n, double scale, doublecomplex *x, long ldx, double *y, long ldy, double *trigs, long *ifac, double *work, long lwork, long *ierr);


PURPOSE

zfftdm initializes the trigonometric weight and factor tables or computes the one-dimensional inverse Fast Fourier Transform of a set of double complex data sequences stored in a two-dimensional array: .Ve

                 N1-1

Y(k,l) = scale * SUM W*X(j,l)

                 j=0
.Ve

where

k ranges from 0 to N1-1 and l ranges from 0 to N2-1

i = sqrt(-1)

isign = 1 for inverse transform

W = exp(isign*i*j*k*2*pi/N1)

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. Furthermore, due to symmetries the imaginary of the component of X(0,0:N2-1) and X(N1/2,0:N2-1) (if N1 is even in the latter) is assumed to be zero and is not referenced.


ARGUMENTS


SEE ALSO

fft