cfftc2 - pute the two-dimensional Fast Fourier Transform (forward or inverse) of a two-dimensional complex array.
SUBROUTINE CFFTC2(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR COMPLEX X(LDX, *), Y(LDY, *) REAL SCALE, TRIGS(*), WORK(*) SUBROUTINE CFFTC2_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER*8 IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR REAL SCALE, TRIGS(*), WORK(*) COMPLEX X(LDX, *), Y(LDY, *) F95 INTERFACE SUBROUTINE FFT2(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER*4, INTENT(IN) :: IOPT INTEGER*4, INTENT(IN), OPTIONAL :: M, N, LDX, LDY, 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 FFT2_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER(8), INTENT(IN) :: IOPT INTEGER(8), INTENT(IN), OPTIONAL :: M, N, LDX, LDY, 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 cfftc2_ (int *iopt, int *n1, int *n2, float *scale, complex *x, int *ldx, complex *y, int *ldy, float *trigs, int *ifac, float *work, int *lwork, int *ierr); void cfftc2_64_ (long *iopt, long *n1, long *n2, float *scale, complex *x, long *ldx, complex *y, long *ldy, float *trigs, long *ifac, float *work, long *lwork, long *ierr);
Oracle Solaris Studio Performance Library cfftc2(3P)
NAME
cfftc2 - initialize the trigonometric weight and factor tables or com-
pute the two-dimensional Fast Fourier Transform (forward or inverse) of
a two-dimensional complex array.
SYNOPSIS
SUBROUTINE CFFTC2(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)
INTEGER IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR
COMPLEX X(LDX, *), Y(LDY, *)
REAL SCALE, TRIGS(*), WORK(*)
SUBROUTINE CFFTC2_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)
INTEGER*8 IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR
REAL SCALE, TRIGS(*), WORK(*)
COMPLEX X(LDX, *), Y(LDY, *)
F95 INTERFACE
SUBROUTINE FFT2(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS,
IFAC, WORK, LWORK, IERR)
INTEGER*4, INTENT(IN) :: IOPT
INTEGER*4, INTENT(IN), OPTIONAL :: M, N, LDX, LDY, 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 FFT2_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR)
INTEGER(8), INTENT(IN) :: IOPT
INTEGER(8), INTENT(IN), OPTIONAL :: M, N, LDX, LDY, 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 cfftc2_ (int *iopt, int *n1, int *n2, float *scale, complex *x,
int *ldx, complex *y, int *ldy, float *trigs, int *ifac,
float *work, int *lwork, int *ierr);
void cfftc2_64_ (long *iopt, long *n1, long *n2, float *scale, complex
*x, long *ldx, complex *y, long *ldy, float *trigs, long
*ifac, float *work, long *lwork, long *ierr);
PURPOSE
cfftc2 initializes the trigonometric weight and factor tables or com-
putes the two-dimensional Fast Fourier Transform (forward or inverse)
of a two-dimensional complex array. In computing the two-dimensional
FFT, one-dimensional FFTs are computed along the columns of the input
array. One-dimensional FFTs are then computed along the rows of the
intermediate results.
N-1 M-1
Y(k1,k2) = scale * SUM SUM W2*W1*X(j1,j2)
j2=0 j1=0
where
k1 ranges from 0 to M-1 and k2 ranges from 0 to N-1
i = sqrt(-1)
isign = 1 for inverse transform or -1 for forward transform
W1 = exp(isign*i*j1*k1*2*pi/M)
W2 = exp(isign*i*j2*k2*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
M (input)
Integer specifying length of the transform in the first
dimension. M is most efficient when it is a product of small
primes. M >= 0. Unchanged on exit.
N (input)
Integer specifying length of the transform in the second
dimension. 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.
X (input) X is a complex array of dimensions (LDX, N) that contains
input data to be transformed.
LDX (input)
Leading dimension of X. LDX >= M Unchanged on exit.
Y (output)
Y is a complex array of dimensions (LDY, N) that contains the
transform results. X and Y can be the same array starting at
the same memory location, in which case the input data are
overwritten by their transform results. Otherwise, it is
assumed that there is no overlap between X and Y in memory.
LDY (input)
Leading dimension of Y. If X and Y are the same array, LDY =
LDX Else LDY >= M Unchanged on exit.
TRIGS (input/output)
Real array of length 2*(M+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 2*128 that contains the
factors of M and N. The factors are computed when the rou-
tine is called with IOPT = 0 and they are used in subsequent
calls when IOPT = 1 or IOPT = -1. Unchanged on exit.
WORK (workspace)
Real array of dimension at least 2*MAX(M,N)*NCPUS where NCPUS
is the number of threads used to execute the routine. 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 = M < 0
-3 = N < 0
-4 = (LDX < M)
-5 = (LDY < M) or (LDY not equal LDX when X and Y are same
array)
-6 = (LWORK not equal 0) and (LWORK < 2*MAX(M,N)*NCPUS)
-7 = memory allocation failed
SEE ALSO
fft
CAUTIONS
On exit, entire output array Y(1:LDY, 1:N) is overwritten.
7 Nov 2015 cfftc2(3P)