cfftcm man page on OpenIndiana

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

cfftcm(3P)		    Sun Performance Library		    cfftcm(3P)

NAME
       cfftcm  - initialize the trigonometric weight and factor tables or com‐
       pute the one-dimensional Fast Fourier Transform (forward or inverse) of
       a set of data sequences stored in a two-dimensional complex array.

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

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

       SUBROUTINE CFFTCM_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 SCALE, TRIGS(*), WORK(*)
       COMPLEX X(LDX, *), Y(LDY, *)

   F95 INTERFACE
       SUBROUTINE FFTM(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
       COMPLEX, 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 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, INTENT(IN), OPTIONAL :: SCALE
       COMPLEX, 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  cfftcm_  (int  *iopt, int *n1, int *n2, float *scale, complex *x,
		 int *ldx, complex *y, int  *ldy,  float  *trigs,  int	*ifac,
		 float *work, int *lwork, int *ierr);

       void  cfftcm_64_ (long *iopt, long *n1, long *n2, float *scale, complex
		 *x, long *ldx, complex *y,  long  *ldy,  float	 *trigs,  long
		 *ifac, float *work, long *lwork, long *ierr);

PURPOSE
       cfftcm  initializes  the trigonometric weight and factor tables or com‐
       putes the one-dimensional Fast Fourier Transform (forward  or  inverse)
       of a set of data sequences stored in a two-dimensional complex array:

	      N1-1
       Y(k,l) = 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 inverse transform or -1 for forward transform
       W = exp(isign*i*j*k*2*pi/N1)

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
		 IOPT = +1 computes inverse 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)
		 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
		 the sequences to be transformed stored in its columns.

       LDX (input)
		 Leading dimension of X.  LDX >= N1 Unchanged on exit.

       Y (output)
		 Y  is	a  complex array of dimensions (LDY, N2) that contains
		 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.  If X and Y are the same array, LDY =
		 LDX Else LDY >= N1 Unchanged on exit.

       TRIGS (input/output)
		 Real  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 subsequent calls when IOPT
		 = 1 or 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 or IOPT = -1.  Unchanged on exit.

       WORK (workspace)
		 Real  array  of  dimension at least 2*N1*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, 1 or -1
		 -2 = N1 < 0
		 -3 = N2 < 0
		 -4 = (LDX < N1)
		 -5  =	(LDY < N1) or (LDY not equal LDX when X and Y are same
		 array)
		 -6 = (LWORK not equal 0) and (LWORK < 2*N1*NCPUS)
		 -7 = memory allocation failed

SEE ALSO
       fft

				  6 Mar 2009			    cfftcm(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