~ubuntu-branches/ubuntu/lucid/pdl/lucid

« back to all changes in this revision

Viewing changes to Lib/Slatec/slatec/ezfftf.f

  • Committer: Bazaar Package Importer
  • Author(s): Ben Gertzfield
  • Date: 2002-04-08 18:47:16 UTC
  • Revision ID: james.westby@ubuntu.com-20020408184716-0hf64dc96kin3htp
Tags: upstream-2.3.2
ImportĀ upstreamĀ versionĀ 2.3.2

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
*DECK EZFFTF
 
2
      SUBROUTINE EZFFTF (N, R, AZERO, A, B, WSAVE)
 
3
C***BEGIN PROLOGUE  EZFFTF
 
4
C***PURPOSE  Compute a simplified real, periodic, fast Fourier forward
 
5
C            transform.
 
6
C***LIBRARY   SLATEC (FFTPACK)
 
7
C***CATEGORY  J1A1
 
8
C***TYPE      SINGLE PRECISION (EZFFTF-S)
 
9
C***KEYWORDS  FFTPACK, FOURIER TRANSFORM
 
10
C***AUTHOR  Swarztrauber, P. N., (NCAR)
 
11
C***DESCRIPTION
 
12
C
 
13
C  Subroutine EZFFTF computes the Fourier coefficients of a real
 
14
C  periodic sequence (Fourier analysis).  The transform is defined
 
15
C  below at Output Parameters AZERO, A and B.  EZFFTF is a simplified
 
16
C  but slower version of RFFTF.
 
17
C
 
18
C  Input Parameters
 
19
C
 
20
C  N       the length of the array R to be transformed.  The method
 
21
C          is most efficient when N is the product of small primes.
 
22
C
 
23
C  R       a real array of length N which contains the sequence
 
24
C          to be transformed.  R is not destroyed.
 
25
C
 
26
C
 
27
C  WSAVE   a work array which must be dimensioned at least 3*N+15
 
28
C          in the program that calls EZFFTF.  The WSAVE array must be
 
29
C          initialized by calling subroutine EZFFTI(N,WSAVE), and a
 
30
C          different WSAVE array must be used for each different
 
31
C          value of N.  This initialization does not have to be
 
32
C          repeated so long as N remains unchanged.  Thus subsequent
 
33
C          transforms can be obtained faster than the first.
 
34
C          The same WSAVE array can be used by EZFFTF and EZFFTB.
 
35
C
 
36
C  Output Parameters
 
37
C
 
38
C  AZERO   the sum from I=1 to I=N of R(I)/N
 
39
C
 
40
C  A,B     for N even B(N/2)=0. and A(N/2) is the sum from I=1 to
 
41
C          I=N of (-1)**(I-1)*R(I)/N
 
42
C
 
43
C          for N even define KMAX=N/2-1
 
44
C          for N odd  define KMAX=(N-1)/2
 
45
C
 
46
C          then for  K=1,...,KMAX
 
47
C
 
48
C               A(K) equals the sum from I=1 to I=N of
 
49
C
 
50
C                    2./N*R(I)*COS(K*(I-1)*2*PI/N)
 
51
C
 
52
C               B(K) equals the sum from I=1 to I=N of
 
53
C
 
54
C                    2./N*R(I)*SIN(K*(I-1)*2*PI/N)
 
55
C
 
56
C***REFERENCES  P. N. Swarztrauber, Vectorizing the FFTs, in Parallel
 
57
C                 Computations (G. Rodrigue, ed.), Academic Press,
 
58
C                 1982, pp. 51-83.
 
59
C***ROUTINES CALLED  RFFTF
 
60
C***REVISION HISTORY  (YYMMDD)
 
61
C   790601  DATE WRITTEN
 
62
C   830401  Modified to use SLATEC library source file format.
 
63
C   860115  Modified by Ron Boisvert to adhere to Fortran 77 by
 
64
C           (a) changing dummy array size declarations (1) to (*),
 
65
C           (b) changing references to intrinsic function FLOAT
 
66
C               to REAL.
 
67
C   881128  Modified by Dick Valent to meet prologue standards.
 
68
C   890531  Changed all specific intrinsics to generic.  (WRB)
 
69
C   890531  REVISION DATE from Version 3.2
 
70
C   891214  Prologue converted to Version 4.0 format.  (BAB)
 
71
C   920501  Reformatted the REFERENCES section.  (WRB)
 
72
C***END PROLOGUE  EZFFTF
 
73
      DIMENSION R(*), A(*), B(*), WSAVE(*)
 
74
C***FIRST EXECUTABLE STATEMENT  EZFFTF
 
75
      IF (N-2) 101,102,103
 
76
  101 AZERO = R(1)
 
77
      RETURN
 
78
  102 AZERO = .5*(R(1)+R(2))
 
79
      A(1) = .5*(R(1)-R(2))
 
80
      RETURN
 
81
  103 DO 104 I=1,N
 
82
         WSAVE(I) = R(I)
 
83
  104 CONTINUE
 
84
      CALL RFFTF (N,WSAVE,WSAVE(N+1))
 
85
      CF = 2./N
 
86
      CFM = -CF
 
87
      AZERO = .5*CF*WSAVE(1)
 
88
      NS2 = (N+1)/2
 
89
      NS2M = NS2-1
 
90
      DO 105 I=1,NS2M
 
91
         A(I) = CF*WSAVE(2*I)
 
92
         B(I) = CFM*WSAVE(2*I+1)
 
93
  105 CONTINUE
 
94
      IF (MOD(N,2) .EQ. 0) A(NS2) = .5*CF*WSAVE(N)
 
95
      RETURN
 
96
      END