SUBROUTINE VRFFTB(M,N,R,RT,MDIMR,WSAVE) C***BEGIN PROLOGUE VRFFTB C***DATE WRITTEN 850801 (YYMMDD) C***REVISION DATE 900509 (YYMMDD) C***CATEGORY NO. J1A1 C***KEYWORDS FAST FOURIER TRANSFORM, REAL PERIODIC TRANSFORM, C FOURIER SYNTHESIS, BACKWARD TRANSFORM, MULTIPLE SEQUENCES C***AUTHOR SWEET, R.A. (NIST) AND LINDGREN, L.L. (NIST) C***PURPOSE Backward real periodic transform, M sequences. C***DESCRIPTION C C Subroutine VRFFTB computes the synthesis (backward transform) of a C number of real periodic sequences from their Fourier coefficients. C Specifically, for each set of independent Fourier coefficients C F(K), the corresponding real periodic sequence is computed. C C The array WSAVE which is used by subroutine VRFFTB must be C initialized by calling subroutine VRFFTI(N,WSAVE). C C C Input Parameters C C M the number of sets of coefficients. C C N the length of the sequences of coefficients to be C transformed. The method is most efficient when N is a C product of small primes, however n may be any positive C integer. C C R areal two-dimensional array of size MDIMX x N containing the C coefficients to be transformed. Each set of coefficients C F(K), K\0,1,..,N-1, is stored as a ROW of R. Specifically, C the I-th set of independent Fourier coefficients is stored C C R(I,1) = REAL( F(I,0) ), C C R(I,2*K) = REAL( F(I,K) ) C C R(I,2*K+1) = IMAG( F(I,K) ) C C for K = 1, 2, . . . , M-1, C C and, when N is even, C C R(I,N) = REAL( F(I,N/2) ). C C RT a real two-dimensional work array of size MDIMX x N. C C MDIMR the row (or first) dimension of the arrays R and RT exactly C as they appear in the calling program. This parameter is C used to specify the variable dimension of these arrays. C C WSAVE a real one-dimensional work array which must be dimensioned C at least N+15. The WSAVE array must be initialized by C calling subroutine VRFFTI. A different WSAVE array must be C used for each different value of N. This initialization does C not have to be repeated so long as N remains unchanged. The C same WSAVE array may be used by VRFFTB and VRFFTB. C C Output Parameters C C R contains M real periodic sequences corresponding to the given C coefficients. Specifically, the I-th row of R contains the C real periodic sequence corresponding to the I-th set of C independent Fourier coefficients F(I,K) stored as C C R(I,J) = X(I,J-1) , J = 1, 2, . . . , N, where C C X(I,J) = SQRT(1/N)* F(I,0) + (-1)**J*F(I,N/2) C + 2*SUM(K=1,M)[ REAL(F(I,2K))*COS(2K*J*PI/N) C - IMAG(F(I,2K+1))*SIN(2K*J*PI/N) ] , C C when N is even, and C C X(I,J) = SQRT(1/N)* F(I,0) + C 2*SUM(K=1,M)[ REAL(F(I,2K))*COS(2K*J*PI/N) C - IMAG(F(I,2K+1))*SIN(2K*J*PI/N) ] , C C when N is odd. C C WSAVE contains results which must not be destroyed between calls C to VRFFTF or VRFFTB. C C ----------------------------------------------------------------- C C NOTE - A call of VRFFTF followed immediately by a call of C of VRFFTB will return the original sequences R. Thus, C VRFFTB is the correctly normalized inverse of VRFFTF. C C ----------------------------------------------------------------- C C VRFFTB is a straightforward extension of the subprogram RFFTB to C handle M simultaneous sequences. RFFTB was originally developed C by P. N. Swarztrauber of NCAR. C C C * * * * * * * * * * * * * * * * * * * * * C * * C * PROGRAM SPECIFICATIONS * C * * C * * * * * * * * * * * * * * * * * * * * * C C C DIMENSION OF R(MDIMR,N), RT(MDIMR,N), WSAVE(N+15) C ARGUMENTS C C LATEST AUGUST 1, 1985 C REVISION C C SUBPROGRAMS VRFFTI, VRFTI1, VRFFTF, VRFTF1, VRADF2, VRADF3, C REQUIRED VRADF4, VRADF5, VRADFG, VRFFTB, VRFTB1, VRADB2, C VRADB3, VRADB4, VRADB5, VRADBG, PIMACH C C SPECIAL NONE C CONDITIONS C C COMMON NONE C BLOCKS C C I/O NONE C C PRECISION SINGLE C C SPECIALIST ROLAND SWEET C C LANGUAGE FORTRAN C C HISTORY WRITTEN BY LINDA LINDGREN AND ROLAND SWEET AT THE C NATIONAL BUREAU OF STANDARDS (BOULDER). C C ALGORITHM A REAL VARIANT OF THE STOCKHAM AUTOSORT VERSION C OF THE COOLEY-TUKEY FAST FOURIER TRANSFORM. C C PORTABILITY AMERICAN NATIONAL STANDARDS INSTITUTE FORTRAN 77. C THE ONLY MACHINE DEPENDENT CONSTANT IS LOCATED IN C THE FUNCTION PIMACH. C C REQUIRED COS,SIN C RESIDENT C ROUTINES C C C***REFERENCES P. N. Swarztrauber, Vectorizing the FFTs, in Parallel C Computations, (G. Rodrigue, ed.), Academic Press, 1982, C pp. 51-83. C***ROUTINES CALLED VRFTB1 C***END PROLOGUE VRFFTB C C VRFFTPK, VERSION 1, AUGUST 1985 C DIMENSION R(MDIMR,N),RT(MDIMR,N),WSAVE(N+15) IF (N .EQ. 1) RETURN CALL VRFTB1 (M,N,R,RT,MDIMR,WSAVE(1),WSAVE(N+1)) RETURN END