~ubuntu-branches/ubuntu/karmic/maxima/karmic

« back to all changes in this revision

Viewing changes to src/numerical/slatec/fortran/dqagpe.f

  • Committer: Bazaar Package Importer
  • Author(s): Camm Maguire
  • Date: 2004-11-13 18:39:14 UTC
  • mto: (2.1.2 hoary) (3.2.1 sid) (1.1.5 upstream)
  • mto: This revision was merged to the branch mainline in revision 3.
  • Revision ID: james.westby@ubuntu.com-20041113183914-ttig0evwuatnqosl
Tags: upstream-5.9.1
ImportĀ upstreamĀ versionĀ 5.9.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
*DECK DQAGPE
 
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)
 
13
C***CATEGORY  H2A2A1
 
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
 
20
C             K. U. Leuven
 
21
C           de Doncker, Elise
 
22
C             Applied Mathematics and Programming Division
 
23
C             K. U. Leuven
 
24
C***DESCRIPTION
 
25
C
 
26
C        Computation of a definite integral
 
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
 
42
C
 
43
C            NPTS2  - Integer
 
44
C                     Number equal to two more than the number of
 
45
C                     user-supplied break points within the integration
 
46
C                     range, NPTS2.GE.2.
 
47
C                     If NPTS2.LT.2, the routine will end with IER = 6.
 
48
C
 
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
 
54
C                     sorting.
 
55
C
 
56
C            EPSABS - Double precision
 
57
C                     Absolute accuracy requested
 
58
C            EPSREL - Double precision
 
59
C                     Relative accuracy requested
 
60
C                     If  EPSABS.LE.0
 
61
C                     and EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
 
62
C                     the routine will end with IER = 6.
 
63
C
 
64
C            LIMIT  - Integer
 
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
 
68
C                     IER = 6.
 
69
C
 
70
C         ON RETURN
 
71
C            RESULT - Double precision
 
72
C                     Approximation to the integral
 
73
C
 
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)
 
77
C
 
78
C            NEVAL  - Integer
 
79
C                     Number of integrand evaluations
 
80
C
 
81
C            IER    - Integer
 
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.
 
89
C            ERROR MESSAGES
 
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
 
112
C                             interval.
 
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
 
122
C                             of IER.GT.0.
 
123
C                         = 6 The input is invalid because
 
124
C                             NPTS2.LT.2 or
 
125
C                             Break points are specified outside
 
126
C                             the integration range or
 
127
C                             (EPSABS.LE.0 and
 
128
C                              EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28))
 
129
C                             or LIMIT.LT.NPTS2.
 
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.
 
133
C
 
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)
 
139
C
 
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)
 
145
C
 
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
 
150
C
 
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
 
155
C
 
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.
 
160
C
 
161
C            LEVEL  - Integer
 
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).
 
168
C
 
169
C            NDIN   - Integer
 
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
 
177
C                     NDIN(K) = 0.
 
178
C
 
179
C            IORD   - Integer
 
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
 
186
C                     otherwise
 
187
C
 
188
C            LAST   - Integer
 
189
C                     Number of subintervals actually produced in the
 
190
C                     subdivisions process
 
191
C
 
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
 
209
      LOGICAL EXTRAP,NOEXT
 
210
C
 
211
C
 
212
      DIMENSION ALIST(*),BLIST(*),ELIST(*),IORD(*),
 
213
     1  LEVEL(*),NDIN(*),POINTS(*),PTS(*),RES3LA(3),
 
214
     2  RLIST(*),RLIST2(52)
 
215
C
 
216
      EXTERNAL F
 
217
C
 
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).
 
221
C
 
222
C
 
223
C            LIST OF MAJOR VARIABLES
 
224
C            -----------------------
 
225
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
 
237
C                       ESTIMATE
 
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*
 
244
C                       ABS(RESULT))
 
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)
 
261
C
 
262
C            MACHINE DEPENDENT CONSTANTS
 
263
C            ---------------------------
 
264
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.
 
268
C
 
269
C***FIRST EXECUTABLE STATEMENT  DQAGPE
 
