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

55 lines
1.9 KiB
Fortran

*DECK COSQF1
SUBROUTINE COSQF1 (N, X, W, XH)
C***BEGIN PROLOGUE COSQF1
C***SUBSIDIARY
C***PURPOSE Compute the forward cosine transform with odd wave numbers.
C***LIBRARY SLATEC (FFTPACK)
C***CATEGORY J1A3
C***TYPE SINGLE PRECISION (COSQF1-S)
C***KEYWORDS FFTPACK, FOURIER TRANSFORM
C***AUTHOR Swarztrauber, P. N., (NCAR)
C***DESCRIPTION
C
C Subroutine COSQF1 computes the fast Fourier transform of quarter
C wave data. That is, COSQF1 computes the coefficients in a cosine
C series representation with only odd wave numbers. The transform
C is defined below at Output Parameter X
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 RFFTF
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 changing dummy array size declarations (1) to (*).
C 881128 Modified by Dick Valent to meet prologue standards.
C 891214 Prologue converted to Version 4.0 format. (BAB)
C 920501 Reformatted the REFERENCES section. (WRB)
C***END PROLOGUE COSQF1
DIMENSION X(*), W(*), XH(*)
C***FIRST EXECUTABLE STATEMENT COSQF1
NS2 = (N+1)/2
NP2 = N+2
DO 101 K=2,NS2
KC = NP2-K
XH(K) = X(K)+X(KC)
XH(KC) = X(K)-X(KC)
101 CONTINUE
MODN = MOD(N,2)
IF (MODN .EQ. 0) XH(NS2+1) = X(NS2+1)+X(NS2+1)
DO 102 K=2,NS2
KC = NP2-K
X(K) = W(K-1)*XH(KC)+W(KC-1)*XH(K)
X(KC) = W(K-1)*XH(K)-W(KC-1)*XH(KC)
102 CONTINUE
IF (MODN .EQ. 0) X(NS2+1) = W(NS2)*XH(NS2+1)
CALL RFFTF (N,X,XH)
DO 103 I=3,N,2
XIM1 = X(I-1)-X(I)
X(I) = X(I-1)+X(I)
X(I-1) = XIM1
103 CONTINUE
RETURN
END