zfftdm - pute the one-dimensional inverse Fast Fourier Transform of a set of double complex data sequences stored in a two-dimensional array.
SUBROUTINE ZFFTDM(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR DOUBLE COMPLEX X(LDX, *) DOUBLE PRECISION SCALE, Y(LDY, *), TRIGS(*), WORK(*) SUBROUTINE ZFFTDM_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER*8 IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR DOUBLE COMPLEX X(LDX, *) DOUBLE PRECISION SCALE, Y(LDY,*), TRIGS(*), WORK(*) F95 INTERFACE SUBROUTINE FFTM(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER, INTENT(IN) :: IOPT, M INTEGER, INTENT(IN), OPTIONAL :: N, LDX, LDY, LWORK REAL(8), INTENT(IN), OPTIONAL :: SCALE COMPLEX(8), INTENT(IN), DIMENSION(:,:) :: X REAL(8), INTENT(OUT), DIMENSION(:,:) :: Y REAL(8), INTENT(INOUT), DIMENSION(:) :: TRIGS INTEGER, INTENT(INOUT), DIMENSION(:) :: IFAC REAL(8), INTENT(OUT), DIMENSION(:) :: WORK INTEGER, INTENT(OUT) :: IERR SUBROUTINE FFTM_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER(8), INTENT(IN) :: IOPT, M INTEGER(8), INTENT(IN), OPTIONAL :: N, LDX, LDY, LWORK REAL(8), INTENT(IN), OPTIONAL :: SCALE COMPLEX(8), INTENT(IN), DIMENSION(:,:) :: X REAL(8), INTENT(OUT), DIMENSION(:,:) :: Y REAL(8), INTENT(INOUT), DIMENSION(:) :: TRIGS INTEGER(8), INTENT(INOUT), DIMENSION(:) :: IFAC REAL(8), INTENT(OUT), DIMENSION(:) :: WORK INTEGER(8), INTENT(OUT) :: IERR C INTERFACE #include <sunperf.h> void zfftdm_ (int *iopt, int *m, int *n, double *scale, doublecomplex *x, int *ldx, double *y, int *ldy, double *trigs, int *ifac, double *work, int *lwork, int *ierr); void zfftdm_64_ (long *iopt, long *m, long *n, double *scale, double- complex *x, long *ldx, double *y, long *ldy, double *trigs, long *ifac, double *work, long *lwork, long *ierr);
Oracle Solaris Studio Performance Library zfftdm(3P) NAME zfftdm - initialize the trigonometric weight and factor tables or com- pute the one-dimensional inverse Fast Fourier Transform of a set of double complex data sequences stored in a two-dimensional array. SYNOPSIS SUBROUTINE ZFFTDM(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR DOUBLE COMPLEX X(LDX, *) DOUBLE PRECISION SCALE, Y(LDY, *), TRIGS(*), WORK(*) SUBROUTINE ZFFTDM_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER*8 IOPT, M, N, LDX, LDY, IFAC(*), LWORK, IERR DOUBLE COMPLEX X(LDX, *) DOUBLE PRECISION SCALE, Y(LDY,*), TRIGS(*), WORK(*) F95 INTERFACE SUBROUTINE FFTM(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER, INTENT(IN) :: IOPT, M INTEGER, INTENT(IN), OPTIONAL :: N, LDX, LDY, LWORK REAL(8), INTENT(IN), OPTIONAL :: SCALE COMPLEX(8), INTENT(IN), DIMENSION(:,:) :: X REAL(8), INTENT(OUT), DIMENSION(:,:) :: Y REAL(8), INTENT(INOUT), DIMENSION(:) :: TRIGS INTEGER, INTENT(INOUT), DIMENSION(:) :: IFAC REAL(8), INTENT(OUT), DIMENSION(:) :: WORK INTEGER, INTENT(OUT) :: IERR SUBROUTINE FFTM_64(IOPT, M, N, SCALE, X, LDX, Y, LDY, TRIGS, IFAC, WORK, LWORK, IERR) INTEGER(8), INTENT(IN) :: IOPT, M INTEGER(8), INTENT(IN), OPTIONAL :: N, LDX, LDY, LWORK REAL(8), INTENT(IN), OPTIONAL :: SCALE COMPLEX(8), INTENT(IN), DIMENSION(:,:) :: X REAL(8), INTENT(OUT), DIMENSION(:,:) :: Y REAL(8), INTENT(INOUT), DIMENSION(:) :: TRIGS INTEGER(8), INTENT(INOUT), DIMENSION(:) :: IFAC REAL(8), INTENT(OUT), DIMENSION(:) :: WORK INTEGER(8), INTENT(OUT) :: IERR C INTERFACE #include <sunperf.h> void zfftdm_ (int *iopt, int *m, int *n, double *scale, doublecomplex *x, int *ldx, double *y, int *ldy, double *trigs, int *ifac, double *work, int *lwork, int *ierr); void zfftdm_64_ (long *iopt, long *m, long *n, double *scale, double- complex *x, long *ldx, double *y, long *ldy, double *trigs, long *ifac, double *work, long *lwork, long *ierr); PURPOSE zfftdm initializes the trigonometric weight and factor tables or com- putes the one-dimensional inverse Fast Fourier Transform of a set of double complex data sequences stored in a two-dimensional array: M-1 Y(k,l) = scale * SUM W*X(j,l) j=0 where k ranges from 0 to M-1 and l ranges from 0 to N-1 i = sqrt(-1) isign = 1 for inverse transform W = exp(isign*i*j*k*2*pi/M) In complex-to-real transform of length M, the (M/2+1) complex input data points stored are the positive-frequency half of the spectrum of the Discrete Fourier Transform. The other half can be obtained through complex conjugation and therefore is not stored. Furthermore, due to symmetries the imaginary of the component of X(0,0:N-1) and X(M/2,0:N-1) (if M is even in the latter) is assumed to be zero and is not referenced. ARGUMENTS IOPT (input) Integer specifying the operation to be performed: IOPT = 0 computes the trigonometric weight table and factor table IOPT = 1 computes inverse FFT M (input) Integer specifying length of the input sequences. M is most efficient when it is a product of small primes. M >= 0. Unchanged on exit. N (input) Integer specifying number of input sequences. N >= 0. Unchanged on exit. SCALE (input) Double precision scalar by which transform results are scaled. Unchanged on exit. X (input) X is a double complex array of dimensions (LDX, N) that con- tains the sequences to be transformed stored in its columns in X(0:M/2, 0:N-1). LDX (input) Leading dimension of X. LDX >= (M/2+1) Unchanged on exit. Y (output) Y is a double precision array of dimensions (LDY, N) that contains the transform results of the input sequences in Y(0:M-1,0:N-1). X and Y can be the same array starting at the same memory location, in which case the input sequences 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 = 2*LDX Else LDY >= M Unchanged on exit. TRIGS (input/output) double precision array of length 2*M that contains the trigonometric weights. The weights are computed when the routine is called with IOPT = 0 and they are used in subse- quent calls when IOPT = 1. Unchanged on exit. IFAC (input/output) Integer array of dimension at least 128 that contains the factors of M. The factors are computed when the routine is called with IOPT = 0 and they are used in subsequent calls when IOPT = 1. Unchanged on exit. WORK (workspace) double precision array of dimension at least M. 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 or 1 -2 = M < 0 -3 = N < 0 -4 = (LDX < M/2+1) -5 = (LDY < M) or (LDY not equal 2*LDX when X and Y are same array) -6 = (LWORK not equal 0) and (LWORK < M) -7 = memory allocation failed SEE ALSO fft 7 Nov 2015 zfftdm(3P)