[5246] | 1 | !DECK CHFEV |
---|
| 2 | SUBROUTINE CHFEV (X1, X2, F1, F2, D1, D2, NE, XE, FE, NEXT, IERR) |
---|
| 3 | !***BEGIN PROLOGUE CHFEV |
---|
| 4 | !***PURPOSE Evaluate a cubic polynomial given in Hermite form at an |
---|
| 5 | ! array of points. While designed for use by PCHFE, it may |
---|
| 6 | ! be useful directly as an evaluator for a piecewise cubic |
---|
| 7 | ! Hermite function in applications, such as graphing, where |
---|
| 8 | ! the interval is known in advance. |
---|
| 9 | !***LIBRARY SLATEC (PCHIP) |
---|
| 10 | !***CATEGORY E3 |
---|
| 11 | !***TYPE SINGLE PRECISION (CHFEV-S, DCHFEV-D) |
---|
| 12 | !***KEYWORDS CUBIC HERMITE EVALUATION, CUBIC POLYNOMIAL EVALUATION, |
---|
| 13 | ! PCHIP |
---|
| 14 | !***AUTHOR Fritsch, F. N., (LLNL) |
---|
| 15 | ! Lawrence Livermore National Laboratory |
---|
| 16 | ! P.O. Box 808 (L-316) |
---|
| 17 | ! Livermore, CA 94550 |
---|
| 18 | ! FTS 532-4275, (510) 422-4275 |
---|
| 19 | !***DESCRIPTION |
---|
| 20 | ! |
---|
| 21 | ! CHFEV: Cubic Hermite Function EValuator |
---|
| 22 | ! |
---|
| 23 | ! Evaluates the cubic polynomial determined by function values |
---|
| 24 | ! F1,F2 and derivatives D1,D2 on interval (X1,X2) at the points |
---|
| 25 | ! XE(J), J=1(1)NE. |
---|
| 26 | ! |
---|
| 27 | ! ---------------------------------------------------------------------- |
---|
| 28 | ! |
---|
| 29 | ! Calling sequence: |
---|
| 30 | ! |
---|
| 31 | ! INTEGER NE, NEXT(2), IERR |
---|
| 32 | ! REAL X1, X2, F1, F2, D1, D2, XE(NE), FE(NE) |
---|
| 33 | ! |
---|
| 34 | ! CALL CHFEV (X1,X2, F1,F2, D1,D2, NE, XE, FE, NEXT, IERR) |
---|
| 35 | ! |
---|
| 36 | ! Parameters: |
---|
| 37 | ! |
---|
| 38 | ! X1,X2 -- (input) endpoints of interval of definition of cubic. |
---|
| 39 | ! (Error return if X1.EQ.X2 .) |
---|
| 40 | ! |
---|
| 41 | ! F1,F2 -- (input) values of function at X1 and X2, respectively. |
---|
| 42 | ! |
---|
| 43 | ! D1,D2 -- (input) values of derivative at X1 and X2, respectively. |
---|
| 44 | ! |
---|
| 45 | ! NE -- (input) number of evaluation points. (Error return if |
---|
| 46 | ! NE.LT.1 .) |
---|
| 47 | ! |
---|
| 48 | ! XE -- (input) real array of points at which the function is to be |
---|
| 49 | ! evaluated. If any of the XE are outside the interval |
---|
| 50 | ! [X1,X2], a warning error is returned in NEXT. |
---|
| 51 | ! |
---|
| 52 | ! FE -- (output) real array of values of the cubic function defined |
---|
| 53 | ! by X1,X2, F1,F2, D1,D2 at the points XE. |
---|
| 54 | ! |
---|
| 55 | ! NEXT -- (output) integer array indicating number of extrapolation |
---|
| 56 | ! points: |
---|
| 57 | ! NEXT(1) = number of evaluation points to left of interval. |
---|
| 58 | ! NEXT(2) = number of evaluation points to right of interval. |
---|
| 59 | ! |
---|
| 60 | ! IERR -- (output) error flag. |
---|
| 61 | ! Normal return: |
---|
| 62 | ! IERR = 0 (no errors). |
---|
| 63 | ! "Recoverable" errors: |
---|
| 64 | ! IERR = -1 if NE.LT.1 . |
---|
| 65 | ! IERR = -2 if X1.EQ.X2 . |
---|
| 66 | ! (The FE-array has not been changed in either case.) |
---|
| 67 | ! |
---|
| 68 | !***REFERENCES (NONE) |
---|
| 69 | !***ROUTINES CALLED XERMSG |
---|
| 70 | !***REVISION HISTORY (YYMMDD) |
---|
| 71 | ! 811019 DATE WRITTEN |
---|
| 72 | ! 820803 Minor cosmetic changes for release 1. |
---|
| 73 | ! 890411 Added SAVE statements (Vers. 3.2). |
---|
| 74 | ! 890531 Changed all specific intrinsics to generic. (WRB) |
---|
| 75 | ! 890703 Corrected category record. (WRB) |
---|
| 76 | ! 890703 REVISION DATE from Version 3.2 |
---|
| 77 | ! 891214 Prologue converted to Version 4.0 format. (BAB) |
---|
| 78 | ! 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ) |
---|
| 79 | !***END PROLOGUE CHFEV |
---|
| 80 | ! Programming notes: |
---|
| 81 | ! |
---|
| 82 | ! To produce a double precision version, simply: |
---|
| 83 | ! a. Change CHFEV to DCHFEV wherever it occurs, |
---|
| 84 | ! b. Change the real declaration to double precision, and |
---|
| 85 | ! c. Change the constant ZERO to double precision. |
---|
| 86 | ! |
---|
| 87 | ! DECLARE ARGUMENTS. |
---|
| 88 | ! |
---|
| 89 | INTEGER :: NE, NEXT(2), IERR |
---|
| 90 | REAL :: X1, X2, F1, F2, D1, D2, XE(*), FE(*) |
---|
| 91 | ! |
---|
| 92 | ! DECLARE LOCAL VARIABLES. |
---|
| 93 | ! |
---|
| 94 | INTEGER :: I |
---|
| 95 | REAL :: C2, C3, DEL1, DEL2, DELTA, H, X, XMI, XMA, ZERO |
---|
| 96 | SAVE ZERO |
---|
| 97 | DATA ZERO /0./ |
---|
| 98 | ! |
---|
| 99 | ! VALIDITY-CHECK ARGUMENTS. |
---|
| 100 | ! |
---|
| 101 | !***FIRST EXECUTABLE STATEMENT CHFEV |
---|
| 102 | IF (NE .LT. 1) GO TO 5001 |
---|
| 103 | H = X2 - X1 |
---|
| 104 | IF (H .EQ. ZERO) GO TO 5002 |
---|
| 105 | ! |
---|
| 106 | ! INITIALIZE. |
---|
| 107 | ! |
---|
| 108 | IERR = 0 |
---|
| 109 | NEXT(1) = 0 |
---|
| 110 | NEXT(2) = 0 |
---|
| 111 | XMI = MIN(ZERO, H) |
---|
| 112 | XMA = MAX(ZERO, H) |
---|
| 113 | ! |
---|
| 114 | ! COMPUTE CUBIC COEFFICIENTS (EXPANDED ABOUT X1). |
---|
| 115 | ! |
---|
| 116 | DELTA = (F2 - F1)/H |
---|
| 117 | DEL1 = (D1 - DELTA)/H |
---|
| 118 | DEL2 = (D2 - DELTA)/H |
---|
| 119 | ! (DELTA IS NO LONGER NEEDED.) |
---|
| 120 | C2 = -(DEL1+DEL1 + DEL2) |
---|
| 121 | C3 = (DEL1 + DEL2)/H |
---|
| 122 | ! (H, DEL1 AND DEL2 ARE NO LONGER NEEDED.) |
---|
| 123 | ! |
---|
| 124 | ! EVALUATION LOOP. |
---|
| 125 | ! |
---|
| 126 | DO I = 1, NE |
---|
| 127 | X = XE(I) - X1 |
---|
| 128 | FE(I) = F1 + X*(D1 + X*(C2 + X*C3)) |
---|
| 129 | ! COUNT EXTRAPOLATION POINTS. |
---|
| 130 | IF ( X.LT.XMI ) NEXT(1) = NEXT(1) + 1 |
---|
| 131 | IF ( X.GT.XMA ) NEXT(2) = NEXT(2) + 1 |
---|
| 132 | ! (NOTE REDUNDANCY--IF EITHER CONDITION IS TRUE, OTHER IS FALSE.) |
---|
| 133 | END DO |
---|
| 134 | ! |
---|
| 135 | ! NORMAL RETURN. |
---|
| 136 | ! |
---|
| 137 | RETURN |
---|
| 138 | ! |
---|
| 139 | ! ERROR RETURNS. |
---|
| 140 | ! |
---|
| 141 | 5001 CONTINUE |
---|
| 142 | ! NE.LT.1 RETURN. |
---|
| 143 | IERR = -1 |
---|
| 144 | CALL XERMSG ('SLATEC', 'CHFEV', & |
---|
| 145 | 'NUMBER OF EVALUATION POINTS LESS THAN ONE', IERR, 1) |
---|
| 146 | RETURN |
---|
| 147 | ! |
---|
| 148 | 5002 CONTINUE |
---|
| 149 | ! X1.EQ.X2 RETURN. |
---|
| 150 | IERR = -2 |
---|
| 151 | CALL XERMSG ('SLATEC', 'CHFEV', 'INTERVAL ENDPOINTS EQUAL', IERR, & |
---|
| 152 | 1) |
---|
| 153 | RETURN |
---|
| 154 | !------------- LAST LINE OF CHFEV FOLLOWS ------------------------------ |
---|
| 155 | END SUBROUTINE CHFEV |
---|