cffts3 man page on OpenIndiana

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

cffts3(3P)		    Sun Performance Library		    cffts3(3P)

NAME
       cffts3  - initialize the trigonometric weight and factor tables or com‐
       pute the three-dimensional inverse Fast Fourier Transform of  a	three-
       dimensional complex array.

SYNOPSIS
       SUBROUTINE CFFTS3(IOPT, N1, N2, N3, SCALE, X, LDX1, LDX2, Y, LDY1, LDY2, TRIGS, IFAC, WORK, LWORK, IERR)

       INTEGER IOPT, N1, N2, N3, LDX1, LDX2, LDY1, LDY2, IFAC(*), LWORK, IERR
       COMPLEX X(LDX1, LDX2, *)
       REAL SCALE, TRIGS(*), WORK(*), Y(LDY1, LDY2, *)

       SUBROUTINE CFFTS3_64(IOPT, N1, N2, N3, SCALE, X, LDX1, LDX2, Y, LDY1, LDY2, TRIGS, IFAC, WORK, LWORK, IERR)

       INTEGER*8  IOPT,	 N1,  N2,  N3, LDX1, LDX2, LDY1, LDY2, IFAC(*), LWORK,
       IERR
       COMPLEX X(LDX1, LDX2, *)
       REAL SCALE, TRIGS(*), WORK(*), Y(LDY1, LDY2, *)

   F95 INTERFACE
       SUBROUTINE FFT3(IOPT, N1, [N2], [N3], [SCALE], X, [LDX1], LDX2, Y, [LDY1], LDY2, TRIGS,
		 IFAC, WORK, [LWORK], IERR)

       INTEGER*4, INTENT(IN) :: IOPT, N1, LDX2, LDY2
       INTEGER*4, INTENT(IN), OPTIONAL :: N2, N3, LDX1, LDY1, LWORK
       REAL, INTENT(IN), OPTIONAL :: SCALE
       COMPLEX, INTENT(IN), DIMENSION(:,:,:) :: X
       REAL, 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 FFT3_64(IOPT, N1, [N2], [N3], [SCALE], X, [LDX1], LDX2, Y, [LDY1], LDY2, TRIGS,
		 IFAC, WORK, [LWORK], IERR)

       INTEGER(8), INTENT(IN) :: IOPT, N1, LDX2, LDY2
       INTEGER(8), INTENT(IN), OPTIONAL :: N2, N3, LDX1, LDY1, LWORK
       REAL, INTENT(IN), OPTIONAL :: SCALE
       COMPLEX, INTENT(IN), DIMENSION(:,:,:) :: X
       REAL, 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 cffts3_ (int *iopt, int *n1, int *n2, int *n3, float *scale,  com‐
		 plex  *x,  int	 *ldx1,	 int  *ldx2,  float *y, int *ldy1, int
		 *ldy2, float *trigs, int *ifac, float *work, int *lwork,  int
		 *ierr);

       void  cffts3_64_	 (long	*iopt,	long  *n1,  long  *n2, long *n3, float
		 *scale, complex *x, long *ldx1, long *ldx2,  float  *y,  long
		 *ldy1,	 long  *ldy2,  float  *trigs, long *ifac, float *work,
		 long *lwork, long *ierr);

PURPOSE
       cffts3 initializes the trigonometric weight and factor tables  or  com‐
       putes  the  three-dimensional  inverse  Fast  Fourier  Transform	 of  a
       three-dimensional complex array.

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

       where
       k1 ranges from 0 to N1-1; k2 ranges from 0 to N2-1 and k3 ranges from 0
       to N3-1
       i = sqrt(-1)
       isign = 1 for inverse transform
       W1 = exp(isign*i*j1*k1*2*pi/N1)
       W2 = exp(isign*i*j2*k2*2*pi/N2)
       W3 = exp(isign*i*j3*k3*2*pi/N3)

ARGUMENTS
       IOPT (input)
		 Integer specifying the operation to be performed:
		 IOPT  =  0 computes the trigonometric weight table and factor
		 table
		 IOPT = +1 computes inverse 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.

       N3 (input)
		 Integer specifying length  of	the  transform	in  the	 third
		 dimension.   N3  is  most  efficient  when it is a product of
		 small primes.	N3 >= 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 (LDX1, LDX2, N3) that con‐
		 tains input data to be transformed.

       LDX1 (input)
		 first dimension of X.	LDX1 >= N1/2+1 Unchanged on exit.

       LDX2 (input)
		 second dimension of X.	 LDX2 >= N2 Unchanged on exit.

       Y (output)
		 Y is a real array of dimensions (LDY1, LDY2,  N3)  that  con‐
		 tains	the  transform results.	 X and Y can be the same array
		 starting at the same memory location, 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.

       LDY1 (input)
		 first	dimension of Y.	 If X and Y are the same array, LDY1 =
		 2*LDX1 Else LDY1 >= 2*LDX1 and	 LDY1  is  even	 Unchanged  on
		 exit.

       LDY2 (input)
		 second dimension of Y.	 If X and Y are the same array, LDY2 =
		 LDX2 Else LDY2 >= N2 Unchanged on exit.

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

       WORK (workspace)
		 Real array of dimension at least (MAX(N,2*N2,2*N3) + 16*N3) *
		 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 = N3 < 0
		 -5 = (LDX1 < N1/2+1)
		 -6 = (LDX2 < N2)
		 -7 = LDY1 not equal 2*LDX1 when X and Y are same array
		 -8 = (LDY1 < 2*LDX1) or (LDY1 is odd) when X and  Y  are  not
		 same array
		 -9  =	(LDY2  < N2) or (LDY2 not equal LDX2) when X and Y are
		 same array
		 -10 = (LWORK not equal 0) and ((LWORK	<  MAX(N,2*N2,2*N3)  +
		 16*N3)*NCPUS)
		 -11 = memory allocation failed

SEE ALSO
       fft

CAUTIONS
       This  routine  uses  Y(N1+1:LDY1,:,:) as scratch space.	Therefore, the
       original contents of this subarray will be  lost	 upon  returning  from
       routine	 while	 subarray  Y(1:N1,1:N2,1:N3)  contains	the  transform
       results.

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