2 SUBROUTINE DQAGSE
(F
, A
, B
, EPSABS
, EPSREL
, LIMIT
, RESULT
, ABSERR
,
3 + NEVAL
, IER
, ALIST
, BLIST
, RLIST
, ELIST
, IORD
, LAST
)
4 C***BEGIN PROLOGUE DQAGSE
5 C***PURPOSE The routine calculates an approximation result to a given
6 C definite integral I = Integral of F over (A,B),
7 C hopefully satisfying following claim for accuracy
8 C ABS(I-RESULT).LE.MAX(EPSABS,EPSREL*ABS(I)).
9 C***LIBRARY SLATEC (QUADPACK)
11 C***TYPE DOUBLE PRECISION (QAGSE-S, DQAGSE-D)
12 C***KEYWORDS AUTOMATIC INTEGRATOR, END POINT SINGULARITIES,
13 C EXTRAPOLATION, GENERAL-PURPOSE, GLOBALLY ADAPTIVE,
14 C QUADPACK, QUADRATURE
15 C***AUTHOR Piessens, Robert
16 C Applied Mathematics and Programming Division
19 C Applied Mathematics and Programming Division
23 C Computation of a definite integral
24 C Standard fortran subroutine
25 C Double precision version
29 C F - Double precision
30 C Function subprogram defining the integrand
31 C function F(X). The actual name for F needs to be
32 C declared E X T E R N A L in the driver program.
34 C A - Double precision
35 C Lower limit of integration
37 C B - Double precision
38 C Upper limit of integration
40 C EPSABS - Double precision
41 C Absolute accuracy requested
42 C EPSREL - Double precision
43 C Relative accuracy requested
45 C and EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
46 C the routine will end with IER = 6.
49 C Gives an upper bound on the number of subintervals
50 C in the partition of (A,B)
53 C RESULT - Double precision
54 C Approximation to the integral
56 C ABSERR - Double precision
57 C Estimate of the modulus of the absolute error,
58 C which should equal or exceed ABS(I-RESULT)
61 C Number of integrand evaluations
64 C IER = 0 Normal and reliable termination of the
65 C routine. It is assumed that the requested
66 C accuracy has been achieved.
67 C IER.GT.0 Abnormal termination of the routine
68 C the estimates for integral and error are
69 C less reliable. It is assumed that the
70 C requested accuracy has not been achieved.
72 C = 1 Maximum number of subdivisions allowed
73 C has been achieved. One can allow more sub-
74 C divisions by increasing the value of LIMIT
75 C (and taking the according dimension
76 C adjustments into account). However, if
77 C this yields no improvement it is advised
78 C to analyze the integrand in order to
79 C determine the integration difficulties. If
80 C the position of a local difficulty can be
81 C determined (e.g. singularity,
82 C discontinuity within the interval) one
83 C will probably gain from splitting up the
84 C interval at this point and calling the
85 C integrator on the subranges. If possible,
86 C an appropriate special-purpose integrator
87 C should be used, which is designed for
88 C handling the type of difficulty involved.
89 C = 2 The occurrence of roundoff error is detec-
90 C ted, which prevents the requested
91 C tolerance from being achieved.
92 C The error may be under-estimated.
93 C = 3 Extremely bad integrand behaviour
94 C occurs at some points of the integration
96 C = 4 The algorithm does not converge.
97 C Roundoff error is detected in the
98 C extrapolation table.
99 C It is presumed that the requested
100 C tolerance cannot be achieved, and that the
101 C returned result is the best which can be
103 C = 5 The integral is probably divergent, or
104 C slowly convergent. It must be noted that
105 C divergence can occur with any other value
107 C = 6 The input is invalid, because
109 C EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28).
110 C RESULT, ABSERR, NEVAL, LAST, RLIST(1),
111 C IORD(1) and ELIST(1) are set to zero.
112 C ALIST(1) and BLIST(1) are set to A and B
115 C ALIST - Double precision
116 C Vector of dimension at least LIMIT, the first
117 C LAST elements of which are the left end points
118 C of the subintervals in the partition of the
119 C given integration range (A,B)
121 C BLIST - Double precision
122 C Vector of dimension at least LIMIT, the first
123 C LAST elements of which are the right end points
124 C of the subintervals in the partition of the given
125 C integration range (A,B)
127 C RLIST - Double precision
128 C Vector of dimension at least LIMIT, the first
129 C LAST elements of which are the integral
130 C approximations on the subintervals
132 C ELIST - Double precision
133 C Vector of dimension at least LIMIT, the first
134 C LAST elements of which are the moduli of the
135 C absolute error estimates on the subintervals
138 C Vector of dimension at least LIMIT, the first K
139 C elements of which are pointers to the
140 C error estimates over the subintervals,
141 C such that ELIST(IORD(1)), ..., ELIST(IORD(K))
142 C form a decreasing sequence, with K = LAST
143 C If LAST.LE.(LIMIT/2+2), and K = LIMIT+1-LAST
147 C Number of subintervals actually produced in the
148 C subdivision process
150 C***REFERENCES (NONE)
151 C***ROUTINES CALLED D1MACH, DQELG, DQK21, DQPSRT
152 C***REVISION HISTORY (YYMMDD)
153 C 800101 DATE WRITTEN
154 C 890531 Changed all specific intrinsics to generic. (WRB)
155 C 890831 Modified array declarations. (WRB)
156 C 890831 REVISION DATE from Version 3.2
157 C 891214 Prologue converted to Version 4.0 format. (BAB)
158 C***END PROLOGUE DQAGSE
160 DOUBLE PRECISION A
,ABSEPS
,ABSERR
,ALIST
,AREA
,AREA1
,AREA12
,AREA2
,A1
,
161 1 A2
,B
,BLIST
,B1
,B2
,CORREC
,DEFABS
,DEFAB1
,DEFAB2
,D1MACH
,
162 2 DRES
,ELIST
,EPMACH
,EPSABS
,EPSREL
,ERLARG
,ERLAST
,ERRBND
,ERRMAX
,
163 3 ERROR1
,ERROR2
,ERRO12
,ERRSUM
,ERTEST
,F
,OFLOW
,RESABS
,RESEPS
,RESULT
,
164 4 RES3LA
,RLIST
,RLIST2
,SMALL
,UFLOW
165 INTEGER ID
,IER
,IERRO
,IORD
,IROFF1
,IROFF2
,IROFF3
,JUPBND
,K
,KSGN
,
166 1 KTMIN
,LAST
,LIMIT
,MAXERR
,NEVAL
,NRES
,NRMAX
,NUMRL2
169 DIMENSION ALIST
(*),BLIST
(*),ELIST
(*),IORD
(*),
170 1 RES3LA
(3),RLIST
(*),RLIST2
(52)
174 C THE DIMENSION OF RLIST2 IS DETERMINED BY THE VALUE OF
175 C LIMEXP IN SUBROUTINE DQELG (RLIST2 SHOULD BE OF DIMENSION
176 C (LIMEXP+2) AT LEAST).
178 C LIST OF MAJOR VARIABLES
179 C -----------------------
181 C ALIST - LIST OF LEFT END POINTS OF ALL SUBINTERVALS
182 C CONSIDERED UP TO NOW
183 C BLIST - LIST OF RIGHT END POINTS OF ALL SUBINTERVALS
184 C CONSIDERED UP TO NOW
185 C RLIST(I) - APPROXIMATION TO THE INTEGRAL OVER
186 C (ALIST(I),BLIST(I))
187 C RLIST2 - ARRAY OF DIMENSION AT LEAST LIMEXP+2 CONTAINING
188 C THE PART OF THE EPSILON TABLE WHICH IS STILL
189 C NEEDED FOR FURTHER COMPUTATIONS
190 C ELIST(I) - ERROR ESTIMATE APPLYING TO RLIST(I)
191 C MAXERR - POINTER TO THE INTERVAL WITH LARGEST ERROR
193 C ERRMAX - ELIST(MAXERR)
194 C ERLAST - ERROR ON THE INTERVAL CURRENTLY SUBDIVIDED
195 C (BEFORE THAT SUBDIVISION HAS TAKEN PLACE)
196 C AREA - SUM OF THE INTEGRALS OVER THE SUBINTERVALS
197 C ERRSUM - SUM OF THE ERRORS OVER THE SUBINTERVALS
198 C ERRBND - REQUESTED ACCURACY MAX(EPSABS,EPSREL*
200 C *****1 - VARIABLE FOR THE LEFT INTERVAL
201 C *****2 - VARIABLE FOR THE RIGHT INTERVAL
202 C LAST - INDEX FOR SUBDIVISION
203 C NRES - NUMBER OF CALLS TO THE EXTRAPOLATION ROUTINE
204 C NUMRL2 - NUMBER OF ELEMENTS CURRENTLY IN RLIST2. IF AN
205 C APPROPRIATE APPROXIMATION TO THE COMPOUNDED
206 C INTEGRAL HAS BEEN OBTAINED IT IS PUT IN
207 C RLIST2(NUMRL2) AFTER NUMRL2 HAS BEEN INCREASED
209 C SMALL - LENGTH OF THE SMALLEST INTERVAL CONSIDERED UP
210 C TO NOW, MULTIPLIED BY 1.5
211 C ERLARG - SUM OF THE ERRORS OVER THE INTERVALS LARGER
212 C THAN THE SMALLEST INTERVAL CONSIDERED UP TO NOW
213 C EXTRAP - LOGICAL VARIABLE DENOTING THAT THE ROUTINE IS
214 C ATTEMPTING TO PERFORM EXTRAPOLATION I.E. BEFORE
215 C SUBDIVIDING THE SMALLEST INTERVAL WE TRY TO
216 C DECREASE THE VALUE OF ERLARG.
217 C NOEXT - LOGICAL VARIABLE DENOTING THAT EXTRAPOLATION
218 C IS NO LONGER ALLOWED (TRUE VALUE)
220 C MACHINE DEPENDENT CONSTANTS
221 C ---------------------------
223 C EPMACH IS THE LARGEST RELATIVE SPACING.
224 C UFLOW IS THE SMALLEST POSITIVE MAGNITUDE.
225 C OFLOW IS THE LARGEST POSITIVE MAGNITUDE.
227 C***FIRST EXECUTABLE STATEMENT DQAGSE
230 C TEST ON VALIDITY OF PARAMETERS
231 C ------------------------------
241 IF(EPSABS
.LE
.0.0D
+00.AND
.EPSREL
.LT
.MAX
(0.5D
+02*EPMACH
,0.5D
-28))
243 IF(IER
.EQ
.6) GO TO 999
245 C FIRST APPROXIMATION TO THE INTEGRAL
246 C -----------------------------------
251 CALL DQK21
(F
,A
,B
,RESULT
,ABSERR
,DEFABS
,RESABS
)
256 ERRBND
= MAX
(EPSABS
,EPSREL*DRES
)
261 IF(ABSERR
.LE
.1.0D
+02*EPMACH*DEFABS
.AND
.ABSERR
.GT
.ERRBND
) IER
= 2
262 IF(LIMIT
.EQ
.1) IER
= 1
263 IF(IER
.NE
.0.OR
.(ABSERR
.LE
.ERRBND
.AND
.ABSERR
.NE
.RESABS
).OR
.
264 1 ABSERR
.EQ
.0.0D
+00) GO TO 140
285 IF(DRES
.GE
.(0.1D
+01-0.5D
+02*EPMACH
)*DEFABS
) KSGN
= 1
292 C BISECT THE SUBINTERVAL WITH THE NRMAX-TH LARGEST ERROR
296 B1
= 0.5D
+00*(ALIST
(MAXERR
)+BLIST
(MAXERR
))
300 CALL DQK21
(F
,A1
,B1
,AREA1
,ERROR1
,RESABS
,DEFAB1
)
301 CALL DQK21
(F
,A2
,B2
,AREA2
,ERROR2
,RESABS
,DEFAB2
)
303 C IMPROVE PREVIOUS APPROXIMATIONS TO INTEGRAL
304 C AND ERROR AND TEST FOR ACCURACY.
307 ERRO12
= ERROR1
+ERROR2
308 ERRSUM
= ERRSUM
+ERRO12
-ERRMAX
309 AREA
= AREA
+AREA12
-RLIST
(MAXERR
)
310 IF(DEFAB1
.EQ
.ERROR1
.OR
.DEFAB2
.EQ
.ERROR2
) GO TO 15
311 IF(ABS
(RLIST
(MAXERR
)-AREA12
).GT
.0.1D
-04*ABS
(AREA12
)
312 1 .OR
.ERRO12
.LT
.0.99D
+00*ERRMAX
) GO TO 10
313 IF(EXTRAP
) IROFF2
= IROFF2
+1
314 IF(.NOT
.EXTRAP
) IROFF1
= IROFF1
+1
315 10 IF(LAST
.GT
.10.AND
.ERRO12
.GT
.ERRMAX
) IROFF3
= IROFF3
+1
316 15 RLIST
(MAXERR
) = AREA1
318 ERRBND
= MAX
(EPSABS
,EPSREL*ABS
(AREA
))
320 C TEST FOR ROUNDOFF ERROR AND EVENTUALLY SET ERROR FLAG.
322 IF(IROFF1
+IROFF2
.GE
.10.OR
.IROFF3
.GE
.20) IER
= 2
323 IF(IROFF2
.GE
.5) IERRO
= 3
325 C SET ERROR FLAG IN THE CASE THAT THE NUMBER OF SUBINTERVALS
328 IF(LAST
.EQ
.LIMIT
) IER
= 1
330 C SET ERROR FLAG IN THE CASE OF BAD INTEGRAND BEHAVIOUR
331 C AT A POINT OF THE INTEGRATION RANGE.
333 IF(MAX
(ABS
(A1
),ABS
(B2
)).LE
.(0.1D
+01+0.1D
+03*EPMACH
)*
334 1 (ABS
(A2
)+0.1D
+04*UFLOW
)) IER
= 4
336 C APPEND THE NEWLY-CREATED INTERVALS TO THE LIST.
338 IF(ERROR2
.GT
.ERROR1
) GO TO 20
342 ELIST
(MAXERR
) = ERROR1
345 20 ALIST
(MAXERR
) = A2
348 RLIST
(MAXERR
) = AREA2
350 ELIST
(MAXERR
) = ERROR2
353 C CALL SUBROUTINE DQPSRT TO MAINTAIN THE DESCENDING ORDERING
354 C IN THE LIST OF ERROR ESTIMATES AND SELECT THE SUBINTERVAL
355 C WITH NRMAX-TH LARGEST ERROR ESTIMATE (TO BE BISECTED NEXT).
357 30 CALL DQPSRT
(LIMIT
,LAST
,MAXERR
,ERRMAX
,ELIST
,IORD
,NRMAX
)
358 C ***JUMP OUT OF DO-LOOP
359 IF(ERRSUM
.LE
.ERRBND
) GO TO 115
360 C ***JUMP OUT OF DO-LOOP
361 IF(IER
.NE
.0) GO TO 100
362 IF(LAST
.EQ
.2) GO TO 80
364 ERLARG
= ERLARG
-ERLAST
365 IF(ABS
(B1
-A1
).GT
.SMALL
) ERLARG
= ERLARG
+ERRO12
368 C TEST WHETHER THE INTERVAL TO BE BISECTED NEXT IS THE
371 IF(ABS
(BLIST
(MAXERR
)-ALIST
(MAXERR
)).GT
.SMALL
) GO TO 90
374 40 IF(IERRO
.EQ
.3.OR
.ERLARG
.LE
.ERTEST
) GO TO 60
376 C THE SMALLEST INTERVAL HAS THE LARGEST ERROR.
377 C BEFORE BISECTING DECREASE THE SUM OF THE ERRORS OVER THE
378 C LARGER INTERVALS (ERLARG) AND PERFORM EXTRAPOLATION.
382 IF(LAST
.GT
.(2+LIMIT
/2)) JUPBND
= LIMIT
+3-LAST
385 ERRMAX
= ELIST
(MAXERR
)
386 C ***JUMP OUT OF DO-LOOP
387 IF(ABS
(BLIST
(MAXERR
)-ALIST
(MAXERR
)).GT
.SMALL
) GO TO 90
391 C PERFORM EXTRAPOLATION.
394 RLIST2
(NUMRL2
) = AREA
395 CALL DQELG
(NUMRL2
,RLIST2
,RESEPS
,ABSEPS
,RES3LA
,NRES
)
397 IF(KTMIN
.GT
.5.AND
.ABSERR
.LT
.0.1D
-02*ERRSUM
) IER
= 5
398 IF(ABSEPS
.GE
.ABSERR
) GO TO 70
403 ERTEST
= MAX
(EPSABS
,EPSREL*ABS
(RESEPS
))
404 C ***JUMP OUT OF DO-LOOP
405 IF(ABSERR
.LE
.ERTEST
) GO TO 100
407 C PREPARE BISECTION OF THE SMALLEST INTERVAL.
409 70 IF(NUMRL2
.EQ
.1) NOEXT
= .TRUE
.
410 IF(IER
.EQ
.5) GO TO 100
412 ERRMAX
= ELIST
(MAXERR
)
415 SMALL
= SMALL*0
.5D
+00
418 80 SMALL
= ABS
(B
-A
)*0.375D
+00
424 C SET FINAL RESULT AND ERROR ESTIMATE.
425 C ------------------------------------
427 100 IF(ABSERR
.EQ
.OFLOW
) GO TO 115
428 IF(IER
+IERRO
.EQ
.0) GO TO 110
429 IF(IERRO
.EQ
.3) ABSERR
= ABSERR
+CORREC
431 IF(RESULT
.NE
.0.0D
+00.AND
.AREA
.NE
.0.0D
+00) GO TO 105
432 IF(ABSERR
.GT
.ERRSUM
) GO TO 115
433 IF(AREA
.EQ
.0.0D
+00) GO TO 130
435 105 IF(ABSERR
/ABS
(RESULT
).GT
.ERRSUM
/ABS
(AREA
)) GO TO 115
437 C TEST ON DIVERGENCE.
439 110 IF(KSGN
.EQ
.(-1).AND
.MAX
(ABS
(RESULT
),ABS
(AREA
)).LE
.
440 1 DEFABS*0
.1D
-01) GO TO 130
441 IF(0.1D
-01.GT
.(RESULT
/AREA
).OR
.(RESULT
/AREA
).GT
.0.1D
+03
442 1 .OR
.ERRSUM
.GT
.ABS
(AREA
)) IER
= 6
445 C COMPUTE GLOBAL INTEGRAL SUM.
449 RESULT
= RESULT
+RLIST
(K
)
452 130 IF(IER
.GT
.2) IER
= IER
-1
453 140 NEVAL
= 42*LAST
-21