Contents


NAME

     rfft3b - compute a periodic sequence from its Fourier  coef-
     ficients.   The  RFFT operations are unnormalized, so a call
     of RFFT3F followed by a call of  RFFT3B  will  multiply  the
     input sequence by M*N*K.

SYNOPSIS

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

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

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

     CHARACTER * 1 PLACE
     INTEGER*8 M, N, K, LDA, LDB, LWORK
     REAL 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, DIMENSION(:) :: WORK
     REAL, 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, DIMENSION(:) :: WORK
     REAL, DIMENSION(:,:,:) :: A, B

  C INTERFACE
     #include <sunperf.h>

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

     void rfft3b_64(char place, long m, long n, long k, float *a,
               long  lda,  float  *b, long ldb, float *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) contains  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 con-
               tains the data to  be  transformed  and  2*LDB  >=
               2*(M/2+1).  Otherwise it is not referenced.

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

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