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

« back to all changes in this revision

Viewing changes to deps/openlibm/slatec/dqaws.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 DQAWS
 
2
      SUBROUTINE DQAWS (F, A, B, ALFA, BETA, INTEGR, EPSABS, EPSREL,
 
3
     +   RESULT, ABSERR, NEVAL, IER, LIMIT, LENW, LAST, IWORK, WORK)
 
4
C***BEGIN PROLOGUE  DQAWS
 
5
C***PURPOSE  The routine calculates an approximation result to a given
 
6
C            definite integral I = Integral of F*W over (A,B),
 
7
C            (where W shows a singular behaviour at the end points
 
8
C            see parameter INTEGR).
 
9
C            Hopefully satisfying following claim for accuracy
 
10
C            ABS(I-RESULT).LE.MAX(EPSABS,EPSREL*ABS(I)).
 
11
C***LIBRARY   SLATEC (QUADPACK)
 
12
C***CATEGORY  H2A2A1
 
13
C***TYPE      DOUBLE PRECISION (QAWS-S, DQAWS-D)
 
14
C***KEYWORDS  ALGEBRAIC-LOGARITHMIC END POINT SINGULARITIES,
 
15
C             AUTOMATIC INTEGRATOR, CLENSHAW-CURTIS METHOD,
 
16
C             GLOBALLY ADAPTIVE, QUADPACK, QUADRATURE, SPECIAL-PURPOSE
 
17
C***AUTHOR  Piessens, Robert
 
18
C             Applied Mathematics and Programming Division
 
19
C             K. U. Leuven
 
20
C           de Doncker, Elise
 
21
C             Applied Mathematics and Programming Division
 
22
C             K. U. Leuven
 
23
C***DESCRIPTION
 
24
C
 
25
C        Integration of functions having algebraico-logarithmic
 
26
C        end point singularities
 
27
C        Standard fortran subroutine
 
28
C        Double precision version
 
29
C
 
30
C        PARAMETERS
 
31
C         ON ENTRY
 
32
C            F      - Double precision
 
33
C                     Function subprogram defining the integrand
 
34
C                     function F(X). The actual name for F needs to be
 
35
C                     declared E X T E R N A L in the driver program.
 
36
C
 
37
C            A      - Double precision
 
38
C                     Lower limit of integration
 
39
C
 
40
C            B      - Double precision
 
41
C                     Upper limit of integration, B.GT.A
 
42
C                     If B.LE.A, the routine will end with IER = 6.
 
43
C
 
44
C            ALFA   - Double precision
 
45
C                     Parameter in the integrand function, ALFA.GT.(-1)
 
46
C                     If ALFA.LE.(-1), the routine will end with
 
47
C                     IER = 6.
 
48
C
 
49
C            BETA   - Double precision
 
50
C                     Parameter in the integrand function, BETA.GT.(-1)
 
51
C                     If BETA.LE.(-1), the routine will end with
 
52
C                     IER = 6.
 
53
C
 
54
C            INTEGR - Integer
 
55
C                     Indicates which WEIGHT function is to be used
 
56
C                     = 1  (X-A)**ALFA*(B-X)**BETA
 
57
C                     = 2  (X-A)**ALFA*(B-X)**BETA*LOG(X-A)
 
58
C                     = 3  (X-A)**ALFA*(B-X)**BETA*LOG(B-X)
 
59
C                     = 4  (X-A)**ALFA*(B-X)**BETA*LOG(X-A)*LOG(B-X)
 
60
C                     If INTEGR.LT.1 or INTEGR.GT.4, the routine
 
61
C                     will end with IER = 6.
 
62
C
 
63
C            EPSABS - Double precision
 
64
C                     Absolute accuracy requested
 
65
C            EPSREL - Double precision
 
66
C                     Relative accuracy requested
 
67
C                     If  EPSABS.LE.0
 
68
C                     and EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
 
69
C                     the routine will end with IER = 6.
 
70
C
 
71
C         ON RETURN
 
72
C            RESULT - Double precision
 
73
C                     Approximation to the integral
 
74
C
 
75
C            ABSERR - Double precision
 
76
C                     Estimate of the modulus of the absolute error,
 
77
C                     Which should equal or exceed ABS(I-RESULT)
 
78
C
 
79
C            NEVAL  - Integer
 
80
C                     Number of integrand evaluations
 
81
C
 
82
C            IER    - Integer
 
83
C                     IER = 0 Normal and reliable termination of the
 
84
C                             routine. It is assumed that the requested
 
85
C                             accuracy has been achieved.
 
86
C                     IER.GT.0 Abnormal termination of the routine
 
87
C                             The estimates for the integral and error
 
88
C                             are less reliable. It is assumed that the
 
89
C                             requested accuracy has not been achieved.
 
90
C            ERROR MESSAGES
 
91
C                     IER = 1 Maximum number of subdivisions allowed
 
92
C                             has been achieved. One can allow more
 
93
C                             subdivisions by increasing the value of
 
94
C                             LIMIT (and taking the according dimension
 
95
C                             adjustments into account). However, if
 
96
C                             this yields no improvement it is advised
 
97
C                             to analyze the integrand, in order to
 
98
C                             determine the integration difficulties
 
99
C                             which prevent the requested tolerance from
 
100
C                             being achieved. In case of a jump
 
101
C                             discontinuity or a local singularity
 
102
C                             of algebraico-logarithmic type at one or
 
103
C                             more interior points of the integration
 
104
C                             range, one should proceed by splitting up
 
105
C                             the interval at these points and calling
 
106
C                             the integrator on the subranges.
 
107
C                         = 2 The occurrence of roundoff error is
 
108
C                             detected, which prevents the requested
 
