OpenLibm/slatec/cffti1.f
Viral B. Shah c977aa998f Add Makefile.extras to build libopenlibm-extras.
Replace amos with slatec
2012-12-31 16:37:05 -05:00

114 lines
3.5 KiB
Fortran

*DECK CFFTI1
SUBROUTINE CFFTI1 (N, WA, IFAC)
C***BEGIN PROLOGUE CFFTI1
C***PURPOSE Initialize a real and an integer work array for CFFTF1 and
C CFFTB1.
C***LIBRARY SLATEC (FFTPACK)
C***CATEGORY J1A2
C***TYPE COMPLEX (RFFTI1-S, CFFTI1-C)
C***KEYWORDS FFTPACK, FOURIER TRANSFORM
C***AUTHOR Swarztrauber, P. N., (NCAR)
C***DESCRIPTION
C
C Subroutine CFFTI1 initializes the work arrays WA and IFAC which are
C used in both CFFTF1 and CFFTB1. The prime factorization of N and a
C tabulation of the trigonometric functions are computed and stored in
C IFAC and WA, respectively.
C
C Input Parameter
C
C N the length of the sequence to be transformed
C
C Output Parameters
C
C WA a real work array which must be dimensioned at least 2*N.
C
C IFAC an integer work array which must be dimensioned at least 15.
C
C The same work arrays can be used for both CFFTF1 and CFFTB1
C as long as N remains unchanged. Different WA and IFAC arrays
C are required for different values of N. The contents of
C WA and IFAC must not be changed between calls of CFFTF1 or
C CFFTB1.
C
C***REFERENCES P. N. Swarztrauber, Vectorizing the FFTs, in Parallel
C Computations (G. Rodrigue, ed.), Academic Press,
C 1982, pp. 51-83.
C***ROUTINES CALLED (NONE)
C***REVISION HISTORY (YYMMDD)
C 790601 DATE WRITTEN
C 830401 Modified to use SLATEC library source file format.
C 860115 Modified by Ron Boisvert to adhere to Fortran 77 by
C (a) changing dummy array size declarations (1) to (*),
C (b) changing references to intrinsic function FLOAT
C to REAL, and
C (c) changing definition of variable TPI by using
C FORTRAN intrinsic function ATAN instead of a DATA
C statement.
C 881128 Modified by Dick Valent to meet prologue standards.
C 890531 Changed all specific intrinsics to generic. (WRB)
C 891214 Prologue converted to Version 4.0 format. (BAB)
C 900131 Routine changed from subsidiary to user-callable. (WRB)
C 920501 Reformatted the REFERENCES section. (WRB)
C***END PROLOGUE CFFTI1
DIMENSION WA(*), IFAC(*), NTRYH(4)
SAVE NTRYH
DATA NTRYH(1),NTRYH(2),NTRYH(3),NTRYH(4)/3,4,2,5/
C***FIRST EXECUTABLE STATEMENT CFFTI1
NL = N
NF = 0
J = 0
101 J = J+1
IF (J-4) 102,102,103
102 NTRY = NTRYH(J)
GO TO 104
103 NTRY = NTRY+2
104 NQ = NL/NTRY
NR = NL-NTRY*NQ
IF (NR) 101,105,101
105 NF = NF+1
IFAC(NF+2) = NTRY
NL = NQ
IF (NTRY .NE. 2) GO TO 107
IF (NF .EQ. 1) GO TO 107
DO 106 I=2,NF
IB = NF-I+2
IFAC(IB+2) = IFAC(IB+1)
106 CONTINUE
IFAC(3) = 2
107 IF (NL .NE. 1) GO TO 104
IFAC(1) = N
IFAC(2) = NF
TPI = 8.*ATAN(1.)
ARGH = TPI/N
I = 2
L1 = 1
DO 110 K1=1,NF
IP = IFAC(K1+2)
LD = 0
L2 = L1*IP
IDO = N/L2
IDOT = IDO+IDO+2
IPM = IP-1
DO 109 J=1,IPM
I1 = I
WA(I-1) = 1.
WA(I) = 0.
LD = LD+L1
FI = 0.
ARGLD = LD*ARGH
DO 108 II=4,IDOT,2
I = I+2
FI = FI+1.
ARG = FI*ARGLD
WA(I-1) = COS(ARG)
WA(I) = SIN(ARG)
108 CONTINUE
IF (IP .LE. 5) GO TO 109
WA(I1-1) = WA(I-1)
WA(I1) = WA(I)
109 CONTINUE
L1 = L2
110 CONTINUE
RETURN
END