~ubuntu-branches/ubuntu/wily/julia/wily

« back to all changes in this revision

Viewing changes to deps/openlibm/slatec/ezfftb.f

  • Committer: Package Import Robot
  • Author(s): Sébastien Villemot
  • Date: 2013-01-16 12:29:42 UTC
  • mfrom: (1.1.2)
  • Revision ID: package-import@ubuntu.com-20130116122942-x86e42akjq31repw
Tags: 0.0.0+20130107.gitd9656f41-1
* New upstream snashot
* No longer try to rebuild helpdb.jl.
   + debian/rules: remove helpdb.jl from build-arch rule
   + debian/control: move back python-sphinx to Build-Depends-Indep
* debian/copyright: reflect upstream changes
* Add Build-Conflicts on libatlas3-base (makes linalg tests fail)
* debian/rules: replace obsolete USE_DEBIAN makeflag by a list of
  USE_SYSTEM_* flags
* debian/rules: on non-x86 systems, use libm instead of openlibm
* dpkg-buildflags.patch: remove patch, applied upstream
* Refreshed other patches

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
*DECK EZFFTB
 
2
      SUBROUTINE EZFFTB (N, R, AZERO, A, B, WSAVE)
 
3
C***BEGIN PROLOGUE  EZFFTB
 
4
C***PURPOSE  A simplified real, periodic, backward fast Fourier
 
5
C            transform.
 
6
C***LIBRARY   SLATEC (FFTPACK)
 
7
C***CATEGORY  J1A1
 
8
C***TYPE      SINGLE PRECISION (EZFFTB-S)
 
9
C***KEYWORDS  FFTPACK, FOURIER TRANSFORM
 
10
C***AUTHOR  Swarztrauber, P. N., (NCAR)
 
11
C***DESCRIPTION
 
12
C
 
13
C  Subroutine EZFFTB computes a real periodic sequence from its
 
14
C  Fourier coefficients (Fourier synthesis).  The transform is
 
15
C  defined below at Output Parameter R.  EZFFTB is a simplified
 
16
C  but slower version of RFFTB.
 
17
C
 
18
C  Input Parameters
 
19
C
 
20
C  N       the length of the output array R.  The method is most
 
21
C          efficient when N is the product of small primes.
 
22
C
 
23
C  AZERO   the constant Fourier coefficient
 
24
C
 
25
C  A,B     arrays which contain the remaining Fourier coefficients.
 
26
C          These arrays are not destroyed.
 
27
C
 
28
C          The length of these arrays depends on whether N is even or
 
29
C          odd.
 
30
C
 
31
C          If N is even, N/2    locations are required.
 
32
C          If N is odd, (N-1)/2 locations are required
 
33
C
 
34
C  WSAVE   a work array which must be dimensioned at least 3*N+15
 
35
C          in the program that calls EZFFTB.  The WSAVE array must be
 
36
C          initialized by calling subroutine EZFFTI(N,WSAVE), and a
 
37
C          different WSAVE array must be used for each different
 
38
C          value of N.  This initialization does not have to be
 
39
C          repeated so long as N remains unchanged.  Thus subsequent
 
40
C          transforms can be obtained faster than the first.
 
41
C          The same WSAVE array can be used by EZFFTF and EZFFTB.
 
42
C
 
43
C  Output Parameters
 
44
C
 
45
C  R       if N is even, define KMAX=N/2
 
46
C          if N is odd,  define KMAX=(N-1)/2
 
47
C
 
48
C          Then for I=1,...,N
 
49
C
 
50
C               R(I)=AZERO plus the sum from K=1 to K=KMAX of
 
51
C
 
52
C               A(K)*COS(K*(I-1)*2*PI/N)+B(K)*SIN(K*(I-1)*2*PI/N)
 
53
C
 
54
C  ********************* Complex Notation **************************
 
55
C
 
56
C          For J=1,...,N
 
57
C
 
58
C          R(J) equals the sum from K=-KMAX to K=KMAX of
 
59
C
 
60
C               C(K)*EXP(I*K*(J-1)*2*PI/N)
 
61
C
 
62
C          where
 
63
C
 
64
C               C(K) = .5*CMPLX(A(K),-B(K))   for K=1,...,KMAX
 
65
C
 
66
C               C(-K) = CONJG(C(K))
 
67
C
 
68
C               C(0) = AZERO
 
69
C
 
70
C                    and I=SQRT(-1)
 
71
C
 
72
C  *************** Amplitude - Phase Notation ***********************
 
73
C
 
74
C          For I=1,...,N
 
75
C
 
76
C          R(I) equals AZERO plus the sum from K=1 to K=KMAX of
 
77
C
 
78
C               ALPHA(K)*COS(K*(I-1)*2*PI/N+BETA(K))
 
79
C
 
80
C          where
 
81
C
 
82
C               ALPHA(K) = SQRT(A(K)*A(K)+B(K)*B(K))
 
83
C
 
84
C               COS(BETA(K))=A(K)/ALPHA(K)
 
85
C
 
86
C               SIN(BETA(K))=-B(K)/ALPHA(K)
 
87
C
 
88
C***REFERENCES  P. N. Swarztrauber, Vectorizing the FFTs, in Parallel
 
89
C                 Computations (G. Rodrigue, ed.), Academic Press,
 
90
C                 1982, pp. 51-83.
 
91
C***ROUTINES CALLED  RFFTB
 
92
C***REVISION HISTORY  (YYMMDD)
 
93
C   790601  DATE WRITTEN
 
94
C   830401  Modified to use SLATEC library source file format.
 
95
C   860115  Modified by Ron Boisvert to adhere to Fortran 77 by
 
96
C           changing dummy array size declarations (1) to (*)
 
97
C   861211  REVISION DATE from Version 3.2
 
98
C   881128  Modified by Dick Valent to meet prologue standards.
 
99
C   891214  Prologue converted to Version 4.0 format.  (BAB)
 
100
C   920501  Reformatted the REFERENCES section.  (WRB)
 
101
C***END PROLOGUE  EZFFTB
 
102
      DIMENSION R(*), A(*), B(*), WSAVE(*)
 
103
C***FIRST EXECUTABLE STATEMENT  EZFFTB
 
104
      IF (N-2) 101,102,103
 
105
  101 R(1) = AZERO
 
106
      RETURN
 
107
  102 R(1) = AZERO+A(1)
 
108
      R(2) = AZERO-A(1)
 
109
      RETURN
 
110
  103 NS2 = (N-1)/2
 
111
      DO 104 I=1,NS2
 
112
         R(2*I) = .5*A(I)
 
113
         R(2*I+1) = -.5*B(I)
 
114
  104 CONTINUE
 
115
      R(1) = AZERO
 
116
      IF (MOD(N,2) .EQ. 0) R(N) = A(NS2+1)
 
117
      CALL RFFTB (N,R,WSAVE(N+1))
 
118
      RETURN
 
119
      END