pchic.f 13 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341
  1. *DECK PCHIC
  2. SUBROUTINE PCHIC (IC, VC, SWITCH, N, X, F, D, INCFD, WK, NWK,
  3. + IERR)
  4. C***BEGIN PROLOGUE PCHIC
  5. C***PURPOSE Set derivatives needed to determine a piecewise monotone
  6. C piecewise cubic Hermite interpolant to given data.
  7. C User control is available over boundary conditions and/or
  8. C treatment of points where monotonicity switches direction.
  9. C***LIBRARY SLATEC (PCHIP)
  10. C***CATEGORY E1A
  11. C***TYPE SINGLE PRECISION (PCHIC-S, DPCHIC-D)
  12. C***KEYWORDS CUBIC HERMITE INTERPOLATION, MONOTONE INTERPOLATION,
  13. C PCHIP, PIECEWISE CUBIC INTERPOLATION,
  14. C SHAPE-PRESERVING INTERPOLATION
  15. C***AUTHOR Fritsch, F. N., (LLNL)
  16. C Lawrence Livermore National Laboratory
  17. C P.O. Box 808 (L-316)
  18. C Livermore, CA 94550
  19. C FTS 532-4275, (510) 422-4275
  20. C***DESCRIPTION
  21. C
  22. C PCHIC: Piecewise Cubic Hermite Interpolation Coefficients.
  23. C
  24. C Sets derivatives needed to determine a piecewise monotone piece-
  25. C wise cubic interpolant to the data given in X and F satisfying the
  26. C boundary conditions specified by IC and VC.
  27. C
  28. C The treatment of points where monotonicity switches direction is
  29. C controlled by argument SWITCH.
  30. C
  31. C To facilitate two-dimensional applications, includes an increment
  32. C between successive values of the F- and D-arrays.
  33. C
  34. C The resulting piecewise cubic Hermite function may be evaluated
  35. C by PCHFE or PCHFD.
  36. C
  37. C ----------------------------------------------------------------------
  38. C
  39. C Calling sequence:
  40. C
  41. C PARAMETER (INCFD = ...)
  42. C INTEGER IC(2), N, NWK, IERR
  43. C REAL VC(2), SWITCH, X(N), F(INCFD,N), D(INCFD,N), WK(NWK)
  44. C
  45. C CALL PCHIC (IC, VC, SWITCH, N, X, F, D, INCFD, WK, NWK, IERR)
  46. C
  47. C Parameters:
  48. C
  49. C IC -- (input) integer array of length 2 specifying desired
  50. C boundary conditions:
  51. C IC(1) = IBEG, desired condition at beginning of data.
  52. C IC(2) = IEND, desired condition at end of data.
  53. C
  54. C IBEG = 0 for the default boundary condition (the same as
  55. C used by PCHIM).
  56. C If IBEG.NE.0, then its sign indicates whether the boundary
  57. C derivative is to be adjusted, if necessary, to be
  58. C compatible with monotonicity:
  59. C IBEG.GT.0 if no adjustment is to be performed.
  60. C IBEG.LT.0 if the derivative is to be adjusted for
  61. C monotonicity.
  62. C
  63. C Allowable values for the magnitude of IBEG are:
  64. C IBEG = 1 if first derivative at X(1) is given in VC(1).
  65. C IBEG = 2 if second derivative at X(1) is given in VC(1).
  66. C IBEG = 3 to use the 3-point difference formula for D(1).
  67. C (Reverts to the default b.c. if N.LT.3 .)
  68. C IBEG = 4 to use the 4-point difference formula for D(1).
  69. C (Reverts to the default b.c. if N.LT.4 .)
  70. C IBEG = 5 to set D(1) so that the second derivative is con-
  71. C tinuous at X(2). (Reverts to the default b.c. if N.LT.4.)
  72. C This option is somewhat analogous to the "not a knot"
  73. C boundary condition provided by PCHSP.
  74. C
  75. C NOTES (IBEG):
  76. C 1. An error return is taken if ABS(IBEG).GT.5 .
  77. C 2. Only in case IBEG.LE.0 is it guaranteed that the
  78. C interpolant will be monotonic in the first interval.
  79. C If the returned value of D(1) lies between zero and
  80. C 3*SLOPE(1), the interpolant will be monotonic. This
  81. C is **NOT** checked if IBEG.GT.0 .
  82. C 3. If IBEG.LT.0 and D(1) had to be changed to achieve mono-
  83. C tonicity, a warning error is returned.
  84. C
  85. C IEND may take on the same values as IBEG, but applied to
  86. C derivative at X(N). In case IEND = 1 or 2, the value is
  87. C given in VC(2).
  88. C
  89. C NOTES (IEND):
  90. C 1. An error return is taken if ABS(IEND).GT.5 .
  91. C 2. Only in case IEND.LE.0 is it guaranteed that the
  92. C interpolant will be monotonic in the last interval.
  93. C If the returned value of D(1+(N-1)*INCFD) lies between
  94. C zero and 3*SLOPE(N-1), the interpolant will be monotonic.
  95. C This is **NOT** checked if IEND.GT.0 .
  96. C 3. If IEND.LT.0 and D(1+(N-1)*INCFD) had to be changed to
  97. C achieve monotonicity, a warning error is returned.
  98. C
  99. C VC -- (input) real array of length 2 specifying desired boundary
  100. C values, as indicated above.
  101. C VC(1) need be set only if IC(1) = 1 or 2 .
  102. C VC(2) need be set only if IC(2) = 1 or 2 .
  103. C
  104. C SWITCH -- (input) indicates desired treatment of points where
  105. C direction of monotonicity switches:
  106. C Set SWITCH to zero if interpolant is required to be mono-
  107. C tonic in each interval, regardless of monotonicity of data.
  108. C NOTES:
  109. C 1. This will cause D to be set to zero at all switch
  110. C points, thus forcing extrema there.
  111. C 2. The result of using this option with the default boun-
  112. C dary conditions will be identical to using PCHIM, but
  113. C will generally cost more compute time.
  114. C This option is provided only to facilitate comparison
  115. C of different switch and/or boundary conditions.
  116. C Set SWITCH nonzero to use a formula based on the 3-point
  117. C difference formula in the vicinity of switch points.
  118. C If SWITCH is positive, the interpolant on each interval
  119. C containing an extremum is controlled to not deviate from
  120. C the data by more than SWITCH*DFLOC, where DFLOC is the
  121. C maximum of the change of F on this interval and its two
  122. C immediate neighbors.
  123. C If SWITCH is negative, no such control is to be imposed.
  124. C
  125. C N -- (input) number of data points. (Error return if N.LT.2 .)
  126. C
  127. C X -- (input) real array of independent variable values. The
  128. C elements of X must be strictly increasing:
  129. C X(I-1) .LT. X(I), I = 2(1)N.
  130. C (Error return if not.)
  131. C
  132. C F -- (input) real array of dependent variable values to be inter-
  133. C polated. F(1+(I-1)*INCFD) is value corresponding to X(I).
  134. C
  135. C D -- (output) real array of derivative values at the data points.
  136. C These values will determine a monotone cubic Hermite func-
  137. C tion on each subinterval on which the data are monotonic,
  138. C except possibly adjacent to switches in monotonicity.
  139. C The value corresponding to X(I) is stored in
  140. C D(1+(I-1)*INCFD), I=1(1)N.
  141. C No other entries in D are changed.
  142. C
  143. C INCFD -- (input) increment between successive values in F and D.
  144. C This argument is provided primarily for 2-D applications.
  145. C (Error return if INCFD.LT.1 .)
  146. C
  147. C WK -- (scratch) real array of working storage. The user may wish
  148. C to know that the returned values are:
  149. C WK(I) = H(I) = X(I+1) - X(I) ;
  150. C WK(N-1+I) = SLOPE(I) = (F(1,I+1) - F(1,I)) / H(I)
  151. C for I = 1(1)N-1.
  152. C
  153. C NWK -- (input) length of work array.
  154. C (Error return if NWK.LT.2*(N-1) .)
  155. C
  156. C IERR -- (output) error flag.
  157. C Normal return:
  158. C IERR = 0 (no errors).
  159. C Warning errors:
  160. C IERR = 1 if IBEG.LT.0 and D(1) had to be adjusted for
  161. C monotonicity.
  162. C IERR = 2 if IEND.LT.0 and D(1+(N-1)*INCFD) had to be
  163. C adjusted for monotonicity.
  164. C IERR = 3 if both of the above are true.
  165. C "Recoverable" errors:
  166. C IERR = -1 if N.LT.2 .
  167. C IERR = -2 if INCFD.LT.1 .
  168. C IERR = -3 if the X-array is not strictly increasing.
  169. C IERR = -4 if ABS(IBEG).GT.5 .
  170. C IERR = -5 if ABS(IEND).GT.5 .
  171. C IERR = -6 if both of the above are true.
  172. C IERR = -7 if NWK.LT.2*(N-1) .
  173. C (The D-array has not been changed in any of these cases.)
  174. C NOTE: The above errors are checked in the order listed,
  175. C and following arguments have **NOT** been validated.
  176. C
  177. C***REFERENCES 1. F. N. Fritsch, Piecewise Cubic Hermite Interpolation
  178. C Package, Report UCRL-87285, Lawrence Livermore Nation-
  179. C al Laboratory, July 1982. [Poster presented at the
  180. C SIAM 30th Anniversary Meeting, 19-23 July 1982.]
  181. C 2. F. N. Fritsch and J. Butland, A method for construc-
  182. C ting local monotone piecewise cubic interpolants, SIAM
  183. C Journal on Scientific and Statistical Computing 5, 2
  184. C (June 1984), pp. 300-304.
  185. C 3. F. N. Fritsch and R. E. Carlson, Monotone piecewise
  186. C cubic interpolation, SIAM Journal on Numerical Ana-
  187. C lysis 17, 2 (April 1980), pp. 238-246.
  188. C***ROUTINES CALLED PCHCE, PCHCI, PCHCS, XERMSG
  189. C***REVISION HISTORY (YYMMDD)
  190. C 820218 DATE WRITTEN
  191. C 820804 Converted to SLATEC library version.
  192. C 870813 Updated Reference 2.
  193. C 890411 Added SAVE statements (Vers. 3.2).
  194. C 890531 Changed all specific intrinsics to generic. (WRB)
  195. C 890703 Corrected category record. (WRB)
  196. C 890831 Modified array declarations. (WRB)
  197. C 890831 REVISION DATE from Version 3.2
  198. C 891214 Prologue converted to Version 4.0 format. (BAB)
  199. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  200. C 920429 Revised format and order of references. (WRB,FNF)
  201. C***END PROLOGUE PCHIC
  202. C Programming notes:
  203. C
  204. C To produce a double precision version, simply:
  205. C a. Change PCHIC to DPCHIC wherever it occurs,
  206. C b. Change PCHCE to DPCHCE wherever it occurs,
  207. C c. Change PCHCI to DPCHCI wherever it occurs,
  208. C d. Change PCHCS to DPCHCS wherever it occurs,
  209. C e. Change the real declarations to double precision, and
  210. C f. Change the constant ZERO to double precision.
  211. C
  212. C DECLARE ARGUMENTS.
  213. C
  214. INTEGER IC(2), N, INCFD, NWK, IERR
  215. REAL VC(2), SWITCH, X(*), F(INCFD,*), D(INCFD,*), WK(NWK)
  216. C
  217. C DECLARE LOCAL VARIABLES.
  218. C
  219. INTEGER I, IBEG, IEND, NLESS1
  220. REAL ZERO
  221. SAVE ZERO
  222. DATA ZERO /0./
  223. C
  224. C VALIDITY-CHECK ARGUMENTS.
  225. C
  226. C***FIRST EXECUTABLE STATEMENT PCHIC
  227. IF ( N.LT.2 ) GO TO 5001
  228. IF ( INCFD.LT.1 ) GO TO 5002
  229. DO 1 I = 2, N
  230. IF ( X(I).LE.X(I-1) ) GO TO 5003
  231. 1 CONTINUE
  232. C
  233. IBEG = IC(1)
  234. IEND = IC(2)
  235. IERR = 0
  236. IF (ABS(IBEG) .GT. 5) IERR = IERR - 1
  237. IF (ABS(IEND) .GT. 5) IERR = IERR - 2
  238. IF (IERR .LT. 0) GO TO 5004
  239. C
  240. C FUNCTION DEFINITION IS OK -- GO ON.
  241. C
  242. NLESS1 = N - 1
  243. IF ( NWK .LT. 2*NLESS1 ) GO TO 5007
  244. C
  245. C SET UP H AND SLOPE ARRAYS.
  246. C
  247. DO 20 I = 1, NLESS1
  248. WK(I) = X(I+1) - X(I)
  249. WK(NLESS1+I) = (F(1,I+1) - F(1,I)) / WK(I)
  250. 20 CONTINUE
  251. C
  252. C SPECIAL CASE N=2 -- USE LINEAR INTERPOLATION.
  253. C
  254. IF (NLESS1 .GT. 1) GO TO 1000
  255. D(1,1) = WK(2)
  256. D(1,N) = WK(2)
  257. GO TO 3000
  258. C
  259. C NORMAL CASE (N .GE. 3) .
  260. C
  261. 1000 CONTINUE
  262. C
  263. C SET INTERIOR DERIVATIVES AND DEFAULT END CONDITIONS.
  264. C
  265. C --------------------------------------
  266. CALL PCHCI (N, WK(1), WK(N), D, INCFD)
  267. C --------------------------------------
  268. C
  269. C SET DERIVATIVES AT POINTS WHERE MONOTONICITY SWITCHES DIRECTION.
  270. C
  271. IF (SWITCH .EQ. ZERO) GO TO 3000
  272. C ----------------------------------------------------
  273. CALL PCHCS (SWITCH, N, WK(1), WK(N), D, INCFD, IERR)
  274. C ----------------------------------------------------
  275. IF (IERR .NE. 0) GO TO 5008
  276. C
  277. C SET END CONDITIONS.
  278. C
  279. 3000 CONTINUE
  280. IF ( (IBEG.EQ.0) .AND. (IEND.EQ.0) ) GO TO 5000
  281. C -------------------------------------------------------
  282. CALL PCHCE (IC, VC, N, X, WK(1), WK(N), D, INCFD, IERR)
  283. C -------------------------------------------------------
  284. IF (IERR .LT. 0) GO TO 5009
  285. C
  286. C NORMAL RETURN.
  287. C
  288. 5000 CONTINUE
  289. RETURN
  290. C
  291. C ERROR RETURNS.
  292. C
  293. 5001 CONTINUE
  294. C N.LT.2 RETURN.
  295. IERR = -1
  296. CALL XERMSG ('SLATEC', 'PCHIC',
  297. + 'NUMBER OF DATA POINTS LESS THAN TWO', IERR, 1)
  298. RETURN
  299. C
  300. 5002 CONTINUE
  301. C INCFD.LT.1 RETURN.
  302. IERR = -2
  303. CALL XERMSG ('SLATEC', 'PCHIC', 'INCREMENT LESS THAN ONE', IERR,
  304. + 1)
  305. RETURN
  306. C
  307. 5003 CONTINUE
  308. C X-ARRAY NOT STRICTLY INCREASING.
  309. IERR = -3
  310. CALL XERMSG ('SLATEC', 'PCHIC', 'X-ARRAY NOT STRICTLY INCREASING'
  311. + , IERR, 1)
  312. RETURN
  313. C
  314. 5004 CONTINUE
  315. C IC OUT OF RANGE RETURN.
  316. IERR = IERR - 3
  317. CALL XERMSG ('SLATEC', 'PCHIC', 'IC OUT OF RANGE', IERR, 1)
  318. RETURN
  319. C
  320. 5007 CONTINUE
  321. C NWK .LT. 2*(N-1) RETURN.
  322. IERR = -7
  323. CALL XERMSG ('SLATEC', 'PCHIC', 'WORK ARRAY TOO SMALL', IERR, 1)
  324. RETURN
  325. C
  326. 5008 CONTINUE
  327. C ERROR RETURN FROM PCHCS.
  328. IERR = -8
  329. CALL XERMSG ('SLATEC', 'PCHIC', 'ERROR RETURN FROM PCHCS', IERR,
  330. + 1)
  331. RETURN
  332. C
  333. 5009 CONTINUE
  334. C ERROR RETURN FROM PCHCE.
  335. C *** THIS CASE SHOULD NEVER OCCUR ***
  336. IERR = -9
  337. CALL XERMSG ('SLATEC', 'PCHIC', 'ERROR RETURN FROM PCHCE', IERR,
  338. + 1)
  339. RETURN
  340. C------------- LAST LINE OF PCHIC FOLLOWS ------------------------------
  341. END