dbfqad.f 4.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137
  1. *DECK DBFQAD
  2. SUBROUTINE DBFQAD (F, T, BCOEF, N, K, ID, X1, X2, TOL, QUAD, IERR,
  3. + WORK)
  4. C***BEGIN PROLOGUE DBFQAD
  5. C***PURPOSE Compute the integral of a product of a function and a
  6. C derivative of a K-th order B-spline.
  7. C***LIBRARY SLATEC
  8. C***CATEGORY H2A2A1, E3, K6
  9. C***TYPE DOUBLE PRECISION (BFQAD-S, DBFQAD-D)
  10. C***KEYWORDS INTEGRAL OF B-SPLINE, QUADRATURE
  11. C***AUTHOR Amos, D. E., (SNLA)
  12. C***DESCRIPTION
  13. C
  14. C Abstract **** a double precision routine ****
  15. C
  16. C DBFQAD computes the integral on (X1,X2) of a product of a
  17. C function F and the ID-th derivative of a K-th order B-spline,
  18. C using the B-representation (T,BCOEF,N,K). (X1,X2) must be a
  19. C subinterval of T(K) .LE. X .LE. T(N+1). An integration rou-
  20. C tine, DBSGQ8 (a modification of GAUS8), integrates the product
  21. C on subintervals of (X1,X2) formed by included (distinct) knots
  22. C
  23. C The maximum number of significant digits obtainable in
  24. C DBSQAD is the smaller of 18 and the number of digits
  25. C carried in double precision arithmetic.
  26. C
  27. C Description of Arguments
  28. C Input F,T,BCOEF,X1,X2,TOL are double precision
  29. C F - external function of one argument for the
  30. C integrand BF(X)=F(X)*DBVALU(T,BCOEF,N,K,ID,X,INBV,
  31. C WORK)
  32. C T - knot array of length N+K
  33. C BCOEF - coefficient array of length N
  34. C N - length of coefficient array
  35. C K - order of B-spline, K .GE. 1
  36. C ID - order of the spline derivative, 0 .LE. ID .LE. K-1
  37. C ID=0 gives the spline function
  38. C X1,X2 - end points of quadrature interval in
  39. C T(K) .LE. X .LE. T(N+1)
  40. C TOL - desired accuracy for the quadrature, suggest
  41. C 10.*DTOL .LT. TOL .LE. .1 where DTOL is the maximum
  42. C of 1.0D-18 and double precision unit roundoff for
  43. C the machine = D1MACH(4)
  44. C
  45. C Output QUAD,WORK are double precision
  46. C QUAD - integral of BF(X) on (X1,X2)
  47. C IERR - a status code
  48. C IERR=1 normal return
  49. C 2 some quadrature on (X1,X2) does not meet
  50. C the requested tolerance.
  51. C WORK - work vector of length 3*K
  52. C
  53. C Error Conditions
  54. C Improper input is a fatal error
  55. C Some quadrature fails to meet the requested tolerance
  56. C
  57. C***REFERENCES D. E. Amos, Quadrature subroutines for splines and
  58. C B-splines, Report SAND79-1825, Sandia Laboratories,
  59. C December 1979.
  60. C***ROUTINES CALLED D1MACH, DBSGQ8, DINTRV, XERMSG
  61. C***REVISION HISTORY (YYMMDD)
  62. C 800901 DATE WRITTEN
  63. C 890531 Changed all specific intrinsics to generic. (WRB)
  64. C 890531 REVISION DATE from Version 3.2
  65. C 891214 Prologue converted to Version 4.0 format. (BAB)
  66. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  67. C 900326 Removed duplicate information from DESCRIPTION section.
  68. C (WRB)
  69. C 920501 Reformatted the REFERENCES section. (WRB)
  70. C***END PROLOGUE DBFQAD
  71. C
  72. C
  73. INTEGER ID, IERR, IFLG, ILO, IL1, IL2, K, LEFT, MFLAG, N, NPK, NP1
  74. DOUBLE PRECISION A,AA,ANS,B,BB,BCOEF,Q,QUAD,T,TA,TB,TOL,WORK,WTOL,
  75. 1 X1, X2
  76. DOUBLE PRECISION D1MACH, F
  77. DIMENSION T(*), BCOEF(*), WORK(*)
  78. EXTERNAL F
  79. C***FIRST EXECUTABLE STATEMENT DBFQAD
  80. IERR = 1
  81. QUAD = 0.0D0
  82. IF(K.LT.1) GO TO 100
  83. IF(N.LT.K) GO TO 105
  84. IF(ID.LT.0 .OR. ID.GE.K) GO TO 110
  85. WTOL = D1MACH(4)
  86. WTOL = MAX(WTOL,1.D-18)
  87. IF (TOL.LT.WTOL .OR. TOL.GT.0.1D0) GO TO 30
  88. AA = MIN(X1,X2)
  89. BB = MAX(X1,X2)
  90. IF (AA.LT.T(K)) GO TO 20
  91. NP1 = N + 1
  92. IF (BB.GT.T(NP1)) GO TO 20
  93. IF (AA.EQ.BB) RETURN
  94. NPK = N + K
  95. C
  96. ILO = 1
  97. CALL DINTRV(T, NPK, AA, ILO, IL1, MFLAG)
  98. CALL DINTRV(T, NPK, BB, ILO, IL2, MFLAG)
  99. IF (IL2.GE.NP1) IL2 = N
  100. INBV = 1
  101. Q = 0.0D0
  102. DO 10 LEFT=IL1,IL2
  103. TA = T(LEFT)
  104. TB = T(LEFT+1)
  105. IF (TA.EQ.TB) GO TO 10
  106. A = MAX(AA,TA)
  107. B = MIN(BB,TB)
  108. CALL DBSGQ8(F,T,BCOEF,N,K,ID,A,B,INBV,TOL,ANS,IFLG,WORK)
  109. IF (IFLG.GT.1) IERR = 2
  110. Q = Q + ANS
  111. 10 CONTINUE
  112. IF (X1.GT.X2) Q = -Q
  113. QUAD = Q
  114. RETURN
  115. C
  116. C
  117. 20 CONTINUE
  118. CALL XERMSG ('SLATEC', 'DBFQAD',
  119. + 'X1 OR X2 OR BOTH DO NOT SATISFY T(K).LE.X.LE.T(N+1)', 2, 1)
  120. RETURN
  121. 30 CONTINUE
  122. CALL XERMSG ('SLATEC', 'DBFQAD',
  123. + 'TOL IS LESS DTOL OR GREATER THAN 0.1', 2, 1)
  124. RETURN
  125. 100 CONTINUE
  126. CALL XERMSG ('SLATEC', 'DBFQAD', 'K DOES NOT SATISFY K.GE.1', 2,
  127. + 1)
  128. RETURN
  129. 105 CONTINUE
  130. CALL XERMSG ('SLATEC', 'DBFQAD', 'N DOES NOT SATISFY N.GE.K', 2,
  131. + 1)
  132. RETURN
  133. 110 CONTINUE
  134. CALL XERMSG ('SLATEC', 'DBFQAD',
  135. + 'ID DOES NOT SATISFY 0.LE.ID.LT.K', 2, 1)
  136. RETURN
  137. END