1*DECK DQAWSE
2      SUBROUTINE DQAWSE (F, A, B, ALFA, BETA, INTEGR, EPSABS, EPSREL,
3     +   LIMIT, RESULT, ABSERR, NEVAL, IER, ALIST, BLIST, RLIST, ELIST,
4     +   IORD, LAST)
5C***BEGIN PROLOGUE  DQAWSE
6C***PURPOSE  The routine calculates an approximation result to a given
7C            definite integral I = Integral of F*W over (A,B),
8C            (where W shows a singular behaviour at the end points,
9C            see parameter INTEGR).
10C            Hopefully satisfying following claim for accuracy
11C            ABS(I-RESULT).LE.MAX(EPSABS,EPSREL*ABS(I)).
12C***LIBRARY   SLATEC (QUADPACK)
13C***CATEGORY  H2A2A1
14C***TYPE      DOUBLE PRECISION (QAWSE-S, DQAWSE-D)
15C***KEYWORDS  ALGEBRAIC-LOGARITHMIC END POINT SINGULARITIES,
16C             AUTOMATIC INTEGRATOR, CLENSHAW-CURTIS METHOD, QUADPACK,
17C             QUADRATURE, SPECIAL-PURPOSE
18C***AUTHOR  Piessens, Robert
19C             Applied Mathematics and Programming Division
20C             K. U. Leuven
21C           de Doncker, Elise
22C             Applied Mathematics and Programming Division
23C             K. U. Leuven
24C***DESCRIPTION
25C
26C        Integration of functions having algebraico-logarithmic
27C        end point singularities
28C        Standard fortran subroutine
29C        Double precision version
30C
31C        PARAMETERS
32C         ON ENTRY
33C            F      - Double precision
34C                     Function subprogram defining the integrand
35C                     function F(X). The actual name for F needs to be
36C                     declared E X T E R N A L in the driver program.
37C
38C            A      - Double precision
39C                     Lower limit of integration
40C
41C            B      - Double precision
42C                     Upper limit of integration, B.GT.A
43C                     If B.LE.A, the routine will end with IER = 6.
44C
45C            ALFA   - Double precision
46C                     Parameter in the WEIGHT function, ALFA.GT.(-1)
47C                     If ALFA.LE.(-1), the routine will end with
48C                     IER = 6.
49C
50C            BETA   - Double precision
51C                     Parameter in the WEIGHT function, BETA.GT.(-1)
52C                     If BETA.LE.(-1), the routine will end with
53C                     IER = 6.
54C
55C            INTEGR - Integer
56C                     Indicates which WEIGHT function is to be used
57C                     = 1  (X-A)**ALFA*(B-X)**BETA
58C                     = 2  (X-A)**ALFA*(B-X)**BETA*LOG(X-A)
59C                     = 3  (X-A)**ALFA*(B-X)**BETA*LOG(B-X)
60C                     = 4  (X-A)**ALFA*(B-X)**BETA*LOG(X-A)*LOG(B-X)
61C                     If INTEGR.LT.1 or INTEGR.GT.4, the routine
62C                     will end with IER = 6.
63C
64C            EPSABS - Double precision
65C                     Absolute accuracy requested
66C            EPSREL - Double precision
67C                     Relative accuracy requested
68C                     If  EPSABS.LE.0
69C                     and EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
70C                     the routine will end with IER = 6.
71C
72C            LIMIT  - Integer
73C                     Gives an upper bound on the number of subintervals
74C                     in the partition of (A,B), LIMIT.GE.2
75C                     If LIMIT.LT.2, the routine will end with IER = 6.
76C
77C         ON RETURN
78C            RESULT - Double precision
79C                     Approximation to the integral
80C
81C            ABSERR - Double precision
82C                     Estimate of the modulus of the absolute error,
83C                     which should equal or exceed ABS(I-RESULT)
84C
85C            NEVAL  - Integer
86C                     Number of integrand evaluations
87C
88C            IER    - Integer
89C                     IER = 0 Normal and reliable termination of the
90C                             routine. It is assumed that the requested
91C                             accuracy has been achieved.
92C                     IER.GT.0 Abnormal termination of the routine
93C                             the estimates for the integral and error
94C                             are less reliable. It is assumed that the
95C                             requested accuracy has not been achieved.
96C            ERROR MESSAGES
97C                         = 1 Maximum number of subdivisions allowed
98C                             has been achieved. One can allow more
99C                             subdivisions by increasing the value of
100C                             LIMIT. However, if this yields no
101C                             improvement, it is advised to analyze the
102C                             integrand in order to determine the
103C                             integration difficulties which prevent the
104C                             requested tolerance from being achieved.
105C                             In case of a jump DISCONTINUITY or a local
106C                             SINGULARITY of algebraico-logarithmic type
107C                             at one or more interior points of the
108C                             integration range, one should proceed by
109C                             splitting up the interval at these
110C                             points and calling the integrator on the
111C                             subranges.
112C                         = 2 The occurrence of roundoff error is
113C                             detected, which prevents the requested
114C                             tolerance from being achieved.
115C                         = 3 Extremely bad integrand behaviour occurs
116C                             at some points of the integration
117C                             interval.
118C                         = 6 The input is invalid, because
119C                             B.LE.A or ALFA.LE.(-1) or BETA.LE.(-1), or
120C                             INTEGR.LT.1 or INTEGR.GT.4, or
121C                             (EPSABS.LE.0 and
122C                              EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
123C                             or LIMIT.LT.2.
124C                             RESULT, ABSERR, NEVAL, RLIST(1), ELIST(1),
125C                             IORD(1) and LAST are set to zero. ALIST(1)
126C                             and BLIST(1) are set to A and B
127C                             respectively.
128C
129C            ALIST  - Double precision
130C                     Vector of dimension at least LIMIT, the first
131C                      LAST  elements of which are the left
132C                     end points of the subintervals in the partition
133C                     of the given integration range (A,B)
134C
135C            BLIST  - Double precision
136C                     Vector of dimension at least LIMIT, the first
137C                      LAST  elements of which are the right
138C                     end points of the subintervals in the partition
139C                     of the given integration range (A,B)
140C
141C            RLIST  - Double precision
142C                     Vector of dimension at least LIMIT, the first
143C                      LAST  elements of which are the integral
144C                     approximations on the subintervals
145C
146C            ELIST  - Double precision
147C                     Vector of dimension at least LIMIT, the first
148C                      LAST  elements of which are the moduli of the
149C                     absolute error estimates on the subintervals
150C
151C            IORD   - Integer
152C                     Vector of dimension at least LIMIT, the first K
153C                     of which are pointers to the error
154C                     estimates over the subintervals, so that
155C                     ELIST(IORD(1)), ..., ELIST(IORD(K)) with K = LAST
156C                     If LAST.LE.(LIMIT/2+2), and K = LIMIT+1-LAST
157C                     otherwise form a decreasing sequence
158C
159C            LAST   - Integer
160C                     Number of subintervals actually produced in
161C                     the subdivision process
162C
163C***REFERENCES  (NONE)
164C***ROUTINES CALLED  D1MACH, DQC25S, DQMOMO, DQPSRT
165C***REVISION HISTORY  (YYMMDD)
166C   800101  DATE WRITTEN
167C   890531  Changed all specific intrinsics to generic.  (WRB)
168C   890831  Modified array declarations.  (WRB)
169C   890831  REVISION DATE from Version 3.2
170C   891214  Prologue converted to Version 4.0 format.  (BAB)
171C***END PROLOGUE  DQAWSE
172C
173      DOUBLE PRECISION A,ABSERR,ALFA,ALIST,AREA,AREA1,AREA12,AREA2,A1,
174     1  A2,B,BETA,BLIST,B1,B2,CENTRE,D1MACH,ELIST,EPMACH,
175     2  EPSABS,EPSREL,ERRBND,ERRMAX,ERROR1,ERRO12,ERROR2,ERRSUM,F,
176     3  RESAS1,RESAS2,RESULT,RG,RH,RI,RJ,RLIST,UFLOW
177      INTEGER IER,INTEGR,IORD,IROFF1,IROFF2,K,LAST,LIMIT,MAXERR,NEV,
178     1  NEVAL,NRMAX
179C
180      EXTERNAL F
181C
182      DIMENSION ALIST(*),BLIST(*),RLIST(*),ELIST(*),
183     1  IORD(*),RI(25),RJ(25),RH(25),RG(25)
184C
185C            LIST OF MAJOR VARIABLES
186C            -----------------------
187C
188C           ALIST     - LIST OF LEFT END POINTS OF ALL SUBINTERVALS
189C                       CONSIDERED UP TO NOW
190C           BLIST     - LIST OF RIGHT END POINTS OF ALL SUBINTERVALS
191C                       CONSIDERED UP TO NOW
192C           RLIST(I)  - APPROXIMATION TO THE INTEGRAL OVER
193C                       (ALIST(I),BLIST(I))
194C           ELIST(I)  - ERROR ESTIMATE APPLYING TO RLIST(I)
195C           MAXERR    - POINTER TO THE INTERVAL WITH LARGEST
196C                       ERROR ESTIMATE
197C           ERRMAX    - ELIST(MAXERR)
198C           AREA      - SUM OF THE INTEGRALS OVER THE SUBINTERVALS
199C           ERRSUM    - SUM OF THE ERRORS OVER THE SUBINTERVALS
200C           ERRBND    - REQUESTED ACCURACY MAX(EPSABS,EPSREL*
201C                       ABS(RESULT))
202C           *****1    - VARIABLE FOR THE LEFT SUBINTERVAL
203C           *****2    - VARIABLE FOR THE RIGHT SUBINTERVAL
204C           LAST      - INDEX FOR SUBDIVISION
205C
206C
207C            MACHINE DEPENDENT CONSTANTS
208C            ---------------------------
209C
210C           EPMACH IS THE LARGEST RELATIVE SPACING.
211C           UFLOW IS THE SMALLEST POSITIVE MAGNITUDE.
212C
213C***FIRST EXECUTABLE STATEMENT  DQAWSE
214      EPMACH = D1MACH(4)
215      UFLOW = D1MACH(1)
216C
217C           TEST ON VALIDITY OF PARAMETERS
218C           ------------------------------
219C
220      IER = 6
221      NEVAL = 0
222      LAST = 0
223      RLIST(1) = 0.0D+00
224      ELIST(1) = 0.0D+00
225      IORD(1) = 0
226      RESULT = 0.0D+00
227      ABSERR = 0.0D+00
228      IF (B.LE.A.OR.(EPSABS.EQ.0.0D+00.AND.
229     1    EPSREL.LT.MAX(0.5D+02*EPMACH,0.5D-28)).OR.ALFA.LE.(-0.1D+01)
230     2    .OR.BETA.LE.(-0.1D+01).OR.INTEGR.LT.1.OR.INTEGR.GT.4.OR.
231     3    LIMIT.LT.2) GO TO 999
232      IER = 0
233C
234C           COMPUTE THE MODIFIED CHEBYSHEV MOMENTS.
235C
236      CALL DQMOMO(ALFA,BETA,RI,RJ,RG,RH,INTEGR)
237C
238C           INTEGRATE OVER THE INTERVALS (A,(A+B)/2) AND ((A+B)/2,B).
239C
240      CENTRE = 0.5D+00*(B+A)
241      CALL DQC25S(F,A,B,A,CENTRE,ALFA,BETA,RI,RJ,RG,RH,AREA1,
242     1  ERROR1,RESAS1,INTEGR,NEV)
243      NEVAL = NEV
244      CALL DQC25S(F,A,B,CENTRE,B,ALFA,BETA,RI,RJ,RG,RH,AREA2,
245     1  ERROR2,RESAS2,INTEGR,NEV)
246      LAST = 2
247      NEVAL = NEVAL+NEV
248      RESULT = AREA1+AREA2
249      ABSERR = ERROR1+ERROR2
250C
251C           TEST ON ACCURACY.
252C
253      ERRBND = MAX(EPSABS,EPSREL*ABS(RESULT))
254C
255C           INITIALIZATION
256C           --------------
257C
258      IF(ERROR2.GT.ERROR1) GO TO 10
259      ALIST(1) = A
260      ALIST(2) = CENTRE
261      BLIST(1) = CENTRE
262      BLIST(2) = B
263      RLIST(1) = AREA1
264      RLIST(2) = AREA2
265      ELIST(1) = ERROR1
266      ELIST(2) = ERROR2
267      GO TO 20
268   10 ALIST(1) = CENTRE
269      ALIST(2) = A
270      BLIST(1) = B
271      BLIST(2) = CENTRE
272      RLIST(1) = AREA2
273      RLIST(2) = AREA1
274      ELIST(1) = ERROR2
275      ELIST(2) = ERROR1
276   20 IORD(1) = 1
277      IORD(2) = 2
278      IF(LIMIT.EQ.2) IER = 1
279      IF(ABSERR.LE.ERRBND.OR.IER.EQ.1) GO TO 999
280      ERRMAX = ELIST(1)
281      MAXERR = 1
282      NRMAX = 1
283      AREA = RESULT
284      ERRSUM = ABSERR
285      IROFF1 = 0
286      IROFF2 = 0
287C
288C            MAIN DO-LOOP
289C            ------------
290C
291      DO 60 LAST = 3,LIMIT
292C
293C           BISECT THE SUBINTERVAL WITH LARGEST ERROR ESTIMATE.
294C
295        A1 = ALIST(MAXERR)
296        B1 = 0.5D+00*(ALIST(MAXERR)+BLIST(MAXERR))
297        A2 = B1
298        B2 = BLIST(MAXERR)
299C
300        CALL DQC25S(F,A,B,A1,B1,ALFA,BETA,RI,RJ,RG,RH,AREA1,
301     1  ERROR1,RESAS1,INTEGR,NEV)
302        NEVAL = NEVAL+NEV
303        CALL DQC25S(F,A,B,A2,B2,ALFA,BETA,RI,RJ,RG,RH,AREA2,
304     1  ERROR2,RESAS2,INTEGR,NEV)
305        NEVAL = NEVAL+NEV
306C
307C           IMPROVE PREVIOUS APPROXIMATIONS INTEGRAL AND ERROR
308C           AND TEST FOR ACCURACY.
309C
310        AREA12 = AREA1+AREA2
311        ERRO12 = ERROR1+ERROR2
312        ERRSUM = ERRSUM+ERRO12-ERRMAX
313        AREA = AREA+AREA12-RLIST(MAXERR)
314        IF(A.EQ.A1.OR.B.EQ.B2) GO TO 30
315        IF(RESAS1.EQ.ERROR1.OR.RESAS2.EQ.ERROR2) GO TO 30
316C
317C           TEST FOR ROUNDOFF ERROR.
318C
319        IF(ABS(RLIST(MAXERR)-AREA12).LT.0.1D-04*ABS(AREA12)
320     1  .AND.ERRO12.GE.0.99D+00*ERRMAX) IROFF1 = IROFF1+1
321        IF(LAST.GT.10.AND.ERRO12.GT.ERRMAX) IROFF2 = IROFF2+1
322   30   RLIST(MAXERR) = AREA1
323        RLIST(LAST) = AREA2
324C
325C           TEST ON ACCURACY.
326C
327        ERRBND = MAX(EPSABS,EPSREL*ABS(AREA))
328        IF(ERRSUM.LE.ERRBND) GO TO 35
329C
330C           SET ERROR FLAG IN THE CASE THAT THE NUMBER OF INTERVAL
331C           BISECTIONS EXCEEDS LIMIT.
332C
333        IF(LAST.EQ.LIMIT) IER = 1
334C
335C
336C           SET ERROR FLAG IN THE CASE OF ROUNDOFF ERROR.
337C
338        IF(IROFF1.GE.6.OR.IROFF2.GE.20) IER = 2
339C
340C           SET ERROR FLAG IN THE CASE OF BAD INTEGRAND BEHAVIOUR
341C           AT INTERIOR POINTS OF INTEGRATION RANGE.
342C
343        IF(MAX(ABS(A1),ABS(B2)).LE.(0.1D+01+0.1D+03*EPMACH)*
344     1  (ABS(A2)+0.1D+04*UFLOW)) IER = 3
345C
346C           APPEND THE NEWLY-CREATED INTERVALS TO THE LIST.
347C
348   35   IF(ERROR2.GT.ERROR1) GO TO 40
349        ALIST(LAST) = A2
350        BLIST(MAXERR) = B1
351        BLIST(LAST) = B2
352        ELIST(MAXERR) = ERROR1
353        ELIST(LAST) = ERROR2
354        GO TO 50
355   40   ALIST(MAXERR) = A2
356        ALIST(LAST) = A1
357        BLIST(LAST) = B1
358        RLIST(MAXERR) = AREA2
359        RLIST(LAST) = AREA1
360        ELIST(MAXERR) = ERROR2
361        ELIST(LAST) = ERROR1
362C
363C           CALL SUBROUTINE DQPSRT TO MAINTAIN THE DESCENDING ORDERING
364C           IN THE LIST OF ERROR ESTIMATES AND SELECT THE SUBINTERVAL
365C           WITH LARGEST ERROR ESTIMATE (TO BE BISECTED NEXT).
366C
367   50   CALL DQPSRT(LIMIT,LAST,MAXERR,ERRMAX,ELIST,IORD,NRMAX)
368C ***JUMP OUT OF DO-LOOP
369        IF (IER.NE.0.OR.ERRSUM.LE.ERRBND) GO TO 70
370   60 CONTINUE
371C
372C           COMPUTE FINAL RESULT.
373C           ---------------------
374C
375   70 RESULT = 0.0D+00
376      DO 80 K=1,LAST
377        RESULT = RESULT+RLIST(K)
378   80 CONTINUE
379      ABSERR = ERRSUM
380  999 RETURN
381      END
382