cfftc man page on OpenIndiana

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

cfftc(3P)		    Sun Performance Library		     cfftc(3P)

NAME
       cfftc  -	 initialize the trigonometric weight and factor tables or com‐
       pute the Fast Fourier transform	(forward  or  inverse)	of  a  complex
       sequence.

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

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

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

       INTEGER*8 IOPT, N, IFAC(*), LWORK, IERR
       REAL SCALE, TRIGS(*), WORK(*)
       COMPLEX X(*), 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
       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 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
       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  cfftc_  (int *iopt, int *n, float *scale, complex *x, complex *y,
		 float *trigs, int *ifac, float *work, int *lwork, int *ierr);

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

PURPOSE
       cfftc initializes the trigonometric weight and factor  tables  or  com‐
       putes  the  Fast	 Fourier  transform  (forward or inverse) of a complex
       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 inverse transform or -1 for forward transform
       W = exp(isign*i*j*k*2*pi/N)

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

       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.  SCALE is defaulted to 1.0 for F95 INTERFACE.

       X (input) On entry, X is a complex array of dimension at least  N  that
		 contains the sequence to be transformed.

       Y (output)
		 Complex  array	 of  dimension	at  least  N that contains the
		 transform results.  X and Y may be the same array starting at
		 the  same  memory  location.	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 or 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 or IOPT = -1.  Unchanged on exit.

       WORK (workspace)
		 Real array of dimension at least  2*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, 1 or -1
		 -2 = N < 0
		 -3 = (LWORK is not 0) and (LWORK is less than 2*N)
		 -4 = memory allocation for workspace failed

SEE ALSO
       fft

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