NAME

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

  SUBROUTINE CFFTS( IOPT, N, SCALE, X, Y, TRIGS, IFAC, WORK, LWORK, 
 *      IERR)
  COMPLEX X(*)
  INTEGER IOPT, N, LWORK, IERR
  INTEGER IFAC(*)
  REAL SCALE
  REAL Y(*), TRIGS(*), WORK(*)
  SUBROUTINE CFFTS_64( IOPT, N, SCALE, X, Y, TRIGS, IFAC, WORK, LWORK, 
 *      IERR)
  COMPLEX X(*)
  INTEGER*8 IOPT, N, LWORK, IERR
  INTEGER*8 IFAC(*)
  REAL SCALE
  REAL Y(*), TRIGS(*), WORK(*)

F95 INTERFACE

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

C INTERFACE

#include <sunperf.h>

void cffts(int iopt, int n, float scale, complex *x, float *y, float *trigs, int *ifac, float *work, int lwork, int *ierr);

void cffts_64(long iopt, long n, float scale, complex *x, float *y, float *trigs, long *ifac, float *work, long lwork, long *ierr);


PURPOSE

cffts initializes the trigonometric weight and factor tables or computes the inverse Fast Fourier Transform of a 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