pchce.f 8.3 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246
  1. *DECK PCHCE
  2. SUBROUTINE PCHCE (IC, VC, N, X, H, SLOPE, D, INCFD, IERR)
  3. C***BEGIN PROLOGUE PCHCE
  4. C***SUBSIDIARY
  5. C***PURPOSE Set boundary conditions for PCHIC
  6. C***LIBRARY SLATEC (PCHIP)
  7. C***TYPE SINGLE PRECISION (PCHCE-S, DPCHCE-D)
  8. C***AUTHOR Fritsch, F. N., (LLNL)
  9. C***DESCRIPTION
  10. C
  11. C PCHCE: PCHIC End Derivative Setter.
  12. C
  13. C Called by PCHIC to set end derivatives as requested by the user.
  14. C It must be called after interior derivative values have been set.
  15. C -----
  16. C
  17. C To facilitate two-dimensional applications, includes an increment
  18. C between successive values of the D-array.
  19. C
  20. C ----------------------------------------------------------------------
  21. C
  22. C Calling sequence:
  23. C
  24. C PARAMETER (INCFD = ...)
  25. C INTEGER IC(2), N, IERR
  26. C REAL VC(2), X(N), H(N), SLOPE(N), D(INCFD,N)
  27. C
  28. C CALL PCHCE (IC, VC, N, X, H, SLOPE, D, INCFD, IERR)
  29. C
  30. C Parameters:
  31. C
  32. C IC -- (input) integer array of length 2 specifying desired
  33. C boundary conditions:
  34. C IC(1) = IBEG, desired condition at beginning of data.
  35. C IC(2) = IEND, desired condition at end of data.
  36. C ( see prologue to PCHIC for details. )
  37. C
  38. C VC -- (input) real array of length 2 specifying desired boundary
  39. C values. VC(1) need be set only if IC(1) = 2 or 3 .
  40. C VC(2) need be set only if IC(2) = 2 or 3 .
  41. C
  42. C N -- (input) number of data points. (assumes N.GE.2)
  43. C
  44. C X -- (input) real array of independent variable values. (the
  45. C elements of X are assumed to be strictly increasing.)
  46. C
  47. C H -- (input) real array of interval lengths.
  48. C SLOPE -- (input) real array of data slopes.
  49. C If the data are (X(I),Y(I)), I=1(1)N, then these inputs are:
  50. C H(I) = X(I+1)-X(I),
  51. C SLOPE(I) = (Y(I+1)-Y(I))/H(I), I=1(1)N-1.
  52. C
  53. C D -- (input) real array of derivative values at the data points.
  54. C The value corresponding to X(I) must be stored in
  55. C D(1+(I-1)*INCFD), I=1(1)N.
  56. C (output) the value of D at X(1) and/or X(N) is changed, if
  57. C necessary, to produce the requested boundary conditions.
  58. C no other entries in D are changed.
  59. C
  60. C INCFD -- (input) increment between successive values in D.
  61. C This argument is provided primarily for 2-D applications.
  62. C
  63. C IERR -- (output) error flag.
  64. C Normal return:
  65. C IERR = 0 (no errors).
  66. C Warning errors:
  67. C IERR = 1 if IBEG.LT.0 and D(1) had to be adjusted for
  68. C monotonicity.
  69. C IERR = 2 if IEND.LT.0 and D(1+(N-1)*INCFD) had to be
  70. C adjusted for monotonicity.
  71. C IERR = 3 if both of the above are true.
  72. C
  73. C -------
  74. C WARNING: This routine does no validity-checking of arguments.
  75. C -------
  76. C
  77. C Fortran intrinsics used: ABS.
  78. C
  79. C***SEE ALSO PCHIC
  80. C***ROUTINES CALLED PCHDF, PCHST, XERMSG
  81. C***REVISION HISTORY (YYMMDD)
  82. C 820218 DATE WRITTEN
  83. C 820805 Converted to SLATEC library version.
  84. C 870707 Minor corrections made to prologue..
  85. C 890411 Added SAVE statements (Vers. 3.2).
  86. C 890531 Changed all specific intrinsics to generic. (WRB)
  87. C 890831 Modified array declarations. (WRB)
  88. C 890831 REVISION DATE from Version 3.2
  89. C 891214 Prologue converted to Version 4.0 format. (BAB)
  90. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  91. C 900328 Added TYPE section. (WRB)
  92. C 910408 Updated AUTHOR section in prologue. (WRB)
  93. C 930503 Improved purpose. (FNF)
  94. C***END PROLOGUE PCHCE
  95. C
  96. C Programming notes:
  97. C 1. The function PCHST(ARG1,ARG2) is assumed to return zero if
  98. C either argument is zero, +1 if they are of the same sign, and
  99. C -1 if they are of opposite sign.
  100. C 2. One could reduce the number of arguments and amount of local
  101. C storage, at the expense of reduced code clarity, by passing in
  102. C the array WK (rather than splitting it into H and SLOPE) and
  103. C increasing its length enough to incorporate STEMP and XTEMP.
  104. C 3. The two monotonicity checks only use the sufficient conditions.
  105. C Thus, it is possible (but unlikely) for a boundary condition to
  106. C be changed, even though the original interpolant was monotonic.
  107. C (At least the result is a continuous function of the data.)
  108. C**End
  109. C
  110. C DECLARE ARGUMENTS.
  111. C
  112. INTEGER IC(2), N, INCFD, IERR
  113. REAL VC(2), X(*), H(*), SLOPE(*), D(INCFD,*)
  114. C
  115. C DECLARE LOCAL VARIABLES.
  116. C
  117. INTEGER IBEG, IEND, IERF, INDEX, J, K
  118. REAL HALF, STEMP(3), THREE, TWO, XTEMP(4), ZERO
  119. SAVE ZERO, HALF, TWO, THREE
  120. REAL PCHDF, PCHST
  121. C
  122. C INITIALIZE.
  123. C
  124. DATA ZERO /0./, HALF /0.5/, TWO /2./, THREE /3./
  125. C
  126. C***FIRST EXECUTABLE STATEMENT PCHCE
  127. IBEG = IC(1)
  128. IEND = IC(2)
  129. IERR = 0
  130. C
  131. C SET TO DEFAULT BOUNDARY CONDITIONS IF N IS TOO SMALL.
  132. C
  133. IF ( ABS(IBEG).GT.N ) IBEG = 0
  134. IF ( ABS(IEND).GT.N ) IEND = 0
  135. C
  136. C TREAT BEGINNING BOUNDARY CONDITION.
  137. C
  138. IF (IBEG .EQ. 0) GO TO 2000
  139. K = ABS(IBEG)
  140. IF (K .EQ. 1) THEN
  141. C BOUNDARY VALUE PROVIDED.
  142. D(1,1) = VC(1)
  143. ELSE IF (K .EQ. 2) THEN
  144. C BOUNDARY SECOND DERIVATIVE PROVIDED.
  145. D(1,1) = HALF*( (THREE*SLOPE(1) - D(1,2)) - HALF*VC(1)*H(1) )
  146. ELSE IF (K .LT. 5) THEN
  147. C USE K-POINT DERIVATIVE FORMULA.
  148. C PICK UP FIRST K POINTS, IN REVERSE ORDER.
  149. DO 10 J = 1, K
  150. INDEX = K-J+1
  151. C INDEX RUNS FROM K DOWN TO 1.
  152. XTEMP(J) = X(INDEX)
  153. IF (J .LT. K) STEMP(J) = SLOPE(INDEX-1)
  154. 10 CONTINUE
  155. C -----------------------------
  156. D(1,1) = PCHDF (K, XTEMP, STEMP, IERF)
  157. C -----------------------------
  158. IF (IERF .NE. 0) GO TO 5001
  159. ELSE
  160. C USE 'NOT A KNOT' CONDITION.
  161. D(1,1) = ( THREE*(H(1)*SLOPE(2) + H(2)*SLOPE(1))
  162. * - TWO*(H(1)+H(2))*D(1,2) - H(1)*D(1,3) ) / H(2)
  163. ENDIF
  164. C
  165. IF (IBEG .GT. 0) GO TO 2000
  166. C
  167. C CHECK D(1,1) FOR COMPATIBILITY WITH MONOTONICITY.
  168. C
  169. IF (SLOPE(1) .EQ. ZERO) THEN
  170. IF (D(1,1) .NE. ZERO) THEN
  171. D(1,1) = ZERO
  172. IERR = IERR + 1
  173. ENDIF
  174. ELSE IF ( PCHST(D(1,1),SLOPE(1)) .LT. ZERO) THEN
  175. D(1,1) = ZERO
  176. IERR = IERR + 1
  177. ELSE IF ( ABS(D(1,1)) .GT. THREE*ABS(SLOPE(1)) ) THEN
  178. D(1,1) = THREE*SLOPE(1)
  179. IERR = IERR + 1
  180. ENDIF
  181. C
  182. C TREAT END BOUNDARY CONDITION.
  183. C
  184. 2000 CONTINUE
  185. IF (IEND .EQ. 0) GO TO 5000
  186. K = ABS(IEND)
  187. IF (K .EQ. 1) THEN
  188. C BOUNDARY VALUE PROVIDED.
  189. D(1,N) = VC(2)
  190. ELSE IF (K .EQ. 2) THEN
  191. C BOUNDARY SECOND DERIVATIVE PROVIDED.
  192. D(1,N) = HALF*( (THREE*SLOPE(N-1) - D(1,N-1)) +
  193. * HALF*VC(2)*H(N-1) )
  194. ELSE IF (K .LT. 5) THEN
  195. C USE K-POINT DERIVATIVE FORMULA.
  196. C PICK UP LAST K POINTS.
  197. DO 2010 J = 1, K
  198. INDEX = N-K+J
  199. C INDEX RUNS FROM N+1-K UP TO N.
  200. XTEMP(J) = X(INDEX)
  201. IF (J .LT. K) STEMP(J) = SLOPE(INDEX)
  202. 2010 CONTINUE
  203. C -----------------------------
  204. D(1,N) = PCHDF (K, XTEMP, STEMP, IERF)
  205. C -----------------------------
  206. IF (IERF .NE. 0) GO TO 5001
  207. ELSE
  208. C USE 'NOT A KNOT' CONDITION.
  209. D(1,N) = ( THREE*(H(N-1)*SLOPE(N-2) + H(N-2)*SLOPE(N-1))
  210. * - TWO*(H(N-1)+H(N-2))*D(1,N-1) - H(N-1)*D(1,N-2) )
  211. * / H(N-2)
  212. ENDIF
  213. C
  214. IF (IEND .GT. 0) GO TO 5000
  215. C
  216. C CHECK D(1,N) FOR COMPATIBILITY WITH MONOTONICITY.
  217. C
  218. IF (SLOPE(N-1) .EQ. ZERO) THEN
  219. IF (D(1,N) .NE. ZERO) THEN
  220. D(1,N) = ZERO
  221. IERR = IERR + 2
  222. ENDIF
  223. ELSE IF ( PCHST(D(1,N),SLOPE(N-1)) .LT. ZERO) THEN
  224. D(1,N) = ZERO
  225. IERR = IERR + 2
  226. ELSE IF ( ABS(D(1,N)) .GT. THREE*ABS(SLOPE(N-1)) ) THEN
  227. D(1,N) = THREE*SLOPE(N-1)
  228. IERR = IERR + 2
  229. ENDIF
  230. C
  231. C NORMAL RETURN.
  232. C
  233. 5000 CONTINUE
  234. RETURN
  235. C
  236. C ERROR RETURN.
  237. C
  238. 5001 CONTINUE
  239. C ERROR RETURN FROM PCHDF.
  240. C *** THIS CASE SHOULD NEVER OCCUR ***
  241. IERR = -1
  242. CALL XERMSG ('SLATEC', 'PCHCE', 'ERROR RETURN FROM PCHDF', IERR,
  243. + 1)
  244. RETURN
  245. C------------- LAST LINE OF PCHCE FOLLOWS ------------------------------
  246. END