dpchfd.f 11 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324
  1. *DECK DPCHFD
  2. SUBROUTINE DPCHFD (N, X, F, D, INCFD, SKIP, NE, XE, FE, DE, IERR)
  3. C***BEGIN PROLOGUE DPCHFD
  4. C***PURPOSE Evaluate a piecewise cubic Hermite function and its first
  5. C derivative at an array of points. May be used by itself
  6. C for Hermite interpolation, or as an evaluator for DPCHIM
  7. C or DPCHIC. If only function values are required, use
  8. C DPCHFE instead.
  9. C***LIBRARY SLATEC (PCHIP)
  10. C***CATEGORY E3, H1
  11. C***TYPE DOUBLE PRECISION (PCHFD-S, DPCHFD-D)
  12. C***KEYWORDS CUBIC HERMITE DIFFERENTIATION, CUBIC HERMITE EVALUATION,
  13. C HERMITE INTERPOLATION, PCHIP, PIECEWISE CUBIC EVALUATION
  14. C***AUTHOR Fritsch, F. N., (LLNL)
  15. C Lawrence Livermore National Laboratory
  16. C P.O. Box 808 (L-316)
  17. C Livermore, CA 94550
  18. C FTS 532-4275, (510) 422-4275
  19. C***DESCRIPTION
  20. C
  21. C DPCHFD: Piecewise Cubic Hermite Function and Derivative
  22. C evaluator
  23. C
  24. C Evaluates the cubic Hermite function defined by N, X, F, D, to-
  25. C gether with its first derivative, at the points XE(J), J=1(1)NE.
  26. C
  27. C If only function values are required, use DPCHFE, instead.
  28. C
  29. C To provide compatibility with DPCHIM and DPCHIC, includes an
  30. C increment between successive values of the F- and D-arrays.
  31. C
  32. C ----------------------------------------------------------------------
  33. C
  34. C Calling sequence:
  35. C
  36. C PARAMETER (INCFD = ...)
  37. C INTEGER N, NE, IERR
  38. C DOUBLE PRECISION X(N), F(INCFD,N), D(INCFD,N), XE(NE), FE(NE),
  39. C DE(NE)
  40. C LOGICAL SKIP
  41. C
  42. C CALL DPCHFD (N, X, F, D, INCFD, SKIP, NE, XE, FE, DE, IERR)
  43. C
  44. C Parameters:
  45. C
  46. C N -- (input) number of data points. (Error return if N.LT.2 .)
  47. C
  48. C X -- (input) real*8 array of independent variable values. The
  49. C elements of X must be strictly increasing:
  50. C X(I-1) .LT. X(I), I = 2(1)N.
  51. C (Error return if not.)
  52. C
  53. C F -- (input) real*8 array of function values. F(1+(I-1)*INCFD) is
  54. C the value corresponding to X(I).
  55. C
  56. C D -- (input) real*8 array of derivative values. D(1+(I-1)*INCFD)
  57. C is the value corresponding to X(I).
  58. C
  59. C INCFD -- (input) increment between successive values in F and D.
  60. C (Error return if INCFD.LT.1 .)
  61. C
  62. C SKIP -- (input/output) logical variable which should be set to
  63. C .TRUE. if the user wishes to skip checks for validity of
  64. C preceding parameters, or to .FALSE. otherwise.
  65. C This will save time in case these checks have already
  66. C been performed (say, in DPCHIM or DPCHIC).
  67. C SKIP will be set to .TRUE. on normal return.
  68. C
  69. C NE -- (input) number of evaluation points. (Error return if
  70. C NE.LT.1 .)
  71. C
  72. C XE -- (input) real*8 array of points at which the functions are to
  73. C be evaluated.
  74. C
  75. C
  76. C NOTES:
  77. C 1. The evaluation will be most efficient if the elements
  78. C of XE are increasing relative to X;
  79. C that is, XE(J) .GE. X(I)
  80. C implies XE(K) .GE. X(I), all K.GE.J .
  81. C 2. If any of the XE are outside the interval [X(1),X(N)],
  82. C values are extrapolated from the nearest extreme cubic,
  83. C and a warning error is returned.
  84. C
  85. C FE -- (output) real*8 array of values of the cubic Hermite
  86. C function defined by N, X, F, D at the points XE.
  87. C
  88. C DE -- (output) real*8 array of values of the first derivative of
  89. C the same function at the points XE.
  90. C
  91. C IERR -- (output) error flag.
  92. C Normal return:
  93. C IERR = 0 (no errors).
  94. C Warning error:
  95. C IERR.GT.0 means that extrapolation was performed at
  96. C IERR points.
  97. C "Recoverable" errors:
  98. C IERR = -1 if N.LT.2 .
  99. C IERR = -2 if INCFD.LT.1 .
  100. C IERR = -3 if the X-array is not strictly increasing.
  101. C IERR = -4 if NE.LT.1 .
  102. C (Output arrays have not been changed in any of these cases.)
  103. C NOTE: The above errors are checked in the order listed,
  104. C and following arguments have **NOT** been validated.
  105. C IERR = -5 if an error has occurred in the lower-level
  106. C routine DCHFDV. NB: this should never happen.
  107. C Notify the author **IMMEDIATELY** if it does.
  108. C
  109. C***REFERENCES (NONE)
  110. C***ROUTINES CALLED DCHFDV, XERMSG
  111. C***REVISION HISTORY (YYMMDD)
  112. C 811020 DATE WRITTEN
  113. C 820803 Minor cosmetic changes for release 1.
  114. C 870707 Corrected XERROR calls for d.p. name(s).
  115. C 890206 Corrected XERROR calls.
  116. C 890531 Changed all specific intrinsics to generic. (WRB)
  117. C 890831 Modified array declarations. (WRB)
  118. C 891006 Cosmetic changes to prologue. (WRB)
  119. C 891006 REVISION DATE from Version 3.2
  120. C 891214 Prologue converted to Version 4.0 format. (BAB)
  121. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  122. C***END PROLOGUE DPCHFD
  123. C Programming notes:
  124. C
  125. C 1. To produce a single precision version, simply:
  126. C a. Change DPCHFD to PCHFD, and DCHFDV to CHFDV, wherever they
  127. C occur,
  128. C b. Change the double precision declaration to real,
  129. C
  130. C 2. Most of the coding between the call to DCHFDV and the end of
  131. C the IR-loop could be eliminated if it were permissible to
  132. C assume that XE is ordered relative to X.
  133. C
  134. C 3. DCHFDV does not assume that X1 is less than X2. thus, it would
  135. C be possible to write a version of DPCHFD that assumes a strict-
  136. C ly decreasing X-array by simply running the IR-loop backwards
  137. C (and reversing the order of appropriate tests).
  138. C
  139. C 4. The present code has a minor bug, which I have decided is not
  140. C worth the effort that would be required to fix it.
  141. C If XE contains points in [X(N-1),X(N)], followed by points .LT.
  142. C X(N-1), followed by points .GT.X(N), the extrapolation points
  143. C will be counted (at least) twice in the total returned in IERR.
  144. C
  145. C DECLARE ARGUMENTS.
  146. C
  147. INTEGER N, INCFD, NE, IERR
  148. DOUBLE PRECISION X(*), F(INCFD,*), D(INCFD,*), XE(*), FE(*),
  149. * DE(*)
  150. LOGICAL SKIP
  151. C
  152. C DECLARE LOCAL VARIABLES.
  153. C
  154. INTEGER I, IERC, IR, J, JFIRST, NEXT(2), NJ
  155. C
  156. C VALIDITY-CHECK ARGUMENTS.
  157. C
  158. C***FIRST EXECUTABLE STATEMENT DPCHFD
  159. IF (SKIP) GO TO 5
  160. C
  161. IF ( N.LT.2 ) GO TO 5001
  162. IF ( INCFD.LT.1 ) GO TO 5002
  163. DO 1 I = 2, N
  164. IF ( X(I).LE.X(I-1) ) GO TO 5003
  165. 1 CONTINUE
  166. C
  167. C FUNCTION DEFINITION IS OK, GO ON.
  168. C
  169. 5 CONTINUE
  170. IF ( NE.LT.1 ) GO TO 5004
  171. IERR = 0
  172. SKIP = .TRUE.
  173. C
  174. C LOOP OVER INTERVALS. ( INTERVAL INDEX IS IL = IR-1 . )
  175. C ( INTERVAL IS X(IL).LE.X.LT.X(IR) . )
  176. JFIRST = 1
  177. IR = 2
  178. 10 CONTINUE
  179. C
  180. C SKIP OUT OF LOOP IF HAVE PROCESSED ALL EVALUATION POINTS.
  181. C
  182. IF (JFIRST .GT. NE) GO TO 5000
  183. C
  184. C LOCATE ALL POINTS IN INTERVAL.
  185. C
  186. DO 20 J = JFIRST, NE
  187. IF (XE(J) .GE. X(IR)) GO TO 30
  188. 20 CONTINUE
  189. J = NE + 1
  190. GO TO 40
  191. C
  192. C HAVE LOCATED FIRST POINT BEYOND INTERVAL.
  193. C
  194. 30 CONTINUE
  195. IF (IR .EQ. N) J = NE + 1
  196. C
  197. 40 CONTINUE
  198. NJ = J - JFIRST
  199. C
  200. C SKIP EVALUATION IF NO POINTS IN INTERVAL.
  201. C
  202. IF (NJ .EQ. 0) GO TO 50
  203. C
  204. C EVALUATE CUBIC AT XE(I), I = JFIRST (1) J-1 .
  205. C
  206. C ----------------------------------------------------------------
  207. CALL DCHFDV (X(IR-1),X(IR), F(1,IR-1),F(1,IR), D(1,IR-1),D(1,IR)
  208. * ,NJ, XE(JFIRST), FE(JFIRST), DE(JFIRST), NEXT, IERC)
  209. C ----------------------------------------------------------------
  210. IF (IERC .LT. 0) GO TO 5005
  211. C
  212. IF (NEXT(2) .EQ. 0) GO TO 42
  213. C IF (NEXT(2) .GT. 0) THEN
  214. C IN THE CURRENT SET OF XE-POINTS, THERE ARE NEXT(2) TO THE
  215. C RIGHT OF X(IR).
  216. C
  217. IF (IR .LT. N) GO TO 41
  218. C IF (IR .EQ. N) THEN
  219. C THESE ARE ACTUALLY EXTRAPOLATION POINTS.
  220. IERR = IERR + NEXT(2)
  221. GO TO 42
  222. 41 CONTINUE
  223. C ELSE
  224. C WE SHOULD NEVER HAVE GOTTEN HERE.
  225. GO TO 5005
  226. C ENDIF
  227. C ENDIF
  228. 42 CONTINUE
  229. C
  230. IF (NEXT(1) .EQ. 0) GO TO 49
  231. C IF (NEXT(1) .GT. 0) THEN
  232. C IN THE CURRENT SET OF XE-POINTS, THERE ARE NEXT(1) TO THE
  233. C LEFT OF X(IR-1).
  234. C
  235. IF (IR .GT. 2) GO TO 43
  236. C IF (IR .EQ. 2) THEN
  237. C THESE ARE ACTUALLY EXTRAPOLATION POINTS.
  238. IERR = IERR + NEXT(1)
  239. GO TO 49
  240. 43 CONTINUE
  241. C ELSE
  242. C XE IS NOT ORDERED RELATIVE TO X, SO MUST ADJUST
  243. C EVALUATION INTERVAL.
  244. C
  245. C FIRST, LOCATE FIRST POINT TO LEFT OF X(IR-1).
  246. DO 44 I = JFIRST, J-1
  247. IF (XE(I) .LT. X(IR-1)) GO TO 45
  248. 44 CONTINUE
  249. C NOTE-- CANNOT DROP THROUGH HERE UNLESS THERE IS AN ERROR
  250. C IN DCHFDV.
  251. GO TO 5005
  252. C
  253. 45 CONTINUE
  254. C RESET J. (THIS WILL BE THE NEW JFIRST.)
  255. J = I
  256. C
  257. C NOW FIND OUT HOW FAR TO BACK UP IN THE X-ARRAY.
  258. DO 46 I = 1, IR-1
  259. IF (XE(J) .LT. X(I)) GO TO 47
  260. 46 CONTINUE
  261. C NB-- CAN NEVER DROP THROUGH HERE, SINCE XE(J).LT.X(IR-1).
  262. C
  263. 47 CONTINUE
  264. C AT THIS POINT, EITHER XE(J) .LT. X(1)
  265. C OR X(I-1) .LE. XE(J) .LT. X(I) .
  266. C RESET IR, RECOGNIZING THAT IT WILL BE INCREMENTED BEFORE
  267. C CYCLING.
  268. IR = MAX(1, I-1)
  269. C ENDIF
  270. C ENDIF
  271. 49 CONTINUE
  272. C
  273. JFIRST = J
  274. C
  275. C END OF IR-LOOP.
  276. C
  277. 50 CONTINUE
  278. IR = IR + 1
  279. IF (IR .LE. N) GO TO 10
  280. C
  281. C NORMAL RETURN.
  282. C
  283. 5000 CONTINUE
  284. RETURN
  285. C
  286. C ERROR RETURNS.
  287. C
  288. 5001 CONTINUE
  289. C N.LT.2 RETURN.
  290. IERR = -1
  291. CALL XERMSG ('SLATEC', 'DPCHFD',
  292. + 'NUMBER OF DATA POINTS LESS THAN TWO', IERR, 1)
  293. RETURN
  294. C
  295. 5002 CONTINUE
  296. C INCFD.LT.1 RETURN.
  297. IERR = -2
  298. CALL XERMSG ('SLATEC', 'DPCHFD', 'INCREMENT LESS THAN ONE', IERR,
  299. + 1)
  300. RETURN
  301. C
  302. 5003 CONTINUE
  303. C X-ARRAY NOT STRICTLY INCREASING.
  304. IERR = -3
  305. CALL XERMSG ('SLATEC', 'DPCHFD',
  306. + 'X-ARRAY NOT STRICTLY INCREASING', IERR, 1)
  307. RETURN
  308. C
  309. 5004 CONTINUE
  310. C NE.LT.1 RETURN.
  311. IERR = -4
  312. CALL XERMSG ('SLATEC', 'DPCHFD',
  313. + 'NUMBER OF EVALUATION POINTS LESS THAN ONE', IERR, 1)
  314. RETURN
  315. C
  316. 5005 CONTINUE
  317. C ERROR RETURN FROM DCHFDV.
  318. C *** THIS CASE SHOULD NEVER OCCUR ***
  319. IERR = -5
  320. CALL XERMSG ('SLATEC', 'DPCHFD',
  321. + 'ERROR RETURN FROM DCHFDV -- FATAL', IERR, 2)
  322. RETURN
  323. C------------- LAST LINE OF DPCHFD FOLLOWS -----------------------------
  324. END