NAME

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

  SUBROUTINE CFFTSM( 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 CFFTSM_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 FFTM( 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 FFTM_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 cfftsm(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 cfftsm_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

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