Contents


NAME

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

SYNOPSIS

     SUBROUTINE CFFTS(IOPT, N, SCALE, X, Y, TRIGS, IFAC, WORK, LWORK, IERR)

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

     SUBROUTINE CFFTS_64(IOPT, N, SCALE, X, Y, TRIGS, IFAC, WORK, LWORK, IERR)

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

  F95 INTERFACE
     SUBROUTINE FFT(IOPT, N, [SCALE], X, Y, TRIGS, IFAC, WORK, [LWORK], IERR)

     INTEGER*4, INTENT(IN) :: IOPT, N
     INTEGER*4, INTENT(IN), OPTIONAL :: LWORK
     REAL, INTENT(IN), OPTIONAL :: SCALE
     COMPLEX, INTENT(IN), DIMENSION(:) :: X
     REAL, INTENT(OUT), DIMENSION(:) :: Y
     REAL, INTENT(INOUT), DIMENSION(:) :: TRIGS
     INTEGER*4, INTENT(INOUT), DIMENSION(:) :: IFAC
     REAL, INTENT(OUT), DIMENSION(:) :: WORK
     INTEGER*4, INTENT(OUT) :: IERR

     SUBROUTINE FFT_64(IOPT, N, [SCALE], X, Y, TRIGS, IFAC, WORK, [LWORK], IERR)

     INTEGER(8), INTENT(IN) :: IOPT, N
     INTEGER(8), INTENT(IN), OPTIONAL :: LWORK
     REAL, INTENT(IN), OPTIONAL :: SCALE
     COMPLEX, INTENT(IN), DIMENSION(:) :: X
     REAL, INTENT(OUT), DIMENSION(:) :: Y
     REAL, INTENT(INOUT), DIMENSION(:) :: TRIGS
     INTEGER(8), INTENT(INOUT), DIMENSION(:) :: IFAC
     REAL, INTENT(OUT), DIMENSION(:) :: WORK
     INTEGER(8), INTENT(OUT) :: IERR

  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:

                    N-1
     Y(k) = scale * SUM  W*X(j)
                    j=0

     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)  com-
     plex  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

     IOPT (input)
               Integer specifying the operation to be performed:
               IOPT = 0 computes the trigonometric  weight  table
               and factor table
               IOPT = 1 computes inverse FFT

     N (input)
               Integer specifying length of the input sequence X.
               N  is most efficient when it is a product of small
               primes.  N >= 0.  Unchanged on exit.

     SCALE (input)
               Real scalar by which transform results are scaled.
               Unchanged  on exit.  SCALE is defaulted to 1.0 for
               F95 INTERFACE.

     X (input) On entry, X is a complex array whose first (N/2+1)
               elements are the input sequence to be transformed.
     Y (output)
               Real array of dimension at least N  that  contains
               the  transform  results.   X and Y may be the same
               array starting at the same memory location.   Oth-
               erwise,  it  is  assumed  that there is no overlap
               between X and Y in memory.

     TRIGS (input/output)
               Real array of length 2*N that  contains  the  tri-
               gonometric weights.  The weights are computed when
               the routine is called with IOPT = 0 and  they  are
               used in subsequent calls when IOPT = 1.  Unchanged
               on exit.

     IFAC (input/output)
               Integer array of dimension at least 128 that  con-
               tains  the factors of N.  The factors are computed
               when the routine is called with IOPT = 0 and  they
               are  used  in  subsequent  calls  where  IOPT = 1.
               Unchanged on exit.

     WORK (workspace)
               Real array of dimension at least N.  The user  can
               also  choose  to have the routine allocate its own
               workspace (see LWORK).

     LWORK (input)
               Integer specifying workspace size.  If LWORK =  0,
               the routine will allocate its own workspace.

     IERR (output)
               On exit, integer IERR has  one  of  the  following
               values:
               0 = normal return
               -1 = IOPT is not 0 or 1
               -2 = N < 0
               -3 = (LWORK is not 0) and (LWORK is less than N)
               -4 = memory allocation for workspace failed

SEE ALSO

     fft