NAME

cfftc3 - initialize the trigonometric weight and factor tables or compute the three-dimensional Fast Fourier Transform (forward or inverse) of a three-dimensional complex array. =head1 SYNOPSIS

  SUBROUTINE CFFTC3( IOPT, N1, N2, N3, SCALE, X, LDX1, LDX2, Y, LDY1, 
 *      LDY2, TRIGS, IFAC, WORK, LWORK, IERR)
  COMPLEX X(LDX1,LDX2,*), Y(LDY1,LDY2,*)
  INTEGER IOPT, N1, N2, N3, LDX1, LDX2, LDY1, LDY2, LWORK, IERR
  INTEGER IFAC(*)
  REAL SCALE
  REAL TRIGS(*), WORK(*)
  SUBROUTINE CFFTC3_64( IOPT, N1, N2, N3, SCALE, X, LDX1, LDX2, Y, 
 *      LDY1, LDY2, TRIGS, IFAC, WORK, LWORK, IERR)
  COMPLEX X(LDX1,LDX2,*), Y(LDY1,LDY2,*)
  INTEGER*8 IOPT, N1, N2, N3, LDX1, LDX2, LDY1, LDY2, LWORK, IERR
  INTEGER*8 IFAC(*)
  REAL SCALE
  REAL TRIGS(*), WORK(*)

F95 INTERFACE

  SUBROUTINE FFT3( IOPT, [N1], [N2], [N3], [SCALE], X, [LDX1], LDX2, 
 *       Y, [LDY1], LDY2, TRIGS, IFAC, WORK, [LWORK], IERR)
  COMPLEX, DIMENSION(:,:,:) :: X, Y
  INTEGER :: IOPT, N1, N2, N3, LDX1, LDX2, LDY1, LDY2, LWORK, IERR
  INTEGER, DIMENSION(:) :: IFAC
  REAL :: SCALE
  REAL, DIMENSION(:) :: TRIGS, WORK
  SUBROUTINE FFT3_64( IOPT, [N1], [N2], [N3], [SCALE], X, [LDX1], 
 *       LDX2, Y, [LDY1], LDY2, TRIGS, IFAC, WORK, [LWORK], IERR)
  COMPLEX, DIMENSION(:,:,:) :: X, Y
  INTEGER(8) :: IOPT, N1, N2, N3, LDX1, LDX2, LDY1, LDY2, LWORK, IERR
  INTEGER(8), DIMENSION(:) :: IFAC
  REAL :: SCALE
  REAL, DIMENSION(:) :: TRIGS, WORK

C INTERFACE

#include <sunperf.h>

void cfftc3(int iopt, int n1, int n2, int n3, float scale, complex *x, int ldx1, int ldx2, complex *y, int ldy1, int ldy2, float *trigs, int *ifac, float *work, int lwork, int *ierr);

void cfftc3_64(long iopt, long n1, long n2, long n3, float scale, complex *x, long ldx1, long ldx2, complex *y, long ldy1, long ldy2, float *trigs, long *ifac, float *work, long lwork, long *ierr);


PURPOSE

cfftc3 initializes the trigonometric weight and factor tables or computes the three-dimensional Fast Fourier Transform (forward or inverse) of a three-dimensional complex array. .Ve

                      N3-1  N2-1  N1-1

Y(k1,k2,k3) = scale * SUM SUM SUM W3*W2*W1*X(j1,j2,j3)

                      j3=0  j2=0  j1=0
.Ve

where

k1 ranges from 0 to N1-1; k2 ranges from 0 to N2-1 and k3 ranges from 0 to N3-1

i = sqrt(-1)

isign = 1 for inverse transform or -1 for forward transform

W1 = exp(isign*i*j1*k1*2*pi/N1)

W2 = exp(isign*i*j2*k2*2*pi/N2)

W3 = exp(isign*i*j3*k3*2*pi/N3)


ARGUMENTS


SEE ALSO

fft


CAUTIONS

This routine uses Y(N1+1:LDY1,:,:) as scratch space. Therefore, the original contents of this subarray will be lost upon returning from routine while subarray Y(1:N1,1:N2,1:N3) contains the transform results.