pchcm.f 8.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236
  1. *DECK PCHCM
  2. SUBROUTINE PCHCM (N, X, F, D, INCFD, SKIP, ISMON, IERR)
  3. C***BEGIN PROLOGUE PCHCM
  4. C***PURPOSE Check a cubic Hermite function for monotonicity.
  5. C***LIBRARY SLATEC (PCHIP)
  6. C***CATEGORY E3
  7. C***TYPE SINGLE PRECISION (PCHCM-S, DPCHCM-D)
  8. C***KEYWORDS CUBIC HERMITE INTERPOLATION, MONOTONE INTERPOLATION,
  9. C PCHIP, PIECEWISE CUBIC INTERPOLATION, UTILITY ROUTINE
  10. C***AUTHOR Fritsch, F. N., (LLNL)
  11. C Computing & Mathematics Research Division
  12. C Lawrence Livermore National Laboratory
  13. C P.O. Box 808 (L-316)
  14. C Livermore, CA 94550
  15. C FTS 532-4275, (510) 422-4275
  16. C***DESCRIPTION
  17. C
  18. C *Usage:
  19. C
  20. C PARAMETER (INCFD = ...)
  21. C INTEGER N, ISMON(N), IERR
  22. C REAL X(N), F(INCFD,N), D(INCFD,N)
  23. C LOGICAL SKIP
  24. C
  25. C CALL PCHCM (N, X, F, D, INCFD, SKIP, ISMON, IERR)
  26. C
  27. C *Arguments:
  28. C
  29. C N:IN is the number of data points. (Error return if N.LT.2 .)
  30. C
  31. C X:IN is a real array of independent variable values. The
  32. C elements of X must be strictly increasing:
  33. C X(I-1) .LT. X(I), I = 2(1)N.
  34. C (Error return if not.)
  35. C
  36. C F:IN is a real array of function values. F(1+(I-1)*INCFD) is
  37. C the value corresponding to X(I).
  38. C
  39. C D:IN is a real array of derivative values. D(1+(I-1)*INCFD) is
  40. C the value corresponding to X(I).
  41. C
  42. C INCFD:IN is the increment between successive values in F and D.
  43. C (Error return if INCFD.LT.1 .)
  44. C
  45. C SKIP:INOUT is a logical variable which should be set to
  46. C .TRUE. if the user wishes to skip checks for validity of
  47. C preceding parameters, or to .FALSE. otherwise.
  48. C This will save time in case these checks have already
  49. C been performed.
  50. C SKIP will be set to .TRUE. on normal return.
  51. C
  52. C ISMON:OUT is an integer array indicating on which intervals the
  53. C PCH function defined by N, X, F, D is monotonic.
  54. C For data interval [X(I),X(I+1)],
  55. C ISMON(I) = -3 if function is probably decreasing;
  56. C ISMON(I) = -1 if function is strictly decreasing;
  57. C ISMON(I) = 0 if function is constant;
  58. C ISMON(I) = 1 if function is strictly increasing;
  59. C ISMON(I) = 2 if function is non-monotonic;
  60. C ISMON(I) = 3 if function is probably increasing.
  61. C If ABS(ISMON)=3, this means that the D-values are near
  62. C the boundary of the monotonicity region. A small
  63. C increase produces non-monotonicity; decrease, strict
  64. C monotonicity.
  65. C The above applies to I=1(1)N-1. ISMON(N) indicates whether
  66. C the entire function is monotonic on [X(1),X(N)].
  67. C
  68. C IERR:OUT is an error flag.
  69. C Normal return:
  70. C IERR = 0 (no errors).
  71. C "Recoverable" errors:
  72. C IERR = -1 if N.LT.2 .
  73. C IERR = -2 if INCFD.LT.1 .
  74. C IERR = -3 if the X-array is not strictly increasing.
  75. C (The ISMON-array has not been changed in any of these cases.)
  76. C NOTE: The above errors are checked in the order listed,
  77. C and following arguments have **NOT** been validated.
  78. C
  79. C *Description:
  80. C
  81. C PCHCM: Piecewise Cubic Hermite -- Check Monotonicity.
  82. C
  83. C Checks the piecewise cubic Hermite function defined by N,X,F,D
  84. C for monotonicity.
  85. C
  86. C To provide compatibility with PCHIM and PCHIC, includes an
  87. C increment between successive values of the F- and D-arrays.
  88. C
  89. C *Cautions:
  90. C This provides the same capability as old PCHMC, except that a
  91. C new output value, -3, was added February 1989. (Formerly, -3
  92. C and +3 were lumped together in the single value 3.) Codes that
  93. C flag nonmonotonicity by "IF (ISMON.EQ.2)" need not be changed.
  94. C Codes that check via "IF (ISMON.GE.3)" should change the test to
  95. C "IF (IABS(ISMON).GE.3)". Codes that declare monotonicity via
  96. C "IF (ISMON.LE.1)" should change to "IF (IABS(ISMON).LE.1)".
  97. C
  98. C***REFERENCES 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 CHFCM, XERMSG
  102. C***REVISION HISTORY (YYMMDD)
  103. C 820518 DATE WRITTEN
  104. C 820804 Converted to SLATEC library version.
  105. C 831201 Reversed order of subscripts of F and D, so that the
  106. C routine will work properly when INCFD.GT.1 . (Bug!!)
  107. C 870707 Minor cosmetic changes to prologue.
  108. C 890208 Added possible ISMON value of -3 and modified code so
  109. C that 1,3,-1 produces ISMON(N)=2, rather than 3.
  110. C 890306 Added caution about changed output.
  111. C 890407 Changed name from PCHMC to PCHCM, as requested at the
  112. C March 1989 SLATEC CML meeting, and made a few other
  113. C minor modifications necessitated by this change.
  114. C 890407 Converted to new SLATEC format.
  115. C 890407 Modified DESCRIPTION to LDOC format.
  116. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  117. C 920429 Revised format and order of references. (WRB,FNF)
  118. C***END PROLOGUE PCHCM
  119. C
  120. C Fortran intrinsics used: ISIGN.
  121. C Other routines used: CHFCM, XERMSG.
  122. C
  123. C ----------------------------------------------------------------------
  124. C
  125. C Programming notes:
  126. C
  127. C An alternate organization would have separate loops for computing
  128. C ISMON(i), i=1,...,NSEG, and for the computation of ISMON(N). The
  129. C first loop can be readily parallelized, since the NSEG calls to
  130. C CHFCM are independent. The second loop can be cut short if
  131. C ISMON(N) is ever equal to 2, for it cannot be changed further.
  132. C
  133. C To produce a double precision version, simply:
  134. C a. Change PCHCM to DPCHCM wherever it occurs,
  135. C b. Change CHFCM to DCHFCM wherever it occurs, and
  136. C c. Change the real declarations to double precision.
  137. C
  138. C DECLARE ARGUMENTS.
  139. C
  140. INTEGER N, INCFD, ISMON(N), IERR
  141. REAL X(N), F(INCFD,N), D(INCFD,N)
  142. LOGICAL SKIP
  143. C
  144. C DECLARE LOCAL VARIABLES.
  145. C
  146. INTEGER I, NSEG
  147. REAL DELTA
  148. INTEGER CHFCM
  149. C
  150. C VALIDITY-CHECK ARGUMENTS.
  151. C
  152. C***FIRST EXECUTABLE STATEMENT PCHCM
  153. IF (SKIP) GO TO 5
  154. C
  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. SKIP = .TRUE.
  161. C
  162. C FUNCTION DEFINITION IS OK -- GO ON.
  163. C
  164. 5 CONTINUE
  165. NSEG = N - 1
  166. DO 90 I = 1, NSEG
  167. DELTA = (F(1,I+1)-F(1,I))/(X(I+1)-X(I))
  168. C -------------------------------
  169. ISMON(I) = CHFCM (D(1,I), D(1,I+1), DELTA)
  170. C -------------------------------
  171. IF (I .EQ. 1) THEN
  172. ISMON(N) = ISMON(1)
  173. ELSE
  174. C Need to figure out cumulative monotonicity from following
  175. C "multiplication table":
  176. C
  177. C + I S M O N (I)
  178. C + -3 -1 0 1 3 2
  179. C +------------------------+
  180. C I -3 I -3 -3 -3 2 2 2 I
  181. C S -1 I -3 -1 -1 2 2 2 I
  182. C M 0 I -3 -1 0 1 3 2 I
  183. C O 1 I 2 2 1 1 3 2 I
  184. C N 3 I 2 2 3 3 3 2 I
  185. C (N) 2 I 2 2 2 2 2 2 I
  186. C +------------------------+
  187. C Note that the 2 row and column are out of order so as not
  188. C to obscure the symmetry in the rest of the table.
  189. C
  190. C No change needed if equal or constant on this interval or
  191. C already declared nonmonotonic.
  192. IF ( (ISMON(I).NE.ISMON(N)) .AND. (ISMON(I).NE.0)
  193. . .AND. (ISMON(N).NE.2) ) THEN
  194. IF ( (ISMON(I).EQ.2) .OR. (ISMON(N).EQ.0) ) THEN
  195. ISMON(N) = ISMON(I)
  196. ELSE IF (ISMON(I)*ISMON(N) .LT. 0) THEN
  197. C This interval has opposite sense from curve so far.
  198. ISMON(N) = 2
  199. ELSE
  200. C At this point, both are nonzero with same sign, and
  201. C we have already eliminated case both +-1.
  202. ISMON(N) = ISIGN (3, ISMON(N))
  203. ENDIF
  204. ENDIF
  205. ENDIF
  206. 90 CONTINUE
  207. C
  208. C NORMAL RETURN.
  209. C
  210. IERR = 0
  211. RETURN
  212. C
  213. C ERROR RETURNS.
  214. C
  215. 5001 CONTINUE
  216. C N.LT.2 RETURN.
  217. IERR = -1
  218. CALL XERMSG ('SLATEC', 'PCHCM',
  219. + 'NUMBER OF DATA POINTS LESS THAN TWO', IERR, 1)
  220. RETURN
  221. C
  222. 5002 CONTINUE
  223. C INCFD.LT.1 RETURN.
  224. IERR = -2
  225. CALL XERMSG ('SLATEC', 'PCHCM', 'INCREMENT LESS THAN ONE', IERR,
  226. + 1)
  227. RETURN
  228. C
  229. 5003 CONTINUE
  230. C X-ARRAY NOT STRICTLY INCREASING.
  231. IERR = -3
  232. CALL XERMSG ('SLATEC', 'PCHCM', 'X-ARRAY NOT STRICTLY INCREASING'
  233. + , IERR, 1)
  234. RETURN
  235. C------------- LAST LINE OF PCHCM FOLLOWS ------------------------------
  236. END