109
C                             tolerance from being achieved.
 
110
C                         = 3 Extremely bad integrand behaviour occurs
 
111
C                             at some points of the integration
 
112
C                             interval.
 
113
C                         = 6 The input is invalid, because
 
114
C                             B.LE.A or ALFA.LE.(-1) or BETA.LE.(-1) or
 
115
C                             or INTEGR.LT.1 or INTEGR.GT.4 or
 
116
C                             (EPSABS.LE.0 and
 
117
C                              EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28))
 
118
C                             or LIMIT.LT.2 or LENW.LT.LIMIT*4.
 
119
C                             RESULT, ABSERR, NEVAL, LAST are set to
 
120
C                             zero. Except when LENW or LIMIT is invalid
 
121
C                             IWORK(1), WORK(LIMIT*2+1) and
 
122
C                             WORK(LIMIT*3+1) are set to zero, WORK(1)
 
123
C                             is set to A and WORK(LIMIT+1) to B.
 
124
C
 
125
C         DIMENSIONING PARAMETERS
 
126
C            LIMIT  - Integer
 
127
C                     Dimensioning parameter for IWORK
 
128
C                     LIMIT determines the maximum number of
 
129
C                     subintervals in the partition of the given
 
130
C                     integration interval (A,B), LIMIT.GE.2.
 
131
C                     If LIMIT.LT.2, the routine will end with IER = 6.
 
132
C
 
133
C            LENW   - Integer
 
134
C                     Dimensioning parameter for WORK
 
135
C                     LENW must be at least LIMIT*4.
 
136
C                     If LENW.LT.LIMIT*4, the routine will end
 
137
C                     with IER = 6.
 
138
C
 
139
C            LAST   - Integer
 
140
C                     On return, LAST equals the number of
 
141
C                     subintervals produced in the subdivision process,
 
142
C                     which determines the significant number of
 
143
C                     elements actually in the WORK ARRAYS.
 
144
C
 
145
C         WORK ARRAYS
 
146
C            IWORK  - Integer
 
147
C                     Vector of dimension LIMIT, the first K
 
148
C                     elements of which contain pointers
 
149
C                     to the error estimates over the subintervals,
 
150
C                     such that WORK(LIMIT*3+IWORK(1)), ...,
 
151
C                     WORK(LIMIT*3+IWORK(K)) form a decreasing
 
152
C                     sequence with K = LAST if LAST.LE.(LIMIT/2+2),
 
153
C                     and K = LIMIT+1-LAST otherwise
 
154
C
 
155
C            WORK   - Double precision
 
156
C                     Vector of dimension LENW
 
157
C                     On return
 
158
C                     WORK(1), ..., WORK(LAST) contain the left
 
159
C                      end points of the subintervals in the
 
160
C                      partition of (A,B),
 
161
C                     WORK(LIMIT+1), ..., WORK(LIMIT+LAST) contain
 
162
C                      the right end points,
 
163
C                     WORK(LIMIT*2+1), ..., WORK(LIMIT*2+LAST)
 
164
C                      contain the integral approximations over
 
165
C                      the subintervals,
 
166
C                     WORK(LIMIT*3+1), ..., WORK(LIMIT*3+LAST)
 
167
C                      contain the error estimates.
 
168
C
 
169
C***REFERENCES  (NONE)
 
170
C***ROUTINES CALLED  DQAWSE, XERMSG
 
171
C***REVISION HISTORY  (YYMMDD)
 
172
C   800101  DATE WRITTEN
 
173
C   890831  Modified array declarations.  (WRB)
 
174
C   890831  REVISION DATE from Version 3.2
 
175
C   891214  Prologue converted to Version 4.0 format.  (BAB)
 
176
C   900315  CALLs to XERROR changed to CALLs to XERMSG.  (THJ)
 
177
C***END PROLOGUE  DQAWS
 
178
C
 
179
      DOUBLE PRECISION A,ABSERR,ALFA,B,BETA,EPSABS,EPSREL,F,RESULT,WORK
 
180
      INTEGER IER,INTEGR,IWORK,LAST,LENW,LIMIT,LVL,L1,L2,L3,NEVAL
 
181
C
 
182
      DIMENSION IWORK(*),WORK(*)
 
183
C
 
184
      EXTERNAL F
 
185
C
 
186
C         CHECK VALIDITY OF LIMIT AND LENW.
 
187
C
 
188
C***FIRST EXECUTABLE STATEMENT  DQAWS
 
189
      IER = 6
 
190
      NEVAL = 0
 
191
      LAST = 0
 
192
      RESULT = 0.0D+00
 
193
      ABSERR = 0.0D+00
 
194
      IF(LIMIT.LT.2.OR.LENW.LT.LIMIT*4) GO TO 10
 
195
C
 
196
C         PREPARE CALL FOR DQAWSE.
 
197
C
 
198
      L1 = LIMIT+1
 
199
      L2 = LIMIT+L1
 
200
      L3 = LIMIT+L2
 
201
C
 
202
      CALL DQAWSE(F,A,B,ALFA,BETA,INTEGR,EPSABS,EPSREL,LIMIT,RESULT,
 
203
     1  ABSERR,NEVAL,IER,WORK(1),WORK(L1),WORK(L2),WORK(L3),IWORK,LAST)
 
204
C
 
205
C         CALL ERROR HANDLER IF NECESSARY.
 
206
C
 
207
      LVL = 0
 
208
10    IF(IER.EQ.6) LVL = 1
 
209
      IF (IER .NE. 0) CALL XERMSG ('SLATEC', 'DQAWS',
 
210
     +   'ABNORMAL RETURN', IER, LVL)
 
211
      RETURN
 
212
      END