Windows installer: Update SBCL.
[maxima.git] / src / numerical / slatec / fortran / dqags.f
blob082bb0a0f22aec29d3ee8116b6240b64a0e74046
1 *DECK DQAGS
2 SUBROUTINE DQAGS (F, A, B, EPSABS, EPSREL, RESULT, ABSERR, NEVAL,
3 + IER, LIMIT, LENW, LAST, IWORK, WORK)
4 C***BEGIN PROLOGUE DQAGS
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)
10 C***CATEGORY H2A1A1
11 C***TYPE DOUBLE PRECISION (QAGS-S, DQAGS-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
17 C K. U. Leuven
18 C de Doncker, Elise
19 C Applied Mathematics and Programming Division
20 C K. U. Leuven
21 C***DESCRIPTION
23 C Computation of a definite integral
24 C Standard fortran subroutine
25 C Double precision version
28 C PARAMETERS
29 C ON ENTRY
30 C F - Double precision
31 C Function subprogram defining the integrand
32 C Function F(X). The actual name for F needs to be
33 C Declared E X T E R N A L in the driver program.
35 C A - Double precision
36 C Lower limit of integration
38 C B - Double precision
39 C Upper limit of integration
41 C EPSABS - Double precision
42 C Absolute accuracy requested
43 C EPSREL - Double precision
44 C Relative accuracy requested
45 C If EPSABS.LE.0
46 C And EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28),
47 C The routine will end with IER = 6.
49 C ON RETURN
50 C RESULT - Double precision
51 C Approximation to the integral
53 C ABSERR - Double precision
54 C Estimate of the modulus of the absolute error,
55 C which should equal or exceed ABS(I-RESULT)
57 C NEVAL - Integer
58 C Number of integrand evaluations
60 C IER - Integer
61 C IER = 0 Normal and reliable termination of the
62 C routine. It is assumed that the requested
63 C accuracy has been achieved.
64 C IER.GT.0 Abnormal termination of the routine
65 C The estimates for integral and error are
66 C less reliable. It is assumed that the
67 C requested accuracy has not been achieved.
68 C ERROR MESSAGES
69 C IER = 1 Maximum number of subdivisions allowed
70 C has been achieved. One can allow more sub-
71 C divisions by increasing the value of LIMIT
72 C (and taking the according dimension
73 C adjustments into account. However, if
74 C this yields no improvement it is advised
75 C to analyze the integrand in order to
76 C determine the integration difficulties. If
77 C the position of a local difficulty can be
78 C determined (E.G. SINGULARITY,
79 C DISCONTINUITY WITHIN THE INTERVAL) one
80 C will probably gain from splitting up the
81 C interval at this point and calling the
82 C integrator on the subranges. If possible,
83 C an appropriate special-purpose integrator
84 C should be used, which is designed for
85 C handling the type of difficulty involved.
86 C = 2 The occurrence of roundoff error is detec-
87 C ted, which prevents the requested
88 C tolerance from being achieved.
89 C The error may be under-estimated.
90 C = 3 Extremely bad integrand behaviour
91 C occurs at some points of the integration
92 C interval.
93 C = 4 The algorithm does not converge.
94 C Roundoff error is detected in the
95 C Extrapolation table. It is presumed that
96 C the requested tolerance cannot be
97 C achieved, and that the returned result is
98 C the best which can be obtained.
99 C = 5 The integral is probably divergent, or
100 C slowly convergent. It must be noted that
101 C divergence can occur with any other value
102 C of IER.
103 C = 6 The input is invalid, because
104 C (EPSABS.LE.0 AND
105 C EPSREL.LT.MAX(50*REL.MACH.ACC.,0.5D-28)
106 C OR LIMIT.LT.1 OR LENW.LT.LIMIT*4.
107 C RESULT, ABSERR, NEVAL, LAST are set to
108 C zero. Except when LIMIT or LENW is
109 C invalid, IWORK(1), WORK(LIMIT*2+1) and
110 C WORK(LIMIT*3+1) are set to zero, WORK(1)
111 C is set to A and WORK(LIMIT+1) TO B.
113 C DIMENSIONING PARAMETERS
114 C LIMIT - Integer
115 C DIMENSIONING PARAMETER FOR IWORK
116 C LIMIT determines the maximum number of subintervals
117 C in the partition of the given integration interval
118 C (A,B), LIMIT.GE.1.
119 C IF LIMIT.LT.1, the routine will end with IER = 6.
121 C LENW - Integer
122 C DIMENSIONING PARAMETER FOR WORK
123 C LENW must be at least LIMIT*4.
124 C If LENW.LT.LIMIT*4, the routine will end
125 C with IER = 6.
127 C LAST - Integer
128 C On return, LAST equals the number of subintervals
129 C produced in the subdivision process, determines the
130 C number of significant elements actually in the WORK
131 C Arrays.
133 C WORK ARRAYS
134 C IWORK - Integer
135 C Vector of dimension at least LIMIT, the first K
136 C elements of which contain pointers
137 C to the error estimates over the subintervals
138 C such that WORK(LIMIT*3+IWORK(1)),... ,
139 C WORK(LIMIT*3+IWORK(K)) form a decreasing
140 C sequence, with K = LAST IF LAST.LE.(LIMIT/2+2),
141 C and K = LIMIT+1-LAST otherwise
143 C WORK - Double precision
144 C Vector of dimension at least LENW
145 C on return
146 C WORK(1), ..., WORK(LAST) contain the left
147 C end-points of the subintervals in the
148 C partition of (A,B),
149 C WORK(LIMIT+1), ..., WORK(LIMIT+LAST) contain
150 C the right end-points,
151 C WORK(LIMIT*2+1), ..., WORK(LIMIT*2+LAST) contain
152 C the integral approximations over the subintervals,
153 C WORK(LIMIT*3+1), ..., WORK(LIMIT*3+LAST)
154 C contain the error estimates.
156 C***REFERENCES (NONE)
157 C***ROUTINES CALLED DQAGSE, XERMSG
158 C***REVISION HISTORY (YYMMDD)
159 C 800101 DATE WRITTEN
160 C 890831 Modified array declarations. (WRB)
161 C 890831 REVISION DATE from Version 3.2
162 C 891214 Prologue converted to Version 4.0 format. (BAB)
163 C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
164 C***END PROLOGUE DQAGS
167 DOUBLE PRECISION A,ABSERR,B,EPSABS,EPSREL,F,RESULT,WORK
168 INTEGER IER,IWORK,LAST,LENW,LIMIT,LVL,L1,L2,L3,NEVAL
170 DIMENSION IWORK(*),WORK(*)
172 EXTERNAL F
174 C CHECK VALIDITY OF LIMIT AND LENW.
176 C***FIRST EXECUTABLE STATEMENT DQAGS
177 IER = 6
178 NEVAL = 0
179 LAST = 0
180 RESULT = 0.0D+00
181 ABSERR = 0.0D+00
182 IF(LIMIT.LT.1.OR.LENW.LT.LIMIT*4) GO TO 10
184 C PREPARE CALL FOR DQAGSE.
186 L1 = LIMIT+1
187 L2 = LIMIT+L1
188 L3 = LIMIT+L2
190 CALL DQAGSE(F,A,B,EPSABS,EPSREL,LIMIT,RESULT,ABSERR,NEVAL,
191 1 IER,WORK(1),WORK(L1),WORK(L2),WORK(L3),IWORK,LAST)
193 C CALL ERROR HANDLER IF NECESSARY.
195 LVL = 0
196 10 IF(IER.EQ.6) LVL = 1
197 IF (IER .NE. 0) CALL XERMSG ('SLATEC', 'DQAGS',
198 + 'ABNORMAL RETURN', IER, LVL)
199 RETURN