bintk.f 7.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187
  1. *DECK BINTK
  2. SUBROUTINE BINTK (X, Y, T, N, K, BCOEF, Q, WORK)
  3. C***BEGIN PROLOGUE BINTK
  4. C***PURPOSE Compute the B-representation of a spline which interpolates
  5. C given data.
  6. C***LIBRARY SLATEC
  7. C***CATEGORY E1A
  8. C***TYPE SINGLE PRECISION (BINTK-S, DBINTK-D)
  9. C***KEYWORDS B-SPLINE, DATA FITTING, INTERPOLATION
  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
  17. C BINTK is the SPLINT routine of the reference.
  18. C
  19. C BINTK produces the B-spline coefficients, BCOEF, of the
  20. C B-spline of order K with knots T(I), I=1,...,N+K, which
  21. C takes on the value Y(I) at X(I), I=1,...,N. The spline or
  22. C any of its derivatives can be evaluated by calls to BVALU.
  23. C The I-th equation of the linear system A*BCOEF = B for the
  24. C coefficients of the interpolant enforces interpolation at
  25. C X(I)), I=1,...,N. Hence, B(I) = Y(I), all I, and A is
  26. C a band matrix with 2K-1 bands if A is invertible. The matrix
  27. C A is generated row by row and stored, diagonal by diagonal,
  28. C in the rows of Q, with the main diagonal going into row K.
  29. C The banded system is then solved by a call to BNFAC (which
  30. C constructs the triangular factorization for A and stores it
  31. C again in Q), followed by a call to BNSLV (which then
  32. C obtains the solution BCOEF by substitution). BNFAC does no
  33. C pivoting, since the total positivity of the matrix A makes
  34. C this unnecessary. The linear system to be solved is
  35. C (theoretically) invertible if and only if
  36. C T(I) .LT. X(I)) .LT. T(I+K), all I.
  37. C Equality is permitted on the left for I=1 and on the right
  38. C for I=N when K knots are used at X(1) or X(N). Otherwise,
  39. C violation of this condition is certain to lead to an error.
  40. C
  41. C Description of Arguments
  42. C Input
  43. C X - vector of length N containing data point abscissa
  44. C in strictly increasing order.
  45. C Y - corresponding vector of length N containing data
  46. C point ordinates.
  47. C T - knot vector of length N+K
  48. C since T(1),..,T(K) .LE. X(1) and T(N+1),..,T(N+K)
  49. C .GE. X(N), this leaves only N-K knots (not nec-
  50. C essarily X(I)) values) interior to (X(1),X(N))
  51. C N - number of data points, N .GE. K
  52. C K - order of the spline, K .GE. 1
  53. C
  54. C Output
  55. C BCOEF - a vector of length N containing the B-spline
  56. C coefficients
  57. C Q - a work vector of length (2*K-1)*N, containing
  58. C the triangular factorization of the coefficient
  59. C matrix of the linear system being solved. The
  60. C coefficients for the interpolant of an
  61. C additional data set (X(I)),YY(I)), I=1,...,N
  62. C with the same abscissa can be obtained by loading
  63. C YY into BCOEF and then executing
  64. C CALL BNSLV (Q,2K-1,N,K-1,K-1,BCOEF)
  65. C WORK - work vector of length 2*K
  66. C
  67. C Error Conditions
  68. C Improper input is a fatal error
  69. C Singular system of equations is a fatal error
  70. C
  71. C***REFERENCES D. E. Amos, Computation with splines and B-splines,
  72. C Report SAND78-1968, Sandia Laboratories, March 1979.
  73. C Carl de Boor, Package for calculating with B-splines,
  74. C SIAM Journal on Numerical Analysis 14, 3 (June 1977),
  75. C pp. 441-472.
  76. C Carl de Boor, A Practical Guide to Splines, Applied
  77. C Mathematics Series 27, Springer-Verlag, New York,
  78. C 1978.
  79. C***ROUTINES CALLED BNFAC, BNSLV, BSPVN, XERMSG
  80. C***REVISION HISTORY (YYMMDD)
  81. C 800901 DATE WRITTEN
  82. C 890531 Changed all specific intrinsics to generic. (WRB)
  83. C 890831 Modified array declarations. (WRB)
  84. C 890831 REVISION DATE from Version 3.2
  85. C 891214 Prologue converted to Version 4.0 format. (BAB)
  86. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  87. C 900326 Removed duplicate information from DESCRIPTION section.
  88. C (WRB)
  89. C 920501 Reformatted the REFERENCES section. (WRB)
  90. C***END PROLOGUE BINTK
  91. C
  92. INTEGER IFLAG, IWORK, K, N, I, ILP1MX, J, JJ, KM1, KPKM2, LEFT,
  93. 1 LENQ, NP1
  94. REAL BCOEF(*), Y(*), Q(*), T(*), X(*), XI, WORK(*)
  95. C DIMENSION Q(2*K-1,N), T(N+K)
  96. C***FIRST EXECUTABLE STATEMENT BINTK
  97. IF(K.LT.1) GO TO 100
  98. IF(N.LT.K) GO TO 105
  99. JJ = N - 1
  100. IF(JJ.EQ.0) GO TO 6
  101. DO 5 I=1,JJ
  102. IF(X(I).GE.X(I+1)) GO TO 110
  103. 5 CONTINUE
  104. 6 CONTINUE
  105. NP1 = N + 1
  106. KM1 = K - 1
  107. KPKM2 = 2*KM1
  108. LEFT = K
  109. C ZERO OUT ALL ENTRIES OF Q
  110. LENQ = N*(K+KM1)
  111. DO 10 I=1,LENQ
  112. Q(I) = 0.0E0
  113. 10 CONTINUE
  114. C
  115. C *** LOOP OVER I TO CONSTRUCT THE N INTERPOLATION EQUATIONS
  116. DO 50 I=1,N
  117. XI = X(I)
  118. ILP1MX = MIN(I+K,NP1)
  119. C *** FIND LEFT IN THE CLOSED INTERVAL (I,I+K-1) SUCH THAT
  120. C T(LEFT) .LE. X(I) .LT. T(LEFT+1)
  121. C MATRIX IS SINGULAR IF THIS IS NOT POSSIBLE
  122. LEFT = MAX(LEFT,I)
  123. IF (XI.LT.T(LEFT)) GO TO 80
  124. 20 IF (XI.LT.T(LEFT+1)) GO TO 30
  125. LEFT = LEFT + 1
  126. IF (LEFT.LT.ILP1MX) GO TO 20
  127. LEFT = LEFT - 1
  128. IF (XI.GT.T(LEFT+1)) GO TO 80
  129. C *** THE I-TH EQUATION ENFORCES INTERPOLATION AT XI, HENCE
  130. C A(I,J) = B(J,K,T)(XI), ALL J. ONLY THE K ENTRIES WITH J =
  131. C LEFT-K+1,...,LEFT ACTUALLY MIGHT BE NONZERO. THESE K NUMBERS
  132. C ARE RETURNED, IN BCOEF (USED FOR TEMP. STORAGE HERE), BY THE
  133. C FOLLOWING
  134. 30 CALL BSPVN(T, K, K, 1, XI, LEFT, BCOEF, WORK, IWORK)
  135. C WE THEREFORE WANT BCOEF(J) = B(LEFT-K+J)(XI) TO GO INTO
  136. C A(I,LEFT-K+J), I.E., INTO Q(I-(LEFT+J)+2*K,(LEFT+J)-K) SINCE
  137. C A(I+J,J) IS TO GO INTO Q(I+K,J), ALL I,J, IF WE CONSIDER Q
  138. C AS A TWO-DIM. ARRAY , WITH 2*K-1 ROWS (SEE COMMENTS IN
  139. C BNFAC). IN THE PRESENT PROGRAM, WE TREAT Q AS AN EQUIVALENT
  140. C ONE-DIMENSIONAL ARRAY (BECAUSE OF FORTRAN RESTRICTIONS ON
  141. C DIMENSION STATEMENTS) . WE THEREFORE WANT BCOEF(J) TO GO INTO
  142. C ENTRY
  143. C I -(LEFT+J) + 2*K + ((LEFT+J) - K-1)*(2*K-1)
  144. C = I-LEFT+1 + (LEFT -K)*(2*K-1) + (2*K-2)*J
  145. C OF Q .
  146. JJ = I - LEFT + 1 + (LEFT-K)*(K+KM1)
  147. DO 40 J=1,K
  148. JJ = JJ + KPKM2
  149. Q(JJ) = BCOEF(J)
  150. 40 CONTINUE
  151. 50 CONTINUE
  152. C
  153. C ***OBTAIN FACTORIZATION OF A , STORED AGAIN IN Q.
  154. CALL BNFAC(Q, K+KM1, N, KM1, KM1, IFLAG)
  155. GO TO (60, 90), IFLAG
  156. C *** SOLVE A*BCOEF = Y BY BACKSUBSTITUTION
  157. 60 DO 70 I=1,N
  158. BCOEF(I) = Y(I)
  159. 70 CONTINUE
  160. CALL BNSLV(Q, K+KM1, N, KM1, KM1, BCOEF)
  161. RETURN
  162. C
  163. C
  164. 80 CONTINUE
  165. CALL XERMSG ('SLATEC', 'BINTK',
  166. + 'SOME ABSCISSA WAS NOT IN THE SUPPORT OF THE CORRESPONDING ' //
  167. + 'BASIS FUNCTION AND THE SYSTEM IS SINGULAR.', 2, 1)
  168. RETURN
  169. 90 CONTINUE
  170. CALL XERMSG ('SLATEC', 'BINTK',
  171. + 'THE SYSTEM OF SOLVER DETECTS A SINGULAR SYSTEM ALTHOUGH ' //
  172. + 'THE THEORETICAL CONDITIONS FOR A SOLUTION WERE SATISFIED.',
  173. + 8, 1)
  174. RETURN
  175. 100 CONTINUE
  176. CALL XERMSG ('SLATEC', 'BINTK', 'K DOES NOT SATISFY K.GE.1', 2,
  177. + 1)
  178. RETURN
  179. 105 CONTINUE
  180. CALL XERMSG ('SLATEC', 'BINTK', 'N DOES NOT SATISFY N.GE.K', 2,
  181. + 1)
  182. RETURN
  183. 110 CONTINUE
  184. CALL XERMSG ('SLATEC', 'BINTK',
  185. + 'X(I) DOES NOT SATISFY X(I).LT.X(I+1) FOR SOME I', 2, 1)
  186. RETURN
  187. END