270
      EPMACH = D1MACH(4)
 
271
C
 
272
C            TEST ON VALIDITY OF PARAMETERS
 
273
C            -----------------------------
 
274
C
 
275
      IER = 0
 
276
      NEVAL = 0
 
277
      LAST = 0
 
278
      RESULT = 0.0D+00
 
279
      ABSERR = 0.0D+00
 
280
      ALIST(1) = A
 
281
      BLIST(1) = B
 
282
      RLIST(1) = 0.0D+00
 
283
      ELIST(1) = 0.0D+00
 
284
      IORD(1) = 0
 
285
      LEVEL(1) = 0
 
286
      NPTS = NPTS2-2
 
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
 
290
C
 
291
C            IF ANY BREAK POINTS ARE PROVIDED, SORT THEM INTO AN
 
292
C            ASCENDING SEQUENCE.
 
293
C
 
294
      SIGN = 1.0D+00
 
295
      IF(A.GT.B) SIGN = -1.0D+00
 
296
      PTS(1) = MIN(A,B)
 
297
      IF(NPTS.EQ.0) GO TO 15
 
298
      DO 10 I = 1,NPTS
 
299
        PTS(I+1) = POINTS(I)
 
300
   10 CONTINUE
 
301
   15 PTS(NPTS+2) = MAX(A,B)
 
302
      NINT = NPTS+1
 
303
      A1 = PTS(1)
 
304
      IF(NPTS.EQ.0) GO TO 40
 
305
      NINTP1 = NINT+1
 
306
      DO 20 I = 1,NINT
 
307
        IP1 = I+1
 
308
        DO 20 J = IP1,NINTP1
 
309
          IF(PTS(I).LE.PTS(J)) GO TO 20
 
310
          TEMP = PTS(I)
 
311
          PTS(I) = PTS(J)
 
312
          PTS(J) = TEMP
 
313
   20 CONTINUE
 
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
 
316
C
 
317
C            COMPUTE FIRST INTEGRAL AND ERROR APPROXIMATIONS.
 
318
C            ------------------------------------------------
 
319
C
 
320
   40 RESABS = 0.0D+00
 
321
      DO 50 I = 1,NINT
 
322
        B1 = PTS(I+1)
 
323
        CALL DQK21(F,A1,B1,AREA1,ERROR1,DEFABS,RESA)
 
324
        ABSERR = ABSERR+ERROR1
 
325
        RESULT = RESULT+AREA1
 
326
        NDIN(I) = 0
 
327
        IF(ERROR1.EQ.RESA.AND.ERROR1.NE.0.0D+00) NDIN(I) = 1
 
328
        RESABS = RESABS+DEFABS
 
329
        LEVEL(I) = 0
 
330
        ELIST(I) = ERROR1
 
331
        ALIST(I) = A1
 
332
        BLIST(I) = B1
 
333
        RLIST(I) = AREA1
 
334
        IORD(I) = I
 
335
        A1 = B1
 
336
   50 CONTINUE
 
337
      ERRSUM = 0.0D+00
 
338
      DO 55 I = 1,NINT
 
339
        IF(NDIN(I).EQ.1) ELIST(I) = ABSERR
 
340
        ERRSUM = ERRSUM+ELIST(I)
 
341
   55 CONTINUE
 
342
C
 
343
C           TEST ON ACCURACY.
 
344
C
 
345
      LAST = NINT
 
346
      NEVAL = 21*NINT
 
347
      DRES = ABS(RESULT)
 
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
 
351
      DO 70 I = 1,NPTS
 
352
        JLOW = I+1
 
353
        IND1 = IORD(I)
 
354
        DO 60 J = JLOW,NINT
 
355
          IND2 = IORD(J)
 
356
          IF(ELIST(IND1).GT.ELIST(IND2)) GO TO 60
 
357
          IND1 = IND2
 
358
          K = J
 
359
   60   CONTINUE
 
360
        IF(IND1.EQ.IORD(I)) GO TO 70
 
361
        IORD(K) = IORD(I)
 
362
        IORD(I) = IND1
 
363
   70 CONTINUE
 
