NAME

zfftd - initialize the trigonometric weight and factor tables or compute the inverse Fast Fourier Transform of a double complex sequence. =head1 SYNOPSIS

  SUBROUTINE ZFFTD( IOPT, N, SCALE, X, Y, TRIGS, IFAC, WORK, LWORK, 
 *      IERR)
  DOUBLE COMPLEX X(*)
  INTEGER IOPT, N, LWORK, IERR
  INTEGER IFAC(*)
  DOUBLE PRECISION SCALE
  DOUBLE PRECISION Y(*), TRIGS(*), WORK(*)
  SUBROUTINE ZFFTD_64( IOPT, N, SCALE, X, Y, TRIGS, IFAC, WORK, LWORK, 
 *      IERR)
  DOUBLE COMPLEX X(*)
  INTEGER*8 IOPT, N, LWORK, IERR
  INTEGER*8 IFAC(*)
  DOUBLE PRECISION SCALE
  DOUBLE PRECISION Y(*), TRIGS(*), WORK(*)

F95 INTERFACE

  SUBROUTINE FFT( IOPT, N, [SCALE], X, Y, TRIGS, IFAC, WORK, [LWORK], 
 *       IERR)
  COMPLEX(8), DIMENSION(:) :: X
  INTEGER :: IOPT, N, LWORK, IERR
  INTEGER, DIMENSION(:) :: IFAC
  REAL(8) :: SCALE
  REAL(8), DIMENSION(:) :: Y, TRIGS, WORK
  SUBROUTINE FFT_64( IOPT, N, [SCALE], X, Y, TRIGS, IFAC, WORK, [LWORK], 
 *       IERR)
  COMPLEX(8), DIMENSION(:) :: X
  INTEGER(8) :: IOPT, N, LWORK, IERR
  INTEGER(8), DIMENSION(:) :: IFAC
  REAL(8) :: SCALE
  REAL(8), DIMENSION(:) :: Y, TRIGS, WORK

C INTERFACE

#include <sunperf.h>

void zfftd(int iopt, int n, double scale, doublecomplex *x, double *y, double *trigs, int *ifac, double *work, int lwork, int *ierr);

void zfftd_64(long iopt, long n, double scale, doublecomplex *x, double *y, double *trigs, long *ifac, double *work, long lwork, long *ierr);


PURPOSE

zfftd initializes the trigonometric weight and factor tables or computes the inverse Fast Fourier Transform of a double complex sequence as follows: .Ve

               N-1

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

               j=0
.Ve

where

k ranges from 0 to N-1

i = sqrt(-1)

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

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

In complex-to-real transform of length N, the (N/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) and X(N/2) (if N is even in the latter) is assumed to be zero and is not referenced.


ARGUMENTS


SEE ALSO

fft