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. =head1 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(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(LDB,N,*), WORK(*)
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
#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);
A(LDA,N,K)
that contains input
data to be transformed. On exit, if an in-place transform 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.
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(2*LDB,N,K)
that contains 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 transformed results.
If FULL = 'F' or 'f', B(1:2*M,1:N,1:K)
will contain the complete
transformed results.
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.