gaus8.f 6.7 KB

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