bspev.f 4.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138
  1. *DECK BSPEV
  2. SUBROUTINE BSPEV (T, AD, N, K, NDERIV, X, INEV, SVALUE, WORK)
  3. C***BEGIN PROLOGUE BSPEV
  4. C***PURPOSE Calculate the value of the spline and its derivatives from
  5. C the B-representation.
  6. C***LIBRARY SLATEC
  7. C***CATEGORY E3, K6
  8. C***TYPE SINGLE PRECISION (BSPEV-S, DBSPEV-D)
  9. C***KEYWORDS B-SPLINE, DATA FITTING, INTERPOLATION, SPLINES
  10. C***AUTHOR Amos, D. E., (SNLA)
  11. C***DESCRIPTION
  12. C
  13. C Written by Carl de Boor and modified by D. E. Amos
  14. C
  15. C Abstract
  16. C BSPEV is the BSPLEV routine of the reference.
  17. C
  18. C BSPEV calculates the value of the spline and its derivatives
  19. C at X from the B-representation (T,A,N,K) and returns them
  20. C in SVALUE(I),I=1,NDERIV, T(K) .LE. X .LE. T(N+1). AD(I) can
  21. C be the B-spline coefficients A(I), I=1,N if NDERIV=1. Other-
  22. C wise AD must be computed before hand by a call to BSPDR (T,A,
  23. C N,K,NDERIV,AD). If X=T(I),I=K,N, right limiting values are
  24. C obtained.
  25. C
  26. C To compute left derivatives or left limiting values at a
  27. C knot T(I), replace N by I-1 and set X=T(I), I=K+1,N+1.
  28. C
  29. C BSPEV calls INTRV, BSPVN
  30. C
  31. C Description of Arguments
  32. C Input
  33. C T - knot vector of length N+K
  34. C AD - vector of length (2*N-NDERIV+1)*NDERIV/2 containing
  35. C the difference table from BSPDR.
  36. C N - number of B-spline coefficients
  37. C N = sum of knot multiplicities-K
  38. C K - order of the B-spline, K .GE. 1
  39. C NDERIV - number of derivatives, 1 .LE. NDERIV .LE. K.
  40. C NDERIV=1 gives the zero-th derivative = function
  41. C value
  42. C X - argument, T(K) .LE. X .LE. T(N+1)
  43. C INEV - an initialization parameter which must be set
  44. C to 1 the first time BSPEV is called.
  45. C
  46. C Output
  47. C INEV - INEV contains information for efficient process-
  48. C ing after the initial call and INEV must not
  49. C be changed by the user. Distinct splines require
  50. C distinct INEV parameters.
  51. C SVALUE - vector of length NDERIV containing the spline
  52. C value in SVALUE(1) and the NDERIV-1 derivatives
  53. C in the remaining components.
  54. C WORK - work vector of length 3*K
  55. C
  56. C Error Conditions
  57. C Improper input is a fatal error.
  58. C
  59. C***REFERENCES Carl de Boor, Package for calculating with B-splines,
  60. C SIAM Journal on Numerical Analysis 14, 3 (June 1977),
  61. C pp. 441-472.
  62. C***ROUTINES CALLED BSPVN, INTRV, XERMSG
  63. C***REVISION HISTORY (YYMMDD)
  64. C 800901 DATE WRITTEN
  65. C 890831 Modified array declarations. (WRB)
  66. C 890831 REVISION DATE from Version 3.2
  67. C 891214 Prologue converted to Version 4.0 format. (BAB)
  68. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  69. C 900326 Removed duplicate information from DESCRIPTION section.
  70. C (WRB)
  71. C 920501 Reformatted the REFERENCES section. (WRB)
  72. C***END PROLOGUE BSPEV
  73. C
  74. INTEGER I,ID,INEV,IWORK,JJ,K,KP1,KP1MN,L,LEFT,LL,MFLAG,
  75. 1 N, NDERIV
  76. REAL AD, SVALUE, SUM, T, WORK, X
  77. C DIMENSION T(N+K)
  78. DIMENSION T(*), AD(*), SVALUE(*), WORK(*)
  79. C***FIRST EXECUTABLE STATEMENT BSPEV
  80. IF(K.LT.1) GO TO 100
  81. IF(N.LT.K) GO TO 105
  82. IF(NDERIV.LT.1 .OR. NDERIV.GT.K) GO TO 115
  83. ID = NDERIV
  84. CALL INTRV(T, N+1, X, INEV, I, MFLAG)
  85. IF (X.LT.T(K)) GO TO 110
  86. IF (MFLAG.EQ.0) GO TO 30
  87. IF (X.GT.T(I)) GO TO 110
  88. 20 IF (I.EQ.K) GO TO 120
  89. I = I - 1
  90. IF (X.EQ.T(I)) GO TO 20
  91. C
  92. C *I* HAS BEEN FOUND IN (K,N) SO THAT T(I) .LE. X .LT. T(I+1)
  93. C (OR .LE. T(I+1), IF T(I) .LT. T(I+1) = T(N+1) ).
  94. 30 KP1MN = K + 1 - ID
  95. KP1 = K + 1
  96. CALL BSPVN(T, KP1MN, K, 1, X, I, WORK(1),WORK(KP1),IWORK)
  97. JJ = (N+N-ID+2)*(ID-1)/2
  98. C ADIF(LEFTPL,ID) = AD(LEFTPL-ID+1 + (2*N-ID+2)*(ID-1)/2)
  99. C LEFTPL = LEFT + L
  100. 40 LEFT = I - KP1MN
  101. SUM = 0.0E0
  102. LL = LEFT + JJ + 2 - ID
  103. DO 50 L=1,KP1MN
  104. SUM = SUM + WORK(L)*AD(LL)
  105. LL = LL + 1
  106. 50 CONTINUE
  107. SVALUE(ID) = SUM
  108. ID = ID - 1
  109. IF (ID.EQ.0) GO TO 60
  110. JJ = JJ-(N-ID+1)
  111. KP1MN = KP1MN + 1
  112. CALL BSPVN(T, KP1MN, K, 2, X, I, WORK(1), WORK(KP1),IWORK)
  113. GO TO 40
  114. C
  115. 60 RETURN
  116. C
  117. C
  118. 100 CONTINUE
  119. CALL XERMSG ('SLATEC', 'BSPEV', 'K DOES NOT SATISFY K.GE.1', 2,
  120. + 1)
  121. RETURN
  122. 105 CONTINUE
  123. CALL XERMSG ('SLATEC', 'BSPEV', 'N DOES NOT SATISFY N.GE.K', 2,
  124. + 1)
  125. RETURN
  126. 110 CONTINUE
  127. CALL XERMSG ('SLATEC', 'BSPEV', 'X IS NOT IN T(K).LE.X.LE.T(N+1)'
  128. + , 2, 1)
  129. RETURN
  130. 115 CONTINUE
  131. CALL XERMSG ('SLATEC', 'BSPEV',
  132. + 'NDERIV DOES NOT SATISFY 1.LE.NDERIV.LE.K', 2, 1)
  133. RETURN
  134. 120 CONTINUE
  135. CALL XERMSG ('SLATEC', 'BSPEV',
  136. + 'A LEFT LIMITING VALUE CANNOT BE OBTAINED AT T(K)', 2, 1)
  137. RETURN
  138. END