source: LMDZ6/branches/Amaury_dev/libf/misc/pchfe.f90 @ 5112

Last change on this file since 5112 was 5106, checked in by abarral, 2 months ago

Turn coefils.h into lmdz_coefils.f90
Put filtreg.F90 inside lmdz_filtreg.F90
Turn mod_filtreg_p.F90 into lmdz_filtreg_p.F90
Delete obsolete parafilt.h*
(lint) remove spaces between routine name and args

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