dbspev.f 4.9 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137
  1. *DECK DBSPEV
  2. SUBROUTINE DBSPEV (T, AD, N, K, NDERIV, X, INEV, SVALUE, WORK)
  3. C***BEGIN PROLOGUE DBSPEV
  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 DOUBLE 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 **** a double precision routine ****
  16. C DBSPEV is the BSPLEV routine of the reference.
  17. C
  18. C DBSPEV calculates the value of the spline and its derivatives
  19. C at X from the B-representation (T,A,N,K) and returns them in
  20. C SVALUE(I),I=1,NDERIV, T(K) .LE. X .LE. T(N+1). AD(I) can be
  21. C the B-spline coefficients A(I), I=1,N) if NDERIV=1. Otherwise
  22. C AD must be computed before hand by a call to DBSPDR (T,A,N,K,
  23. C 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 DBSPEV calls DINTRV, DBSPVN
  30. C
  31. C Description of Arguments
  32. C
  33. C Input T,AD,X, are double precision
  34. C T - knot vector of length N+K
  35. C AD - vector of length (2*N-NDERIV+1)*NDERIV/2 containing
  36. C the difference table from DBSPDR.
  37. C N - number of B-spline coefficients
  38. C N = sum of knot multiplicities-K
  39. C K - order of the B-spline, K .GE. 1
  40. C NDERIV - number of derivatives, 1 .LE. NDERIV .LE. K.
  41. C NDERIV=1 gives the zero-th derivative =
  42. C function value
  43. C X - argument, T(K) .LE. X .LE. T(N+1)
  44. C INEV - an initialization parameter which must be set
  45. C to 1 the first time DBSPEV is called.
  46. C
  47. C Output SVALUE,WORK are double precision
  48. C INEV - INEV contains information for efficient process-
  49. C ing after the initial call and INEV must not
  50. C be changed by the user. Distinct splines require
  51. C distinct INEV parameters.
  52. C SVALUE - vector of length NDERIV containing the spline
  53. C value in SVALUE(1) and the NDERIV-1 derivatives
  54. C in the remaining components.
  55. C WORK - work vector of length 3*K
  56. C
  57. C Error Conditions
  58. C Improper input is a fatal error.
  59. C
  60. C***REFERENCES Carl de Boor, Package for calculating with B-splines,
  61. C SIAM Journal on Numerical Analysis 14, 3 (June 1977),
  62. C pp. 441-472.
  63. C***ROUTINES CALLED DBSPVN, DINTRV, XERMSG
  64. C***REVISION HISTORY (YYMMDD)
  65. C 800901 DATE WRITTEN
  66. C 890831 Modified array declarations. (WRB)
  67. C 890831 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 920501 Reformatted the REFERENCES section. (WRB)
  71. C***END PROLOGUE DBSPEV
  72. C
  73. INTEGER I,ID,INEV,IWORK,JJ,K,KP1,KP1MN,L,LEFT,LL,MFLAG,
  74. 1 N, NDERIV
  75. DOUBLE PRECISION AD, SVALUE, SUM, T, WORK, X
  76. C DIMENSION T(N+K)
  77. DIMENSION T(*), AD(*), SVALUE(*), WORK(*)
  78. C***FIRST EXECUTABLE STATEMENT DBSPEV
  79. IF(K.LT.1) GO TO 100
  80. IF(N.LT.K) GO TO 105
  81. IF(NDERIV.LT.1 .OR. NDERIV.GT.K) GO TO 115
  82. ID = NDERIV
  83. CALL DINTRV(T, N+1, X, INEV, I, MFLAG)
  84. IF (X.LT.T(K)) GO TO 110
  85. IF (MFLAG.EQ.0) GO TO 30
  86. IF (X.GT.T(I)) GO TO 110
  87. 20 IF (I.EQ.K) GO TO 120
  88. I = I - 1
  89. IF (X.EQ.T(I)) GO TO 20
  90. C
  91. C *I* HAS BEEN FOUND IN (K,N) SO THAT T(I) .LE. X .LT. T(I+1)
  92. C (OR .LE. T(I+1), IF T(I) .LT. T(I+1) = T(N+1) ).
  93. 30 KP1MN = K + 1 - ID
  94. KP1 = K + 1
  95. CALL DBSPVN(T, KP1MN, K, 1, X, I, WORK(1),WORK(KP1),IWORK)
  96. JJ = (N+N-ID+2)*(ID-1)/2
  97. C ADIF(LEFTPL,ID) = AD(LEFTPL-ID+1 + (2*N-ID+2)*(ID-1)/2)
  98. C LEFTPL = LEFT + L
  99. 40 LEFT = I - KP1MN
  100. SUM = 0.0D0
  101. LL = LEFT + JJ + 2 - ID
  102. DO 50 L=1,KP1MN
  103. SUM = SUM + WORK(L)*AD(LL)
  104. LL = LL + 1
  105. 50 CONTINUE
  106. SVALUE(ID) = SUM
  107. ID = ID - 1
  108. IF (ID.EQ.0) GO TO 60
  109. JJ = JJ-(N-ID+1)
  110. KP1MN = KP1MN + 1
  111. CALL DBSPVN(T, KP1MN, K, 2, X, I, WORK(1), WORK(KP1),IWORK)
  112. GO TO 40
  113. C
  114. 60 RETURN
  115. C
  116. C
  117. 100 CONTINUE
  118. CALL XERMSG ('SLATEC', 'DBSPEV', 'K DOES NOT SATISFY K.GE.1', 2,
  119. + 1)
  120. RETURN
  121. 105 CONTINUE
  122. CALL XERMSG ('SLATEC', 'DBSPEV', 'N DOES NOT SATISFY N.GE.K', 2,
  123. + 1)
  124. RETURN
  125. 110 CONTINUE
  126. CALL XERMSG ('SLATEC', 'DBSPEV',
  127. + 'X IS NOT IN T(K).LE.X.LE.T(N+1)', 2, 1)
  128. RETURN
  129. 115 CONTINUE
  130. CALL XERMSG ('SLATEC', 'DBSPEV',
  131. + 'NDERIV DOES NOT SATISFY 1.LE.NDERIV.LE.K', 2, 1)
  132. RETURN
  133. 120 CONTINUE
  134. CALL XERMSG ('SLATEC', 'DBSPEV',
  135. + 'A LEFT LIMITING VALUE CANNOT BE OBTAINED AT T(K)', 2, 1)
  136. RETURN
  137. END