364
      IF(LIMIT.LT.NPTS2) IER = 1
 
365
   80 IF(IER.NE.0.OR.ABSERR.LE.ERRBND) GO TO 999
 
366
C
 
367
C           INITIALIZATION
 
368
C           --------------
 
369
C
 
370
      RLIST2(1) = RESULT
 
371
      MAXERR = IORD(1)
 
372
      ERRMAX = ELIST(MAXERR)
 
373
      AREA = RESULT
 
374
      NRMAX = 1
 
375
      NRES = 0
 
376
      NUMRL2 = 1
 
377
      KTMIN = 0
 
378
      EXTRAP = .FALSE.
 
379
      NOEXT = .FALSE.
 
380
      ERLARG = ERRSUM
 
381
      ERTEST = ERRBND
 
382
      LEVMAX = 1
 
383
      IROFF1 = 0
 
384
      IROFF2 = 0
 
385
      IROFF3 = 0
 
386
      IERRO = 0
 
387
      UFLOW = D1MACH(1)
 
388
      OFLOW = D1MACH(2)
 
389
      ABSERR = OFLOW
 
390
      KSGN = -1
 
391
      IF(DRES.GE.(0.1D+01-0.5D+02*EPMACH)*RESABS) KSGN = 1
 
392
C
 
393
C           MAIN DO-LOOP
 
394
C           ------------
 
395
C
 
396
      DO 160 LAST = NPTS2,LIMIT
 
397
C
 
398
C           BISECT THE SUBINTERVAL WITH THE NRMAX-TH LARGEST ERROR
 
399
C           ESTIMATE.
 
400
C
 
401
        LEVCUR = LEVEL(MAXERR)+1
 
402
        A1 = ALIST(MAXERR)
 
403
        B1 = 0.5D+00*(ALIST(MAXERR)+BLIST(MAXERR))
 
404
        A2 = B1
 
405
        B2 = BLIST(MAXERR)
 
406
        ERLAST = ERRMAX
 
407
        CALL DQK21(F,A1,B1,AREA1,ERROR1,RESA,DEFAB1)
 
408
        CALL DQK21(F,A2,B2,AREA2,ERROR2,RESA,DEFAB2)
 
409
C
 
410
C           IMPROVE PREVIOUS APPROXIMATIONS TO INTEGRAL
 
411
C           AND ERROR AND TEST FOR ACCURACY.
 
412
C
 
413
        NEVAL = NEVAL+42
 
414
        AREA12 = AREA1+AREA2
 
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
 
425
        LEVEL(LAST) = LEVCUR
 
426
        RLIST(MAXERR) = AREA1
 
427
        RLIST(LAST) = AREA2
 
428
        ERRBND = MAX(EPSABS,EPSREL*ABS(AREA))
 
429
C
 
430
C           TEST FOR ROUNDOFF ERROR AND EVENTUALLY SET ERROR FLAG.
 
431
C
 
432
        IF(IROFF1+IROFF2.GE.10.OR.IROFF3.GE.20) IER = 2
 
433
        IF(IROFF2.GE.5) IERRO = 3
 
434
C
 
435
C           SET ERROR FLAG IN THE CASE THAT THE NUMBER OF
 
436
C           SUBINTERVALS EQUALS LIMIT.
 
437
C
 
438
        IF(LAST.EQ.LIMIT) IER = 1
 
439
C
 
440
C           SET ERROR FLAG IN THE CASE OF BAD INTEGRAND BEHAVIOUR
 
441
C           AT A POINT OF THE INTEGRATION RANGE
 
442
C
 
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
 
445
C
 
446
C           APPEND THE NEWLY-CREATED INTERVALS TO THE LIST.
 
447
C
 
448
        IF(ERROR2.GT.ERROR1) GO TO 100
 
449
        ALIST(LAST) = A2
 
450
        BLIST(MAXERR) = B1
 
451
        BLIST(LAST) = B2
 
452
        ELIST(MAXERR) = ERROR1
 
453
        ELIST(LAST) = ERROR2
 
454
        GO TO 110
 
455
  100   ALIST(MAXERR) = A2
 
