NAME

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

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

F95 INTERFACE

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

C INTERFACE

#include <sunperf.h>

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

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


PURPOSE

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

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

In real-to-complex transform of length N1, the (N1/2+1) complex output 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