Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dfft3b (3p)

Name

dfft3b - compute a periodic sequence from its Fourier coefficients. 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 DFFT3B(PLACE, M, N, K, A, LDA, B, LDB, WORK, LWORK)

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

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

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




F95 INTERFACE
SUBROUTINE FFT3B(PLACE, M, N, K, A, LDA, B, LDB, WORK,
LWORK)

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

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

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




C INTERFACE
#include <sunperf.h>

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

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

Description

Oracle Solaris Studio Performance Library                           dfft3b(3P)



NAME
       dfft3b - compute a periodic sequence from its Fourier coefficients. 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 DFFT3B(PLACE, M, N, K, A, LDA, B, LDB, WORK, LWORK)

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

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

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




   F95 INTERFACE
       SUBROUTINE FFT3B(PLACE, M, N, K, A, LDA, B, LDB, WORK,
              LWORK)

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

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

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




   C INTERFACE
       #include <sunperf.h>

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

       void dfft3b_64(char place, 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.


       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, the three-dimensional array A(LDA,N,K) contains the
                 data to be transformed if an in-place transform is requested.
                 Otherwise,  it  is  not  referenced.   Upon exit, results are
                 stored in A(1:M,1:N,1:K).


       LDA (input)
                 Integer specifying the leading dimension of A.  If an out-of-
                 place  transform  is  desired  LDA >= M.  Else if an in-place
                 transform is desired LDA >= 2*(M/2+1).


       B (input/output)
                 Real array of dimension B(2*LDB,N,K).  On entry, if  an  out-
                 of-place  transform  is requested B(1:2*(M/2+1),1:N,1:K) con-
                 tains the input data.  Otherwise, B is not referenced.  B  is
                 unchanged upon exit.


       LDB (input)
                 If an out-of-place transform is desired, 2*LDB is the leading
                 dimension of the array B which contains the data to be trans-
                 formed  and  2*LDB  >= 2*(M/2+1).  Otherwise it is not refer-
                 enced.


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


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




                                  7 Nov 2015                        dfft3b(3P)