2
SUBROUTINE DQAGPE (F, A, B, NPTS2, POINTS, EPSABS, EPSREL, LIMIT,
3
+ RESULT, ABSERR, NEVAL, IER, ALIST, BLIST, RLIST, ELIST, PTS,
4
+ IORD, LEVEL, NDIN, LAST)
5
C***BEGIN PROLOGUE DQAGPE
6
C***PURPOSE Approximate a given definite integral I = Integral of F
7
C over (A,B), hopefully satisfying the accuracy claim:
8
C ABS(I-RESULT).LE.MAX(EPSABS,EPSREL*ABS(I)).
9
C Break points of the integration interval, where local
10
C difficulties of the integrand may occur (e.g. singularities
11
C or discontinuities) are provided by the user.
12
C***LIBRARY SLATEC (QUADPACK)
14
C***TYPE DOUBLE PRECISION (QAGPE-S, DQAGPE-D)
15
C***KEYWORDS AUTOMATIC INTEGRATOR, EXTRAPOLATION, GENERAL-PURPOSE,
16
C GLOBALLY ADAPTIVE, QUADPACK, QUADRATURE,
17
C SINGULARITIES AT USER SPECIFIED POINTS
18
C***AUTHOR Piessens, Robert
19
C Applied Mathematics and Programming Division
22
C Applied Mathematics and Programming Division
26
C Computation of a definite integral
27
C Standard fortran subroutine
28
C Double precision version
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.
37
C A - Double precision
38
C Lower limit of integration
40
C B - Double precision
41
C Upper limit of integration
44
C Number equal to two more than the number of
45
C user-supplied break points within the integration
47
C If NPTS2.LT.2, the routine will end with IER = 6.
49
C POINTS - Double precision
50
C Vector of dimension NPTS2, the first (NPTS2-2)
51
C elements of which are the user provided break
52
C POINTS. If these POINTS do not constitute an
53
C ascending sequence there will be an automatic
56
C EPSABS - Double precision
57
C Absolute accuracy requested
58
C EPSREL - Double precision
59
C Relative accuracy requested
61
C and EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
62
C the routine will end with IER = 6.
65
C Gives an upper bound on the number of subintervals
66
C in the partition of (A,B), LIMIT.GE.NPTS2
67
C If LIMIT.LT.NPTS2, the routine will end with
71
C RESULT - Double precision
72
C Approximation to the integral
74
C ABSERR - Double precision
75
C Estimate of the modulus of the absolute error,
76
C which should equal or exceed ABS(I-RESULT)
79
C Number of integrand evaluations
82
C IER = 0 Normal and reliable termination of the
83
C routine. It is assumed that the requested
84
C accuracy has been achieved.
85
C IER.GT.0 Abnormal termination of the routine.
86
C The estimates for integral and error are
87
C less reliable. It is assumed that the
88
C requested accuracy has not been achieved.
90
C IER = 1 Maximum number of subdivisions allowed
91
C has been achieved. One can allow more
92
C subdivisions by increasing the value of
93
C LIMIT (and taking the according dimension
94
C adjustments into account). However, if
95
C this yields no improvement it is advised
96
C to analyze the integrand in order to
97
C determine the integration difficulties. If
98
C the position of a local difficulty can be
99
C determined (i.e. SINGULARITY,
100
C DISCONTINUITY within the interval), it
101
C should be supplied to the routine as an
102
C element of the vector points. If necessary
103
C an appropriate special-purpose integrator
104
C must be used, which is designed for
105
C handling the type of difficulty involved.
106
C = 2 The occurrence of roundoff error is
107
C detected, which prevents the requested
108
C tolerance from being achieved.
109
C The error may be under-estimated.
110
C = 3 Extremely bad integrand behaviour occurs
111
C At some points of the integration
113
C = 4 The algorithm does not converge.
114
C Roundoff error is detected in the
115
C extrapolation table. It is presumed that
116
C the requested tolerance cannot be
117
C achieved, and that the returned result is
118
C the best which can be obtained.
119
C = 5 The integral is probably divergent, or
120
C slowly convergent. It must be noted that
121
C divergence can occur with any other value
123
C = 6 The input is invalid because
125
C Break points are specified outside
126
C the integration range or
128
C EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28))
130
C RESULT, ABSERR, NEVAL, LAST, RLIST(1),
131
C and ELIST(1) are set to zero. ALIST(1) and
132
C BLIST(1) are set to A and B respectively.
134
C ALIST - Double precision
135
C Vector of dimension at least LIMIT, the first
136
C LAST elements of which are the left end points
137
C of the subintervals in the partition of the given
138
C integration range (A,B)
140
C BLIST - Double precision
141
C Vector of dimension at least LIMIT, the first
142
C LAST elements of which are the right end points
143
C of the subintervals in the partition of the given
144
C integration range (A,B)
146
C RLIST - Double precision
147
C Vector of dimension at least LIMIT, the first
148
C LAST elements of which are the integral
149
C approximations on the subintervals
151
C ELIST - Double precision
152
C Vector of dimension at least LIMIT, the first
153
C LAST elements of which are the moduli of the
154
C absolute error estimates on the subintervals
156
C PTS - Double precision
157
C Vector of dimension at least NPTS2, containing the
158
C integration limits and the break points of the
159
C interval in ascending sequence.
162
C Vector of dimension at least LIMIT, containing the
163
C subdivision levels of the subinterval, i.e. if
164
C (AA,BB) is a subinterval of (P1,P2) where P1 as
165
C well as P2 is a user-provided break point or
166
C integration limit, then (AA,BB) has level L if
167
C ABS(BB-AA) = ABS(P2-P1)*2**(-L).
170
C Vector of dimension at least NPTS2, after first
171
C integration over the intervals (PTS(I)),PTS(I+1),
172
C I = 0,1, ..., NPTS2-2, the error estimates over
173
C some of the intervals may have been increased
174
C artificially, in order to put their subdivision
175
C forward. If this happens for the subinterval
176
C numbered K, NDIN(K) is put to 1, otherwise
180
C Vector of dimension at least LIMIT, the first K
181
C elements of which are pointers to the
182
C error estimates over the subintervals,
183
C such that ELIST(IORD(1)), ..., ELIST(IORD(K))
184
C form a decreasing sequence, with K = LAST
185
C If LAST.LE.(LIMIT/2+2), and K = LIMIT+1-LAST
189
C Number of subintervals actually produced in the
190
C subdivisions process
192
C***REFERENCES (NONE)
193
C***ROUTINES CALLED D1MACH, DQELG, DQK21, DQPSRT
194
C***REVISION HISTORY (YYMMDD)
195
C 800101 DATE WRITTEN
196
C 890531 Changed all specific intrinsics to generic. (WRB)
197
C 890831 Modified array declarations. (WRB)
198
C 890831 REVISION DATE from Version 3.2
199
C 891214 Prologue converted to Version 4.0 format. (BAB)
200
C***END PROLOGUE DQAGPE
201
DOUBLE PRECISION A,ABSEPS,ABSERR,ALIST,AREA,AREA1,AREA12,AREA2,A1,
202
1 A2,B,BLIST,B1,B2,CORREC,DEFABS,DEFAB1,DEFAB2,
203
2 DRES,D1MACH,ELIST,EPMACH,EPSABS,EPSREL,ERLARG,ERLAST,ERRBND,
204
3 ERRMAX,ERROR1,ERRO12,ERROR2,ERRSUM,ERTEST,F,OFLOW,POINTS,PTS,
205
4 RESA,RESABS,RESEPS,RESULT,RES3LA,RLIST,RLIST2,SIGN,TEMP,UFLOW
206
INTEGER I,ID,IER,IERRO,IND1,IND2,IORD,IP1,IROFF1,IROFF2,IROFF3,J,
207
1 JLOW,JUPBND,K,KSGN,KTMIN,LAST,LEVCUR,LEVEL,LEVMAX,LIMIT,MAXERR,
208
2 NDIN,NEVAL,NINT,NINTP1,NPTS,NPTS2,NRES,NRMAX,NUMRL2
212
DIMENSION ALIST(*),BLIST(*),ELIST(*),IORD(*),
213
1 LEVEL(*),NDIN(*),POINTS(*),PTS(*),RES3LA(3),
214
2 RLIST(*),RLIST2(52)
218
C THE DIMENSION OF RLIST2 IS DETERMINED BY THE VALUE OF
219
C LIMEXP IN SUBROUTINE EPSALG (RLIST2 SHOULD BE OF DIMENSION
220
C (LIMEXP+2) AT LEAST).
223
C LIST OF MAJOR VARIABLES
224
C -----------------------
226
C ALIST - LIST OF LEFT END POINTS OF ALL SUBINTERVALS
227
C CONSIDERED UP TO NOW
228
C BLIST - LIST OF RIGHT END POINTS OF ALL SUBINTERVALS
229
C CONSIDERED UP TO NOW
230
C RLIST(I) - APPROXIMATION TO THE INTEGRAL OVER
231
C (ALIST(I),BLIST(I))
232
C RLIST2 - ARRAY OF DIMENSION AT LEAST LIMEXP+2
233
C CONTAINING THE PART OF THE EPSILON TABLE WHICH
234
C IS STILL NEEDED FOR FURTHER COMPUTATIONS
235
C ELIST(I) - ERROR ESTIMATE APPLYING TO RLIST(I)
236
C MAXERR - POINTER TO THE INTERVAL WITH LARGEST ERROR
238
C ERRMAX - ELIST(MAXERR)
239
C ERLAST - ERROR ON THE INTERVAL CURRENTLY SUBDIVIDED
240
C (BEFORE THAT SUBDIVISION HAS TAKEN PLACE)
241
C AREA - SUM OF THE INTEGRALS OVER THE SUBINTERVALS
242
C ERRSUM - SUM OF THE ERRORS OVER THE SUBINTERVALS
243
C ERRBND - REQUESTED ACCURACY MAX(EPSABS,EPSREL*
245
C *****1 - VARIABLE FOR THE LEFT SUBINTERVAL
246
C *****2 - VARIABLE FOR THE RIGHT SUBINTERVAL
247
C LAST - INDEX FOR SUBDIVISION
248
C NRES - NUMBER OF CALLS TO THE EXTRAPOLATION ROUTINE
249
C NUMRL2 - NUMBER OF ELEMENTS IN RLIST2. IF AN APPROPRIATE
250
C APPROXIMATION TO THE COMPOUNDED INTEGRAL HAS
251
C BEEN OBTAINED, IT IS PUT IN RLIST2(NUMRL2) AFTER
252
C NUMRL2 HAS BEEN INCREASED BY ONE.
253
C ERLARG - SUM OF THE ERRORS OVER THE INTERVALS LARGER
254
C THAN THE SMALLEST INTERVAL CONSIDERED UP TO NOW
255
C EXTRAP - LOGICAL VARIABLE DENOTING THAT THE ROUTINE
256
C IS ATTEMPTING TO PERFORM EXTRAPOLATION. I.E.
257
C BEFORE SUBDIVIDING THE SMALLEST INTERVAL WE
258
C TRY TO DECREASE THE VALUE OF ERLARG.
259
C NOEXT - LOGICAL VARIABLE DENOTING THAT EXTRAPOLATION IS
260
C NO LONGER ALLOWED (TRUE-VALUE)
262
C MACHINE DEPENDENT CONSTANTS
263
C ---------------------------
265
C EPMACH IS THE LARGEST RELATIVE SPACING.
266
C UFLOW IS THE SMALLEST POSITIVE MAGNITUDE.
267
C OFLOW IS THE LARGEST POSITIVE MAGNITUDE.
269
C***FIRST EXECUTABLE STATEMENT DQAGPE
272
C TEST ON VALIDITY OF PARAMETERS
273
C -----------------------------
287
IF(NPTS2.LT.2.OR.LIMIT.LE.NPTS.OR.(EPSABS.LE.0.0D+00.AND.
288
1 EPSREL.LT.MAX(0.5D+02*EPMACH,0.5D-28))) IER = 6
289
IF(IER.EQ.6) GO TO 999
291
C IF ANY BREAK POINTS ARE PROVIDED, SORT THEM INTO AN
292
C ASCENDING SEQUENCE.
295
IF(A.GT.B) SIGN = -1.0D+00
297
IF(NPTS.EQ.0) GO TO 15
301
15 PTS(NPTS+2) = MAX(A,B)
304
IF(NPTS.EQ.0) GO TO 40
309
IF(PTS(I).LE.PTS(J)) GO TO 20
314
IF(PTS(1).NE.MIN(A,B).OR.PTS(NINTP1).NE.MAX(A,B)) IER = 6
315
IF(IER.EQ.6) GO TO 999
317
C COMPUTE FIRST INTEGRAL AND ERROR APPROXIMATIONS.
318
C ------------------------------------------------
323
CALL DQK21(F,A1,B1,AREA1,ERROR1,DEFABS,RESA)
324
ABSERR = ABSERR+ERROR1
325
RESULT = RESULT+AREA1
327
IF(ERROR1.EQ.RESA.AND.ERROR1.NE.0.0D+00) NDIN(I) = 1
328
RESABS = RESABS+DEFABS
339
IF(NDIN(I).EQ.1) ELIST(I) = ABSERR
340
ERRSUM = ERRSUM+ELIST(I)
348
ERRBND = MAX(EPSABS,EPSREL*DRES)
349
IF(ABSERR.LE.0.1D+03*EPMACH*RESABS.AND.ABSERR.GT.ERRBND) IER = 2
350
IF(NINT.EQ.1) GO TO 80
356
IF(ELIST(IND1).GT.ELIST(IND2)) GO TO 60
360
IF(IND1.EQ.IORD(I)) GO TO 70
364
IF(LIMIT.LT.NPTS2) IER = 1
365
80 IF(IER.NE.0.OR.ABSERR.LE.ERRBND) GO TO 999
372
ERRMAX = ELIST(MAXERR)
391
IF(DRES.GE.(0.1D+01-0.5D+02*EPMACH)*RESABS) KSGN = 1
396
DO 160 LAST = NPTS2,LIMIT
398
C BISECT THE SUBINTERVAL WITH THE NRMAX-TH LARGEST ERROR
401
LEVCUR = LEVEL(MAXERR)+1
403
B1 = 0.5D+00*(ALIST(MAXERR)+BLIST(MAXERR))
407
CALL DQK21(F,A1,B1,AREA1,ERROR1,RESA,DEFAB1)
408
CALL DQK21(F,A2,B2,AREA2,ERROR2,RESA,DEFAB2)
410
C IMPROVE PREVIOUS APPROXIMATIONS TO INTEGRAL
411
C AND ERROR AND TEST FOR ACCURACY.
415
ERRO12 = ERROR1+ERROR2
416
ERRSUM = ERRSUM+ERRO12-ERRMAX
417
AREA = AREA+AREA12-RLIST(MAXERR)
418
IF(DEFAB1.EQ.ERROR1.OR.DEFAB2.EQ.ERROR2) GO TO 95
419
IF(ABS(RLIST(MAXERR)-AREA12).GT.0.1D-04*ABS(AREA12)
420
1 .OR.ERRO12.LT.0.99D+00*ERRMAX) GO TO 90
421
IF(EXTRAP) IROFF2 = IROFF2+1
422
IF(.NOT.EXTRAP) IROFF1 = IROFF1+1
423
90 IF(LAST.GT.10.AND.ERRO12.GT.ERRMAX) IROFF3 = IROFF3+1
424
95 LEVEL(MAXERR) = LEVCUR
426
RLIST(MAXERR) = AREA1
428
ERRBND = MAX(EPSABS,EPSREL*ABS(AREA))
430
C TEST FOR ROUNDOFF ERROR AND EVENTUALLY SET ERROR FLAG.
432
IF(IROFF1+IROFF2.GE.10.OR.IROFF3.GE.20) IER = 2
433
IF(IROFF2.GE.5) IERRO = 3
435
C SET ERROR FLAG IN THE CASE THAT THE NUMBER OF
436
C SUBINTERVALS EQUALS LIMIT.
438
IF(LAST.EQ.LIMIT) IER = 1
440
C SET ERROR FLAG IN THE CASE OF BAD INTEGRAND BEHAVIOUR
441
C AT A POINT OF THE INTEGRATION RANGE
443
IF(MAX(ABS(A1),ABS(B2)).LE.(0.1D+01+0.1D+03*EPMACH)*
444
1 (ABS(A2)+0.1D+04*UFLOW)) IER = 4
446
C APPEND THE NEWLY-CREATED INTERVALS TO THE LIST.
448
IF(ERROR2.GT.ERROR1) GO TO 100
452
ELIST(MAXERR) = ERROR1
455
100 ALIST(MAXERR) = A2
458
RLIST(MAXERR) = AREA2
460
ELIST(MAXERR) = ERROR2
463
C CALL SUBROUTINE DQPSRT TO MAINTAIN THE DESCENDING ORDERING
464
C IN THE LIST OF ERROR ESTIMATES AND SELECT THE SUBINTERVAL
465
C WITH NRMAX-TH LARGEST ERROR ESTIMATE (TO BE BISECTED NEXT).
467
110 CALL DQPSRT(LIMIT,LAST,MAXERR,ERRMAX,ELIST,IORD,NRMAX)
468
C ***JUMP OUT OF DO-LOOP
469
IF(ERRSUM.LE.ERRBND) GO TO 190
470
C ***JUMP OUT OF DO-LOOP
471
IF(IER.NE.0) GO TO 170
473
ERLARG = ERLARG-ERLAST
474
IF(LEVCUR+1.LE.LEVMAX) ERLARG = ERLARG+ERRO12
477
C TEST WHETHER THE INTERVAL TO BE BISECTED NEXT IS THE
480
IF(LEVEL(MAXERR)+1.LE.LEVMAX) GO TO 160
483
120 IF(IERRO.EQ.3.OR.ERLARG.LE.ERTEST) GO TO 140
485
C THE SMALLEST INTERVAL HAS THE LARGEST ERROR.
486
C BEFORE BISECTING DECREASE THE SUM OF THE ERRORS OVER
487
C THE LARGER INTERVALS (ERLARG) AND PERFORM EXTRAPOLATION.
491
IF(LAST.GT.(2+LIMIT/2)) JUPBND = LIMIT+3-LAST
494
ERRMAX = ELIST(MAXERR)
495
C ***JUMP OUT OF DO-LOOP
496
IF(LEVEL(MAXERR)+1.LE.LEVMAX) GO TO 160
500
C PERFORM EXTRAPOLATION.
502
140 NUMRL2 = NUMRL2+1
503
RLIST2(NUMRL2) = AREA
504
IF(NUMRL2.LE.2) GO TO 155
505
CALL DQELG(NUMRL2,RLIST2,RESEPS,ABSEPS,RES3LA,NRES)
507
IF(KTMIN.GT.5.AND.ABSERR.LT.0.1D-02*ERRSUM) IER = 5
508
IF(ABSEPS.GE.ABSERR) GO TO 150
513
ERTEST = MAX(EPSABS,EPSREL*ABS(RESEPS))
514
C ***JUMP OUT OF DO-LOOP
515
IF(ABSERR.LT.ERTEST) GO TO 170
517
C PREPARE BISECTION OF THE SMALLEST INTERVAL.
519
150 IF(NUMRL2.EQ.1) NOEXT = .TRUE.
520
IF(IER.GE.5) GO TO 170
522
ERRMAX = ELIST(MAXERR)
529
C SET THE FINAL RESULT.
530
C ---------------------
533
170 IF(ABSERR.EQ.OFLOW) GO TO 190
534
IF((IER+IERRO).EQ.0) GO TO 180
535
IF(IERRO.EQ.3) ABSERR = ABSERR+CORREC
537
IF(RESULT.NE.0.0D+00.AND.AREA.NE.0.0D+00)GO TO 175
538
IF(ABSERR.GT.ERRSUM)GO TO 190
539
IF(AREA.EQ.0.0D+00) GO TO 210
541
175 IF(ABSERR/ABS(RESULT).GT.ERRSUM/ABS(AREA))GO TO 190
543
C TEST ON DIVERGENCE.
545
180 IF(KSGN.EQ.(-1).AND.MAX(ABS(RESULT),ABS(AREA)).LE.
546
1 RESABS*0.1D-01) GO TO 210
547
IF(0.1D-01.GT.(RESULT/AREA).OR.(RESULT/AREA).GT.0.1D+03.OR.
548
1 ERRSUM.GT.ABS(AREA)) IER = 6
551
C COMPUTE GLOBAL INTEGRAL SUM.
555
RESULT = RESULT+RLIST(K)
558
210 IF(IER.GT.2) IER = IER-1