dfftzm man page on OpenIndiana

Man page or keyword search:  
man Server   20441 pages
apropos Keyword Search (all sections)
Output format
OpenIndiana logo
[printable version]

dfftzm(3P)		    Sun 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, N1, N2, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)

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

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

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

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

       INTEGER, INTENT(IN) :: IOPT
       INTEGER, INTENT(IN), OPTIONAL :: N1, N2, 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, [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(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:

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

       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
       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 input sequences.  N1 is most
		 efficient when it is a product of small  primes.   N1	>=  0.
		 Unchanged on exit.

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

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

       X (input) X is a double precision array of dimensions  (LDX,  N2)  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 >= N1 Unchanged on exit.

       Y (output)
		 Y is a double complex array of dimensions (LDY, N2) 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 >= N1/2 + 1 Unchanged on exit.

       TRIGS (input/output)
		 Double precision array	 of  length  2*N1  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 N1.	 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  N1.   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)
		 -4 = (LDY < N1/2 + 1)
		 -6 = (LWORK not equal 0) and (LWORK < N1)
		 -7 = memory allocation failed

SEE ALSO
       fft

				  6 Mar 2009			    dfftzm(3P)
[top]

List of man pages available for OpenIndiana

Copyright (c) for man pages and the logo by the respective OS vendor.

For those who want to learn more, the polarhome community provides shell access and support.

[legal] [privacy] [GNU] [policy] [cookies] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.
Based on Fawad Halim's script.
....................................................................
Vote for polarhome
Free Shell Accounts :: the biggest list on the net