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