Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sfftc (3p)

Name

sfftc - pute the forward Fast Fourier Transform of a real sequence.

Synopsis

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

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

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

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




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

INTEGER*4, INTENT(IN) :: IOPT
INTEGER*4, INTENT(IN), OPTIONAL :: N, 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 FFT_64(IOPT, N, SCALE, X, Y, TRIGS, IFAC, WORK, LWORK, IERR)

INTEGER(8), INTENT(IN) :: IOPT
INTEGER(8), INTENT(IN), OPTIONAL :: N, 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 sfftc_ (int *iopt, int *n, float *scale,  float  *x,  complex  *y,
float *trigs, int *ifac, float *work, int *lwork, int *ierr);

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

Description

Oracle Solaris Studio Performance Library                            sfftc(3P)



NAME
       sfftc  -  initialize the trigonometric weight and factor tables or com-
       pute the forward Fast Fourier Transform of a real sequence.

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

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

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

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




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

       INTEGER*4, INTENT(IN) :: IOPT
       INTEGER*4, INTENT(IN), OPTIONAL :: N, 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 FFT_64(IOPT, N, SCALE, X, Y, TRIGS, IFAC, WORK, LWORK, IERR)

       INTEGER(8), INTENT(IN) :: IOPT
       INTEGER(8), INTENT(IN), OPTIONAL :: N, 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 sfftc_ (int *iopt, int *n, float *scale,  float  *x,  complex  *y,
                 float *trigs, int *ifac, float *work, int *lwork, int *ierr);

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



PURPOSE
       sfftc initializes the trigonometric weight and factor  tables  or  com-
       putes the forward Fast Fourier Transform of a real 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 forward transform
       W = exp(isign*i*j*k*2*pi/N)
       In real-to-complex transform of length N, the  (N/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
       IOPT (input)
                 Integer specifying the operation to be performed:
                 IOPT  =  0 computes the trigonometric weight table and factor
                 table
                 IOPT = -1 computes forward 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.


       X (input) On  entry,  X  is a real array whose first N elements contain
                 the sequence to be transformed.


       Y (output)
                 Complex array whose first (N/2+1) elements contain the trans-
                 form  results.  X and Y may be the same array starting at the
                 same memory location, in which case the dimension of  X  must
                 be  at  least 2*(N/2+1).  Otherwise, 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  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 128 that contains 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



                                  7 Nov 2015                         sfftc(3P)