456
        ALIST(LAST) = A1
 
457
        BLIST(LAST) = B1
 
458
        RLIST(MAXERR) = AREA2
 
459
        RLIST(LAST) = AREA1
 
460
        ELIST(MAXERR) = ERROR2
 
461
        ELIST(LAST) = ERROR1
 
462
C
 
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).
 
466
C
 
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
 
472
        IF(NOEXT) GO TO 160
 
473
        ERLARG = ERLARG-ERLAST
 
474
        IF(LEVCUR+1.LE.LEVMAX) ERLARG = ERLARG+ERRO12
 
475
        IF(EXTRAP) GO TO 120
 
476
C
 
477
C           TEST WHETHER THE INTERVAL TO BE BISECTED NEXT IS THE
 
478
C           SMALLEST INTERVAL.
 
479
C
 
480
        IF(LEVEL(MAXERR)+1.LE.LEVMAX) GO TO 160
 
481
        EXTRAP = .TRUE.
 
482
        NRMAX = 2
 
483
  120   IF(IERRO.EQ.3.OR.ERLARG.LE.ERTEST) GO TO 140
 
484
C
 
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.
 
488
C
 
489
        ID = NRMAX
 
490
        JUPBND = LAST
 
491
        IF(LAST.GT.(2+LIMIT/2)) JUPBND = LIMIT+3-LAST
 
492
        DO 130 K = ID,JUPBND
 
493
          MAXERR = IORD(NRMAX)
 
494
          ERRMAX = ELIST(MAXERR)
 
495
C ***JUMP OUT OF DO-LOOP
 
496
          IF(LEVEL(MAXERR)+1.LE.LEVMAX) GO TO 160
 
497
          NRMAX = NRMAX+1
 
498
  130   CONTINUE
 
499
C
 
500
C           PERFORM EXTRAPOLATION.
 
501
C
 
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)
 
506
        KTMIN = KTMIN+1
 
507
        IF(KTMIN.GT.5.AND.ABSERR.LT.0.1D-02*ERRSUM) IER = 5
 
508
        IF(ABSEPS.GE.ABSERR) GO TO 150
 
509
        KTMIN = 0
 
510
        ABSERR = ABSEPS
 
511
        RESULT = RESEPS
 
512
        CORREC = ERLARG
 
513
        ERTEST = MAX(EPSABS,EPSREL*ABS(RESEPS))
 
514
C ***JUMP OUT OF DO-LOOP
 
515
        IF(ABSERR.LT.ERTEST) GO TO 170
 
516
C
 
517
C           PREPARE BISECTION OF THE SMALLEST INTERVAL.
 
518
C
 
519
  150   IF(NUMRL2.EQ.1) NOEXT = .TRUE.
 
520
        IF(IER.GE.5) GO TO 170
 
521
  155   MAXERR = IORD(1)
 
522
        ERRMAX = ELIST(MAXERR)
 
523
        NRMAX = 1
 
524
        EXTRAP = .FALSE.
 
525
        LEVMAX = LEVMAX+1
 
526
        ERLARG = ERRSUM
 
527
  160 CONTINUE
 
528
C
 
529
C           SET THE FINAL RESULT.
 
530
C           ---------------------
 
531
C
 
532
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
 
536
      IF(IER.EQ.0) IER = 3
 
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
 
540
      GO TO 180
 
541
  175 IF(ABSERR/ABS(RESULT).GT.ERRSUM/ABS(AREA))GO TO 190
 
542
C
 
543
C           TEST ON DIVERGENCE.
 
544
C
 
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
 
549
      GO TO 210
 
550
C
 
551
C           COMPUTE GLOBAL INTEGRAL SUM.
 
552
C
 
553
  190 RESULT = 0.0D+00
 
554
      DO 200 K = 1,LAST
 
555
        RESULT = RESULT+RLIST(K)
 
556
  200 CONTINUE
 
557
      ABSERR = ERRSUM
 
558
  210 IF(IER.GT.2) IER = IER-1
 
559
      RESULT = RESULT*SIGN
 
560
  999 RETURN
 
561
      END