Contents


NAME

     sfftc2 - initialize  the  trigonometric  weight  and  factor
     tables  or  compute the two-dimensional forward Fast Fourier
     Transform of a two-dimensional real array.

SYNOPSIS

     SUBROUTINE SFFTC2(IOPT, N1, N2, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

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

     SUBROUTINE SFFTC2_64(IOPT, N1, N2, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

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

  F95 INTERFACE
     SUBROUTINE FFT2(IOPT, [N1], [N2], [SCALE], X, [LDX], Y, [LDY], TRIGS,
     &          IFAC, WORK, [LWORK], IERR)

     INTEGER*4, INTENT(IN) :: IOPT
     INTEGER*4, INTENT(IN), OPTIONAL :: N1, N2, LDX, LDY, LWORK
     REAL, INTENT(IN), OPTIONAL :: SCALE
     REAL, INTENT(IN), DIMENSION(:,:) :: X
     COMPLEX, 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 FFT2_64(IOPT, [N1], [N2], [SCALE], X, [LDX], Y, [LDY], TRIGS, IFAC, WORK, [LWORK], IERR)

     INTEGER(8), INTENT(IN) :: IOPT
     INTEGER(8), INTENT(IN), OPTIONAL :: N1, N2, LDX, LDY, LWORK
     REAL, INTENT(IN), OPTIONAL :: SCALE
     REAL, INTENT(IN), DIMENSION(:,:) :: X
     COMPLEX, 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 sfftc2_ (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 sfftc2_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

     sfftc2  initializes  the  trigonometric  weight  and  factor
     tables  or computes the two-dimensional forward Fast Fourier
     Transform of a two-dimensional real array.  In computing the
     two-dimensional FFT, one-dimensional FFTs are computed along
     the columns of the input array.   One-dimensional  FFTs  are
     then computed along the rows of the intermediate results.

                        N2-1  N1-1
     Y(k1,k2) = scale * SUM   SUM   W2*W1*X(j1,j2)
                        j2=0  j1=0

     where
     k1 ranges from 0 to N1-1 and k2 ranges from 0 to N2-1
     i = sqrt(-1)
     isign = -1 for forward transform
     W1 = exp(isign*i*j1*k1*2*pi/N1)
     W2 = exp(isign*i*j2*k2*2*pi/N2)
     In real-to-complex transform of length N1, the (N1/2+1) com-
     plex  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

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

     N1 (input)
               Integer specifying length of the transform in  the
               first  dimension.  N1 is most efficient when it is
               a product of small primes.  N1 >= 0.  Unchanged on
               exit.

     N2 (input)
               Integer specifying length of the transform in  the
               second dimension.  N2 is most efficient when it is
               a product of small primes N2 >= 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) X is a complex array of dimensions (LDX, N2)  that
               contains  input  data  to be transformed.  X and Y
               can be the same array.

     LDX (input)
               Leading dimension of X.  LDX >= N1 if X is not the
               same  array as Y. Else, LDX = 2*LDY.  Unchanged on
               exit.

     Y (output)
               Y is a complex array of dimensions (LDY, N2)  that
               contains  the  transform  results.  X and Y can be
               the same array starting at the same  memory  loca-
               tion, in which case the input data are overwritten
               by their  transform  results.   Otherwise,  it  is
               assumed  that  there is no overlap between X and Y
               in memory.

     LDY (input)
               Leading dimension of Y.  LDY >=  N1/2+1  Unchanged
               on exit.

     TRIGS (input/output)
               Real array of length 2*(N1+N2) that  contains  the
               trigonometric  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  2*128  that
               contains  the  factors  of N1 and N2.  The factors
               are computed when the routine is called with  IOPT
               =  0  and  they  are used in subsequent calls when
               IOPT = -1.  Unchanged on exit.

     WORK (workspace)
               Real  array  of   dimension   at   least   MAX(N1,
               2*N2)*NCPUS,  where NCPUS is the number of threads
               used to execute the routine.  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 = N1 < 0
               -3 = N2 < 0
               -4 = (LDX < N1) or (LDX not equal 2*LDY when X and
               Y are same array)
               -5 = (LDY < N1/2+1)
               -6  =  (LWORK  not   equal   0)   and   (LWORK   <
               MAX(N1,2*N2)*NCPUS)
               -7 = memory allocation failed

SEE ALSO

     fft

CAUTIONS

     Y(N1/2+1:LDY,:) is used as scratch space.   Upon  returning,
     the  original  contents  of  Y(N1/2+1:LDY,:)  will  be lost,
     whereas Y(1:N1/2+1,1:N2) contains the transform results.