1
2      SUBROUTINE DQAGIE(F,BOUND,INF,EPSABS,EPSREL,LIMIT,RESULT,ABSERR,
3     1   NEVAL,IER,ALIST,BLIST,RLIST,ELIST,IORD,LAST)
4C***BEGIN PROLOGUE  DQAGIE
5C***DATE WRITTEN   800101   (YYMMDD)
6C***REVISION DATE  830518   (YYMMDD)
7C***CATEGORY NO.  H2A3A1,H2A4A1
8C***KEYWORDS  AUTOMATIC INTEGRATOR,EXTRAPOLATION,GENERAL-PURPOSE,
9C             GLOBALLY ADAPTIVE,INFINITE INTERVALS,TRANSFORMATION
10C***AUTHOR  PIESSENS, ROBERT, APPLIED MATH. AND PROGR. DIV. -
11C             K. U. LEUVEN
12C           DE DONCKER, ELISE, APPLIED MATH. AND PROGR. DIV. -
13C             K. U. LEUVEN
14C***PURPOSE  The routine calculates an approximation result to a given
15C            integral   I = Integral of F over (BOUND,+INFINITY)
16C            or I = Integral of F over (-INFINITY,BOUND)
17C            or I = Integral of F over (-INFINITY,+INFINITY),
18C            hopefully satisfying following claim for accuracy
19C            ABS(I-RESULT).LE.MAX(EPSABS,EPSREL*ABS(I))
20C***DESCRIPTION
21C
22C Integration over infinite intervals
23C Standard fortran subroutine
24C
25C            F      - Double precision
26C                     Function subprogram defining the integrand
27C                     function F(X). The actual name for F needs to be
28C                     declared E X T E R N A L in the driver program.
29C
30C            BOUND  - Double precision
31C                     Finite bound of integration range
32C                     (has no meaning if interval is doubly-infinite)
33C
34C            INF    - Double precision
35C                     Indicating the kind of integration range involved
36C                     INF = 1 corresponds to  (BOUND,+INFINITY),
37C                     INF = -1            to  (-INFINITY,BOUND),
38C                     INF = 2             to (-INFINITY,+INFINITY).
39C
40C            EPSABS - Double precision
41C                     Absolute accuracy requested
42C            EPSREL - Double precision
43C                     Relative accuracy requested
44C                     If  EPSABS.LE.0
45C                     and EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
46C                     the routine will end with IER = 6.
47C
48C            LIMIT  - Integer
49C                     Gives an upper bound on the number of subintervals
50C                     in the partition of (A,B), LIMIT.GE.1
51C
52C         ON RETURN
53C            RESULT - Double precision
54C                     Approximation to the integral
55C
56C            ABSERR - Double precision
57C                     Estimate of the modulus of the absolute error,
58C                     which should equal or exceed ABS(I-RESULT)
59C
60C            NEVAL  - Integer
61C                     Number of integrand evaluations
62C
63C            IER    - Integer
64C                     IER = 0 Normal and reliable termination of the
65C                             routine. It is assumed that the requested
66C                             accuracy has been achieved.
67C                   - IER.GT.0 Abnormal termination of the routine. The
68C                             estimates for result and error are less
69C                             reliable. It is assumed that the requested
70C                             accuracy has not been achieved.
71C            ERROR MESSAGES
72C                     IER = 1 Maximum number of subdivisions allowed
73C                             has been achieved. One can allow more
74C                             subdivisions by increasing the value of
75C                             LIMIT (and taking the according dimension
76C                             adjustments into account). However,if
77C                             this yields no improvement it is advised
78C                             to analyze the integrand in order to
79C                             determine the integration difficulties.
80C                             If the position of a local difficulty can
81C                             be determined (e.g. SINGULARITY,
82C                             DISCONTINUITY within the interval) one
83C                             will probably gain from splitting up the
84C                             interval at this point and calling the
85C                             integrator on the subranges. If possible,
86C                             an appropriate special-purpose integrator
87C                             should be used, which is designed for
88C                             handling the type of difficulty involved.
89C                         = 2 The occurrence of roundoff error is
90C                             detected, which prevents the requested
91C                             tolerance from being achieved.
92C                             The error may be under-estimated.
93C                         = 3 Extremely bad integrand behaviour occurs
94C                             at some points of the integration
95C                             interval.
96C                         = 4 The algorithm does not converge.
97C                             Roundoff error is detected in the
98C                             extrapolation table.
99C                             It is assumed that the requested tolerance
100C                             cannot be achieved, and that the returned
101C                             result is the best which can be obtained.
102C                         = 5 The integral is probably divergent, or
103C                             slowly convergent. It must be noted that
104C                             divergence can occur with any other value
105C                             of IER.
106C                         = 6 The input is invalid, because
107C                             (EPSABS.LE.0 and
108C                              EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
109C                             RESULT, ABSERR, NEVAL, LAST, RLIST(1),
110C                             ELIST(1) and IORD(1) are set to zero.
111C                             ALIST(1) and BLIST(1) are set to 0
112C                             and 1 respectively.
113C
114C            ALIST  - Double precision
115C                     Vector of dimension at least LIMIT, the first
116C                      LAST  elements of which are the left
117C                     end points of the subintervals in the partition
118C                     of the transformed integration range (0,1).
119C
120C            BLIST  - Double precision
121C                     Vector of dimension at least LIMIT, the first
122C                      LAST  elements of which are the right
123C                     end points of the subintervals in the partition
124C                     of the transformed integration range (0,1).
125C
126C            RLIST  - Double precision
127C                     Vector of dimension at least LIMIT, the first
128C                      LAST  elements of which are the integral
129C                     approximations on the subintervals
130C
131C            ELIST  - Double precision
132C                     Vector of dimension at least LIMIT,  the first
133C                     LAST elements of which are the moduli of the
134C                     absolute error estimates on the subintervals
135C
136C            IORD   - Integer
137C                     Vector of dimension LIMIT, the first K
138C                     elements of which are pointers to the
139C                     error estimates over the subintervals,
140C                     such that ELIST(IORD(1)), ..., ELIST(IORD(K))
141C                     form a decreasing sequence, with K = LAST
142C                     If LAST.LE.(LIMIT/2+2), and K = LIMIT+1-LAST
143C                     otherwise
144C
145C            LAST   - Integer
146C                     Number of subintervals actually produced
147C                     in the subdivision process
148C***REFERENCES  (NONE)
149C***ROUTINES CALLED  D1MACH,DQELG,DQK15I,DQPSRT
150C***END PROLOGUE  DQAGIE
151
152
153