dgaus8.f 7.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201
  1. *DECK DGAUS8
  2. SUBROUTINE DGAUS8 (FUN, A, B, ERR, ANS, IERR)
  3. C***BEGIN PROLOGUE DGAUS8
  4. C***PURPOSE Integrate a real function of one variable over a finite
  5. C interval using an adaptive 8-point Legendre-Gauss
  6. C algorithm. Intended primarily for high accuracy
  7. C integration or integration of smooth functions.
  8. C***LIBRARY SLATEC
  9. C***CATEGORY H2A1A1
  10. C***TYPE DOUBLE PRECISION (GAUS8-S, DGAUS8-D)
  11. C***KEYWORDS ADAPTIVE QUADRATURE, AUTOMATIC INTEGRATOR,
  12. C GAUSS QUADRATURE, NUMERICAL INTEGRATION
  13. C***AUTHOR Jones, R. E., (SNLA)
  14. C***DESCRIPTION
  15. C
  16. C Abstract *** a DOUBLE PRECISION routine ***
  17. C DGAUS8 integrates real functions of one variable over finite
  18. C intervals using an adaptive 8-point Legendre-Gauss algorithm.
  19. C DGAUS8 is intended primarily for high accuracy integration
  20. C or integration of smooth functions.
  21. C
  22. C The maximum number of significant digits obtainable in ANS
  23. C is the smaller of 18 and the number of digits carried in
  24. C double precision arithmetic.
  25. C
  26. C Description of Arguments
  27. C
  28. C Input--* FUN, A, B, ERR are DOUBLE PRECISION *
  29. C FUN - name of external function to be integrated. This name
  30. C must be in an EXTERNAL statement in the calling program.
  31. C FUN must be a DOUBLE PRECISION function of one DOUBLE
  32. C PRECISION argument. The value of the argument to FUN
  33. C is the variable of integration which ranges from A to B.
  34. C A - lower limit of integration
  35. C B - upper limit of integration (may be less than A)
  36. C ERR - is a requested pseudorelative error tolerance. Normally
  37. C pick a value of ABS(ERR) so that DTOL .LT. ABS(ERR) .LE.
  38. C 1.0D-3 where DTOL is the larger of 1.0D-18 and the
  39. C double precision unit roundoff D1MACH(4). ANS will
  40. C normally have no more error than ABS(ERR) times the
  41. C integral of the absolute value of FUN(X). Usually,
  42. C smaller values of ERR yield more accuracy and require
  43. C more function evaluations.
  44. C
  45. C A negative value for ERR causes an estimate of the
  46. C absolute error in ANS to be returned in ERR. Note that
  47. C ERR must be a variable (not a constant) in this case.
  48. C Note also that the user must reset the value of ERR
  49. C before making any more calls that use the variable ERR.
  50. C
  51. C Output--* ERR,ANS are double precision *
  52. C ERR - will be an estimate of the absolute error in ANS if the
  53. C input value of ERR was negative. (ERR is unchanged if
  54. C the input value of ERR was non-negative.) The estimated
  55. C error is solely for information to the user and should
  56. C not be used as a correction to the computed integral.
  57. C ANS - computed value of integral
  58. C IERR- a status code
  59. C --Normal codes
  60. C 1 ANS most likely meets requested error tolerance,
  61. C or A=B.
  62. C -1 A and B are too nearly equal to allow normal
  63. C integration. ANS is set to zero.
  64. C --Abnormal code
  65. C 2 ANS probably does not meet requested error tolerance.
  66. C
  67. C***REFERENCES (NONE)
  68. C***ROUTINES CALLED D1MACH, I1MACH, XERMSG
  69. C***REVISION HISTORY (YYMMDD)
  70. C 810223 DATE WRITTEN
  71. C 890531 Changed all specific intrinsics to generic. (WRB)
  72. C 890911 Removed unnecessary intrinsics. (WRB)
  73. C 890911 REVISION DATE from Version 3.2
  74. C 891214 Prologue converted to Version 4.0 format. (BAB)
  75. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  76. C 900326 Removed duplicate information from DESCRIPTION section.
  77. C (WRB)
  78. C***END PROLOGUE DGAUS8
  79. INTEGER IERR, K, KML, KMX, L, LMN, LMX, LR, MXL, NBITS,
  80. 1 NIB, NLMN, NLMX
  81. INTEGER I1MACH
  82. DOUBLE PRECISION A,AA,AE,ANIB,ANS,AREA,B,C,CE,EE,EF,
  83. 1 EPS, ERR, EST, GL, GLR, GR, HH, SQ2, TOL, VL, VR, W1, W2, W3,
  84. 2 W4, X1, X2, X3, X4, X, H
  85. DOUBLE PRECISION D1MACH, G8, FUN
  86. DIMENSION AA(60), HH(60), LR(60), VL(60), GR(60)
  87. SAVE X1, X2, X3, X4, W1, W2, W3, W4, SQ2,
  88. 1 NLMN, KMX, KML
  89. DATA X1, X2, X3, X4/
  90. 1 1.83434642495649805D-01, 5.25532409916328986D-01,
  91. 2 7.96666477413626740D-01, 9.60289856497536232D-01/
  92. DATA W1, W2, W3, W4/
  93. 1 3.62683783378361983D-01, 3.13706645877887287D-01,
  94. 2 2.22381034453374471D-01, 1.01228536290376259D-01/
  95. DATA SQ2/1.41421356D0/
  96. DATA NLMN/1/,KMX/5000/,KML/6/
  97. G8(X,H)=H*((W1*(FUN(X-X1*H) + FUN(X+X1*H))
  98. 1 +W2*(FUN(X-X2*H) + FUN(X+X2*H)))
  99. 2 +(W3*(FUN(X-X3*H) + FUN(X+X3*H))
  100. 3 +W4*(FUN(X-X4*H) + FUN(X+X4*H))))
  101. C***FIRST EXECUTABLE STATEMENT DGAUS8
  102. C
  103. C Initialize
  104. C
  105. K = I1MACH(14)
  106. ANIB = D1MACH(5)*K/0.30102000D0
  107. NBITS = ANIB
  108. NLMX = MIN(60,(NBITS*5)/8)
  109. ANS = 0.0D0
  110. IERR = 1
  111. CE = 0.0D0
  112. IF (A .EQ. B) GO TO 140
  113. LMX = NLMX
  114. LMN = NLMN
  115. IF (B .EQ. 0.0D0) GO TO 10
  116. IF (SIGN(1.0D0,B)*A .LE. 0.0D0) GO TO 10
  117. C = ABS(1.0D0-A/B)
  118. IF (C .GT. 0.1D0) GO TO 10
  119. IF (C .LE. 0.0D0) GO TO 140
  120. ANIB = 0.5D0 - LOG(C)/0.69314718D0
  121. NIB = ANIB
  122. LMX = MIN(NLMX,NBITS-NIB-7)
  123. IF (LMX .LT. 1) GO TO 130
  124. LMN = MIN(LMN,LMX)
  125. 10 TOL = MAX(ABS(ERR),2.0D0**(5-NBITS))/2.0D0
  126. IF (ERR .EQ. 0.0D0) TOL = SQRT(D1MACH(4))
  127. EPS = TOL
  128. HH(1) = (B-A)/4.0D0
  129. AA(1) = A
  130. LR(1) = 1
  131. L = 1
  132. EST = G8(AA(L)+2.0D0*HH(L),2.0D0*HH(L))
  133. K = 8
  134. AREA = ABS(EST)
  135. EF = 0.5D0
  136. MXL = 0
  137. C
  138. C Compute refined estimates, estimate the error, etc.
  139. C
  140. 20 GL = G8(AA(L)+HH(L),HH(L))
  141. GR(L) = G8(AA(L)+3.0D0*HH(L),HH(L))
  142. K = K + 16
  143. AREA = AREA + (ABS(GL)+ABS(GR(L))-ABS(EST))
  144. C IF (L .LT .LMN) GO TO 11
  145. GLR = GL + GR(L)
  146. EE = ABS(EST-GLR)*EF
  147. AE = MAX(EPS*AREA,TOL*ABS(GLR))
  148. IF (EE-AE) 40, 40, 50
  149. 30 MXL = 1
  150. 40 CE = CE + (EST-GLR)
  151. IF (LR(L)) 60, 60, 80
  152. C
  153. C Consider the left half of this level
  154. C
  155. 50 IF (K .GT. KMX) LMX = KML
  156. IF (L .GE. LMX) GO TO 30
  157. L = L + 1
  158. EPS = EPS*0.5D0
  159. EF = EF/SQ2
  160. HH(L) = HH(L-1)*0.5D0
  161. LR(L) = -1
  162. AA(L) = AA(L-1)
  163. EST = GL
  164. GO TO 20
  165. C
  166. C Proceed to right half at this level
  167. C
  168. 60 VL(L) = GLR
  169. 70 EST = GR(L-1)
  170. LR(L) = 1
  171. AA(L) = AA(L) + 4.0D0*HH(L)
  172. GO TO 20
  173. C
  174. C Return one level
  175. C
  176. 80 VR = GLR
  177. 90 IF (L .LE. 1) GO TO 120
  178. L = L - 1
  179. EPS = EPS*2.0D0
  180. EF = EF*SQ2
  181. IF (LR(L)) 100, 100, 110
  182. 100 VL(L) = VL(L+1) + VR
  183. GO TO 70
  184. 110 VR = VL(L+1) + VR
  185. GO TO 90
  186. C
  187. C Exit
  188. C
  189. 120 ANS = VR
  190. IF ((MXL.EQ.0) .OR. (ABS(CE).LE.2.0D0*TOL*AREA)) GO TO 140
  191. IERR = 2
  192. CALL XERMSG ('SLATEC', 'DGAUS8',
  193. + 'ANS is probably insufficiently accurate.', 3, 1)
  194. GO TO 140
  195. 130 IERR = -1
  196. CALL XERMSG ('SLATEC', 'DGAUS8',
  197. + 'A and B are too nearly equal to allow normal integration. $$'
  198. + // 'ANS is set to zero and IERR to -1.', 1, -1)
  199. 140 IF (ERR .LT. 0.0D0) ERR = CE
  200. RETURN
  201. END