qnc79.f 8.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272
  1. *DECK QNC79
  2. SUBROUTINE QNC79 (FUN, A, B, ERR, ANS, IERR, K)
  3. C***BEGIN PROLOGUE QNC79
  4. C***PURPOSE Integrate a function using a 7-point adaptive Newton-Cotes
  5. C quadrature rule.
  6. C***LIBRARY SLATEC
  7. C***CATEGORY H2A1A1
  8. C***TYPE SINGLE PRECISION (QNC79-S, DQNC79-D)
  9. C***KEYWORDS ADAPTIVE QUADRATURE, INTEGRATION, NEWTON-COTES
  10. C***AUTHOR Kahaner, D. K., (NBS)
  11. C Jones, R. E., (SNLA)
  12. C***DESCRIPTION
  13. C
  14. C Abstract
  15. C QNC79 is a general purpose program for evaluation of
  16. C one dimensional integrals of user defined functions.
  17. C QNC79 will pick its own points for evaluation of the
  18. C integrand and these will vary from problem to problem.
  19. C Thus, QNC79 is not designed to integrate over data sets.
  20. C Moderately smooth integrands will be integrated efficiently
  21. C and reliably. For problems with strong singularities,
  22. C oscillations etc., the user may wish to use more sophis-
  23. C ticated routines such as those in QUADPACK. One measure
  24. C of the reliability of QNC79 is the output parameter K,
  25. C giving the number of integrand evaluations that were needed.
  26. C
  27. C Description of Arguments
  28. C
  29. C --Input--
  30. C FUN - name of external function to be integrated. This name
  31. C must be in an EXTERNAL statement in your calling
  32. C program. You must write a Fortran function to evaluate
  33. C FUN. This should be of the form
  34. C REAL FUNCTION FUN (X)
  35. C C
  36. C C X can vary from A to B
  37. C C FUN(X) should be finite for all X on interval.
  38. C C
  39. C FUN = ...
  40. C RETURN
  41. C END
  42. C A - lower limit of integration
  43. C B - upper limit of integration (may be less than A)
  44. C ERR - is a requested error tolerance. Normally, pick a value
  45. C 0 .LT. ERR .LT. 1.0E-3.
  46. C
  47. C --Output--
  48. C ANS - computed value of the integral. Hopefully, ANS is
  49. C accurate to within ERR * integral of ABS(FUN(X)).
  50. C IERR - a status code
  51. C - Normal codes
  52. C 1 ANS most likely meets requested error tolerance.
  53. C -1 A equals B, or A and B are too nearly equal to
  54. C allow normal integration. ANS is set to zero.
  55. C - Abnormal code
  56. C 2 ANS probably does not meet requested error tolerance.
  57. C K - the number of function evaluations actually used to do
  58. C the integration. A value of K .GT. 1000 indicates a
  59. C difficult problem; other programs may be more efficient.
  60. C QNC79 will gracefully give up if K exceeds 2000.
  61. C
  62. C***REFERENCES (NONE)
  63. C***ROUTINES CALLED I1MACH, R1MACH, XERMSG
  64. C***REVISION HISTORY (YYMMDD)
  65. C 790601 DATE WRITTEN
  66. C 890531 Changed all specific intrinsics to generic. (WRB)
  67. C 890531 REVISION DATE from Version 3.2
  68. C 891214 Prologue converted to Version 4.0 format. (BAB)
  69. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  70. C 920218 Code and prologue polished. (WRB)
  71. C***END PROLOGUE QNC79
  72. C .. Scalar Arguments ..
  73. REAL A, ANS, B, ERR
  74. INTEGER IERR, K
  75. C .. Function Arguments ..
  76. REAL FUN
  77. EXTERNAL FUN
  78. C .. Local Scalars ..
  79. REAL AE, AREA, BANK, BLOCAL, C, CE, EE, EF, EPS, Q13, Q7, Q7L,
  80. + SQ2, TEST, TOL, VR, W1, W2, W3, W4
  81. INTEGER I, KML, KMX, L, LMN, LMX, NBITS, NIB, NLMN, NLMX
  82. LOGICAL FIRST
  83. C .. Local Arrays ..
  84. REAL AA(40), F(13), F1(40), F2(40), F3(40), F4(40), F5(40),
  85. + F6(40), F7(40), HH(40), Q7R(40), VL(40)
  86. INTEGER LR(40)
  87. C .. External Functions ..
  88. REAL R1MACH
  89. INTEGER I1MACH
  90. EXTERNAL R1MACH, I1MACH
  91. C .. External Subroutines ..
  92. EXTERNAL XERMSG
  93. C .. Intrinsic Functions ..
  94. INTRINSIC ABS, LOG, MAX, MIN, SIGN, SQRT
  95. C .. Save statement ..
  96. SAVE NBITS, NLMX, FIRST, SQ2, W1, W2, W3, W4
  97. C .. Data statements ..
  98. DATA KML /7/, KMX /2000/, NLMN /2/
  99. DATA FIRST /.TRUE./
  100. C***FIRST EXECUTABLE STATEMENT QNC79
  101. IF (FIRST) THEN
  102. W1 = 41.0E0/140.0E0
  103. W2 = 216.0E0/140.0E0
  104. W3 = 27.0E0/140.0E0
  105. W4 = 272.0E0/140.0E0
  106. NBITS = R1MACH(5)*I1MACH(11)/0.30102000E0
  107. NLMX = MIN(40,(NBITS*4)/5)
  108. SQ2 = SQRT(2.0E0)
  109. ENDIF
  110. FIRST = .FALSE.
  111. ANS = 0.0E0
  112. IERR = 1
  113. CE = 0.0E0
  114. IF (A .EQ. B) GO TO 260
  115. LMX = NLMX
  116. LMN = NLMN
  117. IF (B .EQ. 0.0E0) GO TO 100
  118. IF (SIGN(1.0E0,B)*A .LE. 0.0E0) GO TO 100
  119. C = ABS(1.0E0-A/B)
  120. IF (C .GT. 0.1E0) GO TO 100
  121. IF (C .LE. 0.0E0) GO TO 260
  122. NIB = 0.5E0 - LOG(C)/LOG(2.0E0)
  123. LMX = MIN(NLMX,NBITS-NIB-4)
  124. IF (LMX .LT. 2) GO TO 260
  125. LMN = MIN(LMN,LMX)
  126. 100 TOL = MAX(ABS(ERR),2.0E0**(5-NBITS))
  127. IF (ERR .EQ. 0.0E0) TOL = SQRT(R1MACH(4))
  128. EPS = TOL
  129. HH(1) = (B-A)/12.0E0
  130. AA(1) = A
  131. LR(1) = 1
  132. DO 110 I = 1,11,2
  133. F(I) = FUN(A+(I-1)*HH(1))
  134. 110 CONTINUE
  135. BLOCAL = B
  136. F(13) = FUN(BLOCAL)
  137. K = 7
  138. L = 1
  139. AREA = 0.0E0
  140. Q7 = 0.0E0
  141. EF = 256.0E0/255.0E0
  142. BANK = 0.0E0
  143. C
  144. C Compute refined estimates, estimate the error, etc.
  145. C
  146. 120 DO 130 I = 2,12,2
  147. F(I) = FUN(AA(L)+(I-1)*HH(L))
  148. 130 CONTINUE
  149. K = K + 6
  150. C
  151. C Compute left and right half estimates
  152. C
  153. Q7L = HH(L)*((W1*(F(1)+F(7))+W2*(F(2)+F(6)))+
  154. + (W3*(F(3)+F(5))+W4*F(4)))
  155. Q7R(L) = HH(L)*((W1*(F(7)+F(13))+W2*(F(8)+F(12)))+
  156. + (W3*(F(9)+F(11))+W4*F(10)))
  157. C
  158. C Update estimate of integral of absolute value
  159. C
  160. AREA = AREA + (ABS(Q7L)+ABS(Q7R(L))-ABS(Q7))
  161. C
  162. C Do not bother to test convergence before minimum refinement level
  163. C
  164. IF (L .LT. LMN) GO TO 180
  165. C
  166. C Estimate the error in new value for whole interval, Q13
  167. C
  168. Q13 = Q7L + Q7R(L)
  169. EE = ABS(Q7-Q13)*EF
  170. C
  171. C Compute nominal allowed error
  172. C
  173. AE = EPS*AREA
  174. C
  175. C Borrow from bank account, but not too much
  176. C
  177. TEST = MIN(AE+0.8E0*BANK,10.0E0*AE)
  178. C
  179. C Don't ask for excessive accuracy
  180. C
  181. TEST = MAX(TEST,TOL*ABS(Q13),0.00003E0*TOL*AREA)
  182. C
  183. C Now, did this interval pass or not?
  184. C
  185. IF (EE-TEST) 150,150,170
  186. C
  187. C Have hit maximum refinement level -- penalize the cumulative error
  188. C
  189. 140 CE = CE + (Q7-Q13)
  190. GO TO 160
  191. C
  192. C On good intervals accumulate the theoretical estimate
  193. C
  194. 150 CE = CE + (Q7-Q13)/255.0
  195. C
  196. C Update the bank account. Don't go into debt.
  197. C
  198. 160 BANK = BANK + (AE-EE)
  199. IF (BANK .LT. 0.0E0) BANK = 0.0E0
  200. C
  201. C Did we just finish a left half or a right half?
  202. C
  203. IF (LR(L)) 190,190,210
  204. C
  205. C Consider the left half of next deeper level
  206. C
  207. 170 IF (K .GT. KMX) LMX = MIN(KML,LMX)
  208. IF (L .GE. LMX) GO TO 140
  209. 180 L = L + 1
  210. EPS = EPS*0.5E0
  211. IF (L .LE. 17) EF = EF/SQ2
  212. HH(L) = HH(L-1)*0.5E0
  213. LR(L) = -1
  214. AA(L) = AA(L-1)
  215. Q7 = Q7L
  216. F1(L) = F(7)
  217. F2(L) = F(8)
  218. F3(L) = F(9)
  219. F4(L) = F(10)
  220. F5(L) = F(11)
  221. F6(L) = F(12)
  222. F7(L) = F(13)
  223. F(13) = F(7)
  224. F(11) = F(6)
  225. F(9) = F(5)
  226. F(7) = F(4)
  227. F(5) = F(3)
  228. F(3) = F(2)
  229. GO TO 120
  230. C
  231. C Proceed to right half at this level
  232. C
  233. 190 VL(L) = Q13
  234. 200 Q7 = Q7R(L-1)
  235. LR(L) = 1
  236. AA(L) = AA(L) + 12.0E0*HH(L)
  237. F(1) = F1(L)
  238. F(3) = F2(L)
  239. F(5) = F3(L)
  240. F(7) = F4(L)
  241. F(9) = F5(L)
  242. F(11) = F6(L)
  243. F(13) = F7(L)
  244. GO TO 120
  245. C
  246. C Left and right halves are done, so go back up a level
  247. C
  248. 210 VR = Q13
  249. 220 IF (L .LE. 1) GO TO 250
  250. IF (L .LE. 17) EF = EF*SQ2
  251. EPS = EPS*2.0E0
  252. L = L - 1
  253. IF (LR(L)) 230,230,240
  254. 230 VL(L) = VL(L+1) + VR
  255. GO TO 200
  256. 240 VR = VL(L+1) + VR
  257. GO TO 220
  258. C
  259. C Exit
  260. C
  261. 250 ANS = VR
  262. IF (ABS(CE) .LE. 2.0E0*TOL*AREA) GO TO 270
  263. IERR = 2
  264. CALL XERMSG ('SLATEC', 'QNC79',
  265. + 'ANS is probably insufficiently accurate.', 2, 1)
  266. GO TO 270
  267. 260 IERR = -1
  268. CALL XERMSG ('SLATEC', 'QNC79',
  269. + 'A and B are too nearly equal to allow normal integration. $$'
  270. + // 'ANS is set to zero and IERR to -1.', -1, -1)
  271. 270 RETURN
  272. END