dfft3f man page on OpenIndiana

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

dfft3f(3P)		    Sun Performance Library		    dfft3f(3P)

NAME
       dfft3f  - compute the Fourier coefficients of a real periodic sequence.
       The DFFT operations are unnormalized, so a call of DFFT3F followed by a
       call of DFFT3B will multiply the input sequence by M*N*K.

SYNOPSIS
       SUBROUTINE DFFT3F(PLACE, FULL, M, N, K, A, LDA, B, LDB, WORK, LWORK)

       CHARACTER * 1 PLACE, FULL
       INTEGER M, N, K, LDA, LDB, LWORK
       DOUBLE PRECISION A(LDA,N,*), B(2*LDB,N,*), WORK(*)

       SUBROUTINE DFFT3F_64(PLACE, FULL, M, N, K, A, LDA, B, LDB, WORK,
	     LWORK)

       CHARACTER * 1 PLACE, FULL
       INTEGER*8 M, N, K, LDA, LDB, LWORK
       DOUBLE PRECISION A(LDA,N,*), B(2*LDB,N,*), WORK(*)

   F95 INTERFACE
       SUBROUTINE FFT3F(PLACE, FULL, [M], [N], [K], A, [LDA], B, [LDB],
	      WORK, LWORK)

       CHARACTER(LEN=1) :: PLACE, FULL
       INTEGER :: M, N, K, LDA, LDB, LWORK
       REAL(8), DIMENSION(:) :: WORK
       REAL(8), DIMENSION(:,:,:) :: A, B

       SUBROUTINE FFT3F_64(PLACE, FULL, [M], [N], [K], A, [LDA], B, [LDB],
	      WORK, LWORK)

       CHARACTER(LEN=1) :: PLACE, FULL
       INTEGER(8) :: M, N, K, LDA, LDB, LWORK
       REAL(8), DIMENSION(:) :: WORK
       REAL(8), DIMENSION(:,:,:) :: A, B

   C INTERFACE
       #include <sunperf.h>

       void  dfft3f(char place, char full, int m, int n, int k, double *a, int
		 lda, double *b, int ldb, double *work, int lwork);

       void dfft3f_64(char place, char full, long m, long n,  long  k,	double
		 *a, long lda, double *b, long ldb, double *work, long lwork);

ARGUMENTS
       PLACE (input)
		 Select	 an in-place ('I' or 'i') or out-of-place ('O' or 'o')
		 transform.

       FULL (input)
		 Select a full ('F' or 'f') or partial (' ') representation of
		 the  results.	If the caller selects full representation then
		 an MxNxK real array will transform to produce an  MxNxK  com‐
		 plex  array.	If the caller does not select full representa‐
		 tion then an MxNxK real array will transform to a (M/2+1)xNxK
		 complex array that takes advantage of the symmetry properties
		 of a transformed real sequence.

       M (input) Integer specifying the number of rows to be transformed.   It
		 is  most efficient when M is a product of small primes.  M >=
		 0; when M = 0, the  subroutine	 returns  immediately  without
		 changing any data.

       N (input) Integer  specifying  the number of columns to be transformed.
		 It is most efficient when N is a product of small primes.   N
		 >=  0; when N = 0, the subroutine returns immediately without
		 changing any data.

       K (input) Integer specifying the number of planes  to  be  transformed.
		 It  is most efficient when K is a product of small primes.  K
		 >= 0; when K = 0, the subroutine returns immediately  without
		 changing any data.

       A (input/output)
		 On  entry, a three-dimensional array A(LDA,N,K) that contains
		 input data to be transformed.	On exit, if an in-place trans‐
		 form	 is    done    and   FULL   is	 not   'F'   or	  'f',
		 A(1:2*(M/2+1),1:N,1:K) will contain the  partial  transformed
		 results.  If FULL = 'F' or 'f', A(1:2*M,1:N,1:K) will contain
		 the complete transformed results.

       LDA (input)
		 Leading dimension of the array	 containing  the  data	to  be
		 transformed.	LDA  must be even if the transformed sequences
		 are to be stored in A.

		 If PLACE = ('O' or 'o') LDA >= M

		 If PLACE = ('I' or 'i') LDA must be even.  If

		 FULL = ('F' or 'f'), LDA >= 2*M

		 FULL is not ('F' or 'f'), LDA >= 2*(M/2+1)

       B (input/output)
		 Upon exit, a three-dimensional array B(2*LDB,N,K)  that  con‐
		 tains the transformed results if an out-of-place transform is
		 done.	Otherwise, B is not used.

		 If an out-of-place transform is done and FULL is not  'F'  or
		 'f',  B(1:2*(M/2+1),1:N,1:K)  will contain the partial trans‐
		 formed results.  If FULL = 'F' or 'f', B(1:2*M,1:N,1:K)  will
		 contain the complete transformed results.

       LDB (input)
		 2*LDB	is  the	 leading  dimension of the array B.  If an in-
		 place transform is desired LDB is ignored.

		 If PLACE is ('O' or 'o') and

		 FULL is ('F' or 'f'), then LDB >= M

		 FULL is not ('F' or 'f'), then LDB >= M/2 + 1

		 Note that even though LDB is used in the argument list, 2*LDB
		 is the actual leading dimension of B.

       WORK (input/output)
		 One-dimensional  real	array  of length at least LWORK.  WORK
		 must have been initialized by DFFT3I.

       LWORK (input)
		 Integer.  LWORK >= (M + 2*(N + K) + 4*K + 45).

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