source: LMDZ6/branches/Amaury_dev/libf/misc/pchdf.f90 @ 5105

Last change on this file since 5105 was 5105, checked in by abarral, 8 weeks ago

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

  • 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: 3.1 KB
Line 
1!DECK PCHDF
2REAL FUNCTION PCHDF (K, X, S, IERR)
3  !***BEGIN PROLOGUE  PCHDF
4  !***SUBSIDIARY
5  !***PURPOSE  Computes divided differences for PCHCE and PCHSP
6  !***LIBRARY   SLATEC (PCHIP)
7  !***TYPE      SINGLE PRECISION (PCHDF-S, DPCHDF-D)
8  !***AUTHOR  Fritsch, F. N., (LLNL)
9  !***DESCRIPTION
10  !
11  !      PCHDF:   PCHIP Finite Difference Formula
12  !
13  ! Uses a divided difference formulation to compute a K-point approx-
14  ! imation to the derivative at X(K) based on the data in X and S.
15  !
16  ! Called by  PCHCE  and  PCHSP  to compute 3- and 4-point boundary
17  ! derivative approximations.
18  !
19  ! ----------------------------------------------------------------------
20  !
21  ! On input:
22  !    K      is the order of the desired derivative approximation.
23  !           K must be at least 3 (error return if not).
24  !    X      contains the K values of the independent variable.
25  !           X need not be ordered, but the values **MUST** be
26  !           distinct.  (Not checked here.)
27  !    S      contains the associated slope values:
28  !              S(I) = (F(I+1)-F(I))/(X(I+1)-X(I)), I=1(1)K-1.
29  !           (Note that S need only be of length K-1.)
30  !
31  ! On return:
32  !    S      will be destroyed.
33  !    IERR   will be set to -1 if K.LT.2 .
34  !    PCHDF  will be set to the desired derivative approximation if
35  !           IERR=0 or to zero if IERR=-1.
36  !
37  ! ----------------------------------------------------------------------
38  !
39  !***SEE ALSO  PCHCE, PCHSP
40  !***REFERENCES  Carl de Boor, A Practical Guide to Splines, Springer-
41  !             Verlag, New York, 1978, pp. 10-16.
42  !***ROUTINES CALLED  XERMSG
43  !***REVISION HISTORY  (YYMMDD)
44  !   820503  DATE WRITTEN
45  !   820805  Converted to SLATEC library version.
46  !   870813  Minor cosmetic changes.
47  !   890411  Added SAVE statements (Vers. 3.2).
48  !   890411  REVISION DATE from Version 3.2
49  !   891214  Prologue converted to Version 4.0 format.  (BAB)
50  !   900315  CALLs to XERROR changed to CALLs to XERMSG.  (THJ)
51  !   900328  Added TYPE section.  (WRB)
52  !   910408  Updated AUTHOR and DATE WRITTEN sections in prologue.  (WRB)
53  !   920429  Revised format and order of references.  (WRB,FNF)
54  !   930503  Improved purpose.  (FNF)
55  !***END PROLOGUE  PCHDF
56  !
57  !**End
58  !
59  !  DECLARE ARGUMENTS.
60  !
61  INTEGER :: K, IERR
62  REAL :: X(K), S(K)
63  !
64  !  DECLARE LOCAL VARIABLES.
65  !
66  INTEGER :: I, J
67  REAL :: VALUE, ZERO
68  SAVE ZERO
69  DATA  ZERO /0./
70  !
71  !  CHECK FOR LEGAL VALUE OF K.
72  !
73  !***FIRST EXECUTABLE STATEMENT  PCHDF
74  IF (K < 3)  GO TO 5001
75  !
76  !  COMPUTE COEFFICIENTS OF INTERPOLATING POLYNOMIAL.
77  !
78  DO J = 2, K-1
79     DO I = 1, K-J
80        S(I) = (S(I+1)-S(I))/(X(I+J)-X(I))
81  END DO
82  END DO
83  !
84  !  EVALUATE DERIVATIVE AT X(K).
85  !
86  VALUE = S(1)
87  DO I = 2, K-1
88     VALUE = S(I) + VALUE*(X(K)-X(I))
89  END DO
90  !
91  !  NORMAL RETURN.
92  !
93  IERR = 0
94  PCHDF = VALUE
95  RETURN
96  !
97  !  ERROR RETURN.
98  !
99 5001   CONTINUE
100  ! K.LT.3 RETURN.
101  IERR = -1
102  CALL XERMSG ('SLATEC', 'PCHDF', 'K LESS THAN THREE', IERR, 1)
103  PCHDF = ZERO
104  RETURN
105  !------------- LAST LINE OF PCHDF FOLLOWS ------------------------------
106END FUNCTION PCHDF
Note: See TracBrowser for help on using the repository browser.