dpchim.f 9.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283
  1. *DECK DPCHIM
  2. SUBROUTINE DPCHIM (N, X, F, D, INCFD, IERR)
  3. C***BEGIN PROLOGUE DPCHIM
  4. C***PURPOSE Set derivatives needed to determine a monotone piecewise
  5. C cubic Hermite interpolant to given data. Boundary values
  6. C are provided which are compatible with monotonicity. The
  7. C interpolant will have an extremum at each point where mono-
  8. C tonicity switches direction. (See DPCHIC if user control
  9. C is desired over boundary or switch conditions.)
  10. C***LIBRARY SLATEC (PCHIP)
  11. C***CATEGORY E1A
  12. C***TYPE DOUBLE PRECISION (PCHIM-S, DPCHIM-D)
  13. C***KEYWORDS CUBIC HERMITE INTERPOLATION, MONOTONE INTERPOLATION,
  14. C PCHIP, PIECEWISE CUBIC 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 DPCHIM: Piecewise Cubic Hermite Interpolation to
  23. C Monotone data.
  24. C
  25. C Sets derivatives needed to determine a monotone piecewise cubic
  26. C Hermite interpolant to the data given in X and F.
  27. C
  28. C Default boundary conditions are provided which are compatible
  29. C with monotonicity. (See DPCHIC if user control of boundary con-
  30. C ditions is desired.)
  31. C
  32. C If the data are only piecewise monotonic, the interpolant will
  33. C have an extremum at each point where monotonicity switches direc-
  34. C tion. (See DPCHIC if user control is desired in such cases.)
  35. C
  36. C To facilitate two-dimensional applications, includes an increment
  37. C between successive values of the F- and D-arrays.
  38. C
  39. C The resulting piecewise cubic Hermite function may be evaluated
  40. C by DPCHFE or DPCHFD.
  41. C
  42. C ----------------------------------------------------------------------
  43. C
  44. C Calling sequence:
  45. C
  46. C PARAMETER (INCFD = ...)
  47. C INTEGER N, IERR
  48. C DOUBLE PRECISION X(N), F(INCFD,N), D(INCFD,N)
  49. C
  50. C CALL DPCHIM (N, X, F, D, INCFD, IERR)
  51. C
  52. C Parameters:
  53. C
  54. C N -- (input) number of data points. (Error return if N.LT.2 .)
  55. C If N=2, simply does linear interpolation.
  56. C
  57. C X -- (input) real*8 array of independent variable values. The
  58. C elements of X must be strictly increasing:
  59. C X(I-1) .LT. X(I), I = 2(1)N.
  60. C (Error return if not.)
  61. C
  62. C F -- (input) real*8 array of dependent variable values to be
  63. C interpolated. F(1+(I-1)*INCFD) is value corresponding to
  64. C X(I). DPCHIM is designed for monotonic data, but it will
  65. C work for any F-array. It will force extrema at points where
  66. C monotonicity switches direction. If some other treatment of
  67. C switch points is desired, DPCHIC should be used instead.
  68. C -----
  69. C D -- (output) real*8 array of derivative values at the data
  70. C points. If the data are monotonic, these values will
  71. C determine a monotone cubic Hermite function.
  72. C The value corresponding to X(I) is stored in
  73. C D(1+(I-1)*INCFD), I=1(1)N.
  74. C No other entries in D are changed.
  75. C
  76. C INCFD -- (input) increment between successive values in F and D.
  77. C This argument is provided primarily for 2-D applications.
  78. C (Error return if INCFD.LT.1 .)
  79. C
  80. C IERR -- (output) error flag.
  81. C Normal return:
  82. C IERR = 0 (no errors).
  83. C Warning error:
  84. C IERR.GT.0 means that IERR switches in the direction
  85. C of monotonicity were detected.
  86. C "Recoverable" errors:
  87. C IERR = -1 if N.LT.2 .
  88. C IERR = -2 if INCFD.LT.1 .
  89. C IERR = -3 if the X-array is not strictly increasing.
  90. C (The D-array has not been changed in any of these cases.)
  91. C NOTE: The above errors are checked in the order listed,
  92. C and following arguments have **NOT** been validated.
  93. C
  94. C***REFERENCES 1. F. N. Fritsch and J. Butland, A method for construc-
  95. C ting local monotone piecewise cubic interpolants, SIAM
  96. C Journal on Scientific and Statistical Computing 5, 2
  97. C (June 1984), pp. 300-304.
  98. C 2. F. N. Fritsch and R. E. Carlson, Monotone piecewise
  99. C cubic interpolation, SIAM Journal on Numerical Ana-
  100. C lysis 17, 2 (April 1980), pp. 238-246.
  101. C***ROUTINES CALLED DPCHST, XERMSG
  102. C***REVISION HISTORY (YYMMDD)
  103. C 811103 DATE WRITTEN
  104. C 820201 1. Introduced DPCHST to reduce possible over/under-
  105. C flow problems.
  106. C 2. Rearranged derivative formula for same reason.
  107. C 820602 1. Modified end conditions to be continuous functions
  108. C of data when monotonicity switches in next interval.
  109. C 2. Modified formulas so end conditions are less prone
  110. C of over/underflow problems.
  111. C 820803 Minor cosmetic changes for release 1.
  112. C 870707 Corrected XERROR calls for d.p. name(s).
  113. C 870813 Updated Reference 1.
  114. C 890206 Corrected XERROR calls.
  115. C 890411 Added SAVE statements (Vers. 3.2).
  116. C 890531 Changed all specific intrinsics to generic. (WRB)
  117. C 890703 Corrected category record. (WRB)
  118. C 890831 Modified array declarations. (WRB)
  119. C 891006 Cosmetic changes to prologue. (WRB)
  120. C 891006 REVISION DATE from Version 3.2
  121. C 891214 Prologue converted to Version 4.0 format. (BAB)
  122. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  123. C 920429 Revised format and order of references. (WRB,FNF)
  124. C***END PROLOGUE DPCHIM
  125. C Programming notes:
  126. C
  127. C 1. The function DPCHST(ARG1,ARG2) is assumed to return zero if
  128. C either argument is zero, +1 if they are of the same sign, and
  129. C -1 if they are of opposite sign.
  130. C 2. To produce a single precision version, simply:
  131. C a. Change DPCHIM to PCHIM wherever it occurs,
  132. C b. Change DPCHST to PCHST wherever it occurs,
  133. C c. Change all references to the Fortran intrinsics to their
  134. C single precision equivalents,
  135. C d. Change the double precision declarations to real, and
  136. C e. Change the constants ZERO and THREE to single precision.
  137. C
  138. C DECLARE ARGUMENTS.
  139. C
  140. INTEGER N, INCFD, IERR
  141. DOUBLE PRECISION X(*), F(INCFD,*), D(INCFD,*)
  142. C
  143. C DECLARE LOCAL VARIABLES.
  144. C
  145. INTEGER I, NLESS1
  146. DOUBLE PRECISION DEL1, DEL2, DMAX, DMIN, DRAT1, DRAT2, DSAVE,
  147. * H1, H2, HSUM, HSUMT3, THREE, W1, W2, ZERO
  148. SAVE ZERO, THREE
  149. DOUBLE PRECISION DPCHST
  150. DATA ZERO /0.D0/, THREE/3.D0/
  151. C
  152. C VALIDITY-CHECK ARGUMENTS.
  153. C
  154. C***FIRST EXECUTABLE STATEMENT DPCHIM
  155. IF ( N.LT.2 ) GO TO 5001
  156. IF ( INCFD.LT.1 ) GO TO 5002
  157. DO 1 I = 2, N
  158. IF ( X(I).LE.X(I-1) ) GO TO 5003
  159. 1 CONTINUE
  160. C
  161. C FUNCTION DEFINITION IS OK, GO ON.
  162. C
  163. IERR = 0
  164. NLESS1 = N - 1
  165. H1 = X(2) - X(1)
  166. DEL1 = (F(1,2) - F(1,1))/H1
  167. DSAVE = DEL1
  168. C
  169. C SPECIAL CASE N=2 -- USE LINEAR INTERPOLATION.
  170. C
  171. IF (NLESS1 .GT. 1) GO TO 10
  172. D(1,1) = DEL1
  173. D(1,N) = DEL1
  174. GO TO 5000
  175. C
  176. C NORMAL CASE (N .GE. 3).
  177. C
  178. 10 CONTINUE
  179. H2 = X(3) - X(2)
  180. DEL2 = (F(1,3) - F(1,2))/H2
  181. C
  182. C SET D(1) VIA NON-CENTERED THREE-POINT FORMULA, ADJUSTED TO BE
  183. C SHAPE-PRESERVING.
  184. C
  185. HSUM = H1 + H2
  186. W1 = (H1 + HSUM)/HSUM
  187. W2 = -H1/HSUM
  188. D(1,1) = W1*DEL1 + W2*DEL2
  189. IF ( DPCHST(D(1,1),DEL1) .LE. ZERO) THEN
  190. D(1,1) = ZERO
  191. ELSE IF ( DPCHST(DEL1,DEL2) .LT. ZERO) THEN
  192. C NEED DO THIS CHECK ONLY IF MONOTONICITY SWITCHES.
  193. DMAX = THREE*DEL1
  194. IF (ABS(D(1,1)) .GT. ABS(DMAX)) D(1,1) = DMAX
  195. ENDIF
  196. C
  197. C LOOP THROUGH INTERIOR POINTS.
  198. C
  199. DO 50 I = 2, NLESS1
  200. IF (I .EQ. 2) GO TO 40
  201. C
  202. H1 = H2
  203. H2 = X(I+1) - X(I)
  204. HSUM = H1 + H2
  205. DEL1 = DEL2
  206. DEL2 = (F(1,I+1) - F(1,I))/H2
  207. 40 CONTINUE
  208. C
  209. C SET D(I)=0 UNLESS DATA ARE STRICTLY MONOTONIC.
  210. C
  211. D(1,I) = ZERO
  212. IF ( DPCHST(DEL1,DEL2) ) 42, 41, 45
  213. C
  214. C COUNT NUMBER OF CHANGES IN DIRECTION OF MONOTONICITY.
  215. C
  216. 41 CONTINUE
  217. IF (DEL2 .EQ. ZERO) GO TO 50
  218. IF ( DPCHST(DSAVE,DEL2) .LT. ZERO) IERR = IERR + 1
  219. DSAVE = DEL2
  220. GO TO 50
  221. C
  222. 42 CONTINUE
  223. IERR = IERR + 1
  224. DSAVE = DEL2
  225. GO TO 50
  226. C
  227. C USE BRODLIE MODIFICATION OF BUTLAND FORMULA.
  228. C
  229. 45 CONTINUE
  230. HSUMT3 = HSUM+HSUM+HSUM
  231. W1 = (HSUM + H1)/HSUMT3
  232. W2 = (HSUM + H2)/HSUMT3
  233. DMAX = MAX( ABS(DEL1), ABS(DEL2) )
  234. DMIN = MIN( ABS(DEL1), ABS(DEL2) )
  235. DRAT1 = DEL1/DMAX
  236. DRAT2 = DEL2/DMAX
  237. D(1,I) = DMIN/(W1*DRAT1 + W2*DRAT2)
  238. C
  239. 50 CONTINUE
  240. C
  241. C SET D(N) VIA NON-CENTERED THREE-POINT FORMULA, ADJUSTED TO BE
  242. C SHAPE-PRESERVING.
  243. C
  244. W1 = -H2/HSUM
  245. W2 = (H2 + HSUM)/HSUM
  246. D(1,N) = W1*DEL1 + W2*DEL2
  247. IF ( DPCHST(D(1,N),DEL2) .LE. ZERO) THEN
  248. D(1,N) = ZERO
  249. ELSE IF ( DPCHST(DEL1,DEL2) .LT. ZERO) THEN
  250. C NEED DO THIS CHECK ONLY IF MONOTONICITY SWITCHES.
  251. DMAX = THREE*DEL2
  252. IF (ABS(D(1,N)) .GT. ABS(DMAX)) D(1,N) = DMAX
  253. ENDIF
  254. C
  255. C NORMAL RETURN.
  256. C
  257. 5000 CONTINUE
  258. RETURN
  259. C
  260. C ERROR RETURNS.
  261. C
  262. 5001 CONTINUE
  263. C N.LT.2 RETURN.
  264. IERR = -1
  265. CALL XERMSG ('SLATEC', 'DPCHIM',
  266. + 'NUMBER OF DATA POINTS LESS THAN TWO', IERR, 1)
  267. RETURN
  268. C
  269. 5002 CONTINUE
  270. C INCFD.LT.1 RETURN.
  271. IERR = -2
  272. CALL XERMSG ('SLATEC', 'DPCHIM', 'INCREMENT LESS THAN ONE', IERR,
  273. + 1)
  274. RETURN
  275. C
  276. 5003 CONTINUE
  277. C X-ARRAY NOT STRICTLY INCREASING.
  278. IERR = -3
  279. CALL XERMSG ('SLATEC', 'DPCHIM',
  280. + 'X-ARRAY NOT STRICTLY INCREASING', IERR, 1)
  281. RETURN
  282. C------------- LAST LINE OF DPCHIM FOLLOWS -----------------------------
  283. END