FFTCI

Computes parameters needed by FFTCF and FFTCB.

Required Arguments

N — Length of the sequence to be transformed. (Input)

WFFTC — Array of length 4N + 15 containing parameters needed by FFTCF and FFTCB. (Output)

FORTRAN 90 Interface

Generic: CALL FFTCI (N, WFFTC)

Specific: The specific interface names are S_FFTCI and D_FFTCI.

FORTRAN 77 Interface

Single: CALL FFTCI (N, WFFTC)

Double: The double precision name is DFFTCI.

Description

The routine FFTCI initializes the functions FFTCF and FFTCB. An efficient way to make multiple calls for the same N to IMSL routine FFTCF or FFTCB is to use routine FFTCI for initialization. (In this case, replace FFTCF or FFTCB with F2TCF or F2TCB, respectively.) The routine FFTCI is based on the routine CFFTI in FFTPACK. The package FFTPACK was developed by Paul Swarztrauber at the National Center for Atmospheric Research.

If the Intel® Math Kernel Library, Sun Performance Library or IBM Engineering and Scientific Subroutine Library is used, parameters computed by FFTCI are not used. In this case, there is no need to call FFTCI.

Comments

Different WFFTC arrays are needed for different values of N.

Example

In this example, we compute a two-dimensional complex FFT by making one call to FFTCI followed by 2N calls to F2TCF.

 

USE FFTCI_INT

USE CONST_INT

USE F2TCF_INT

USE UMACH_INT

 

IMPLICIT NONE

! SPECIFICATIONS FOR PARAMETERS

INTEGER N

PARAMETER (N=4)

!

INTEGER I, IR, IS, J, NOUT

REAL FLOAT, TWOPI, WFFTC(35), CPY(2*N)

COMPLEX CEXP, CMPLX, COEF(N,N), H, SEQ(N,N), TEMP

INTRINSIC CEXP, CMPLX, FLOAT

!

TWOPI = CONST('PI')

TWOPI = 2*TWOPI

IR = 3

IS = 1

! Here we compute e**(2*pi*i/N)

TEMP = CMPLX(0.0,TWOPI/FLOAT(N))

H = CEXP(TEMP)

! Fill SEQ with data

DO 20 I=1, N

DO 10 J=1, N

SEQ(I,J) = H**((I-1)*(IR-1)+(J-1)*(IS-1))

10 CONTINUE

20 CONTINUE

! Print out SEQ

! Get output unit number

CALL UMACH (2, NOUT)

WRITE (NOUT,99997)

DO 30 I=1, N

WRITE (NOUT,99998) (SEQ(I,J),J=1,N)

30 CONTINUE

! Set initialization vector

CALL FFTCI (N, WFFTC)

! Transform the columns of SEQ

DO 40 I=1, N

CALL F2TCF (N, SEQ(1:,I), COEF(1:,I), WFFTC, CPY)

40 CONTINUE

! Take transpose of the result

DO 60 I=1, N

DO 50 J=I + 1, N

TEMP = COEF(I,J)

COEF(I,J) = COEF(J,I)

COEF(J,I) = TEMP

50 CONTINUE

60 CONTINUE

! Transform the columns of this result

DO 70 I=1, N

CALL F2TCF (N, COEF(1:,I), SEQ(1:,I), WFFTC, CPY)

70 CONTINUE

! Take transpose of the result

DO 90 I=1, N

DO 80 J=I + 1, N

TEMP = SEQ(I,J)

SEQ(I,J) = SEQ(J,I)

SEQ(J,I) = TEMP

80 CONTINUE

90 CONTINUE

! Print results

WRITE (NOUT,99999)

DO 100 I=1, N

WRITE (NOUT,99998) (SEQ(I,J),J=1,N)

100 CONTINUE

!

99997 FORMAT (1X, 'The input matrix is below')

99998 FORMAT (1X, 4(' (',F5.2,',',F5.2,')'))

99999 FORMAT (/, 1X, 'Result of two-dimensional transform')

END

Output

 

The input matrix is below

( 1.00, 0.00) ( 1.00, 0.00) ( 1.00, 0.00) ( 1.00, 0.00)

(-1.00, 0.00) (-1.00, 0.00) (-1.00, 0.00) (-1.00, 0.00)

( 1.00, 0.00) ( 1.00, 0.00) ( 1.00, 0.00) ( 1.00, 0.00)

(-1.00, 0.00) (-1.00, 0.00) (-1.00, 0.00) (-1.00, 0.00)

 

Result of two-dimensional transform

( 0.00, 0.00) ( 0.00, 0.00) ( 0.00, 0.00) ( 0.00, 0.00)

( 0.00, 0.00) ( 0.00, 0.00) ( 0.00, 0.00) ( 0.00, 0.00)

(16.00, 0.00) ( 0.00, 0.00) ( 0.00, 0.00) ( 0.00, 0.00)

( 0.00, 0.00) ( 0.00, 0.00) ( 0.00, 0.00) ( 0.00, 0.00)