Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dfftzm (3p)

Name

dfftzm - pute the one-dimensional forward Fast Fourier Transform of a set of double precision data sequences stored in a two-dimensional array.

Synopsis

SUBROUTINE DFFTZM(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

INTEGER IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR
DOUBLE PRECISION X(LDX, *), SCALE, TRIGS(*), WORK(*)
DOUBLE COMPLEX Y(LDY, *)

SUBROUTINE DFFTZM_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

INTEGER*8 IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR
DOUBLE PRECISION X(LDX, *), SCALE, TRIGS(*), WORK(*)
DOUBLE COMPLEX Y(LDY, *)




F95 INTERFACE
SUBROUTINE FFTM(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS,
IFAC, WORK, LWORK, IERR)

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

SUBROUTINE FFTM_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

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




C INTERFACE
#include <sunperf.h>

void  dfftzm_ (int *iopt, int *m, int *n, double *scale, double *x, int
*ldx, doublecomplex *y, int *ldy, double *trigs,  int  *ifac,
double *work, int *lwork, int *ierr);

void  dfftzm_64_  (long  *iopt, long *m, long *n, double *scale, double
*x, long *ldx, doublecomplex *y, long  *ldy,  double  *trigs,
long *ifac, double *work, long *lwork, long *ierr);

Description

Oracle Solaris Studio Performance Library                           dfftzm(3P)



NAME
       dfftzm  - initialize the trigonometric weight and factor tables or com-
       pute the one-dimensional forward Fast Fourier Transform  of  a  set  of
       double precision data sequences stored in a two-dimensional array.

SYNOPSIS
       SUBROUTINE DFFTZM(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

       INTEGER IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR
       DOUBLE PRECISION X(LDX, *), SCALE, TRIGS(*), WORK(*)
       DOUBLE COMPLEX Y(LDY, *)

       SUBROUTINE DFFTZM_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

       INTEGER*8 IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR
       DOUBLE PRECISION X(LDX, *), SCALE, TRIGS(*), WORK(*)
       DOUBLE COMPLEX Y(LDY, *)




   F95 INTERFACE
       SUBROUTINE FFTM(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS,
                 IFAC, WORK, LWORK, IERR)

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

       SUBROUTINE FFTM_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

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




   C INTERFACE
       #include <sunperf.h>

       void  dfftzm_ (int *iopt, int *m, int *n, double *scale, double *x, int
                 *ldx, doublecomplex *y, int *ldy, double *trigs,  int  *ifac,
                 double *work, int *lwork, int *ierr);

       void  dfftzm_64_  (long  *iopt, long *m, long *n, double *scale, double
                 *x, long *ldx, doublecomplex *y, long  *ldy,  double  *trigs,
                 long *ifac, double *work, long *lwork, long *ierr);



PURPOSE
       dfftzm  initializes  the trigonometric weight and factor tables or com-
       putes the one-dimensional forward Fast Fourier Transform of  a  set  of
       double precision data sequences stored in a two-dimensional array:

                        M-1
       Y(k,l) = scale * SUM  W*X(j,l)
                        j=0

       where
       k ranges from 0 to M-1 and l ranges from 0 to N-1
       i = sqrt(-1)
       isign = -1 for forward transform
       W = exp(isign*i*j*k*2*pi/M)
       In  real-to-complex  transform  of length M, the (M/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

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

       N (input)
                 Integer  specifying  number  of  input  sequences.   N  >= 0.
                 Unchanged on exit.

       SCALE (input)
                 Double  precision  scalar  by  which  transform  results  are
                 scaled.  Unchanged on exit.

       X (input) X  is  a  double  precision array of dimensions (LDX, N) that
                 contains the sequences to be transformed stored in  its  col-
                 umns.

       LDX (input)
                 Leading dimension of X.  If X and Y are the same array, LDX =
                 2*LDY Else LDX >= M Unchanged on exit.

       Y (output)
                 Y is a double complex array of dimensions (LDY, N) that  con-
                 tains  the transform results of the input sequences.  X and Y
                 can be the same array starting at the same  memory  location,
                 in  which  case  the input sequences 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 >= M/2 + 1 Unchanged on exit.

       TRIGS (input/output)
                 Double  precision  array  of  length  2*M  that  contains the
                 trigonometric weights.  The weights  are  computed  when  the
                 routine  is  called with IOPT = 0 and they are used in subse-
                 quent calls when IOPT = -1.  Unchanged on exit.

       IFAC (input/output)
                 Integer array of dimension at least  128  that  contains  the
                 factors  of  M.  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)
                 Double precision array of dimension at least M.  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 = M < 0
                 -3 = N < 0
                 -4 = (LDX < M) or (LDX not equal 2*LDY when X and Y are  same
                 array)
                 -4 = (LDY < M/2 + 1)
                 -6 = (LWORK not equal 0) and (LWORK < M)
                 -7 = memory allocation failed

SEE ALSO
       fft



                                  7 Nov 2015                        dfftzm(3P)