1 | ! $Id$ |
---|
2 | module lmdz_interpolation |
---|
3 | |
---|
4 | ! From Press et al., 1996, version 2.10a |
---|
5 | ! B3 Interpolation and Extrapolation |
---|
6 | |
---|
7 | IMPLICIT NONE; PRIVATE |
---|
8 | PUBLIC locate, hunt |
---|
9 | |
---|
10 | CONTAINS |
---|
11 | |
---|
12 | pure FUNCTION locate(xx, x) |
---|
13 | |
---|
14 | REAL, DIMENSION(:), INTENT(IN) :: xx |
---|
15 | REAL, INTENT(IN) :: x |
---|
16 | INTEGER locate |
---|
17 | |
---|
18 | ! Given an array xx(1:N), and given a value x, returns a value j, |
---|
19 | ! between 0 and N, such that x is between xx(j) and xx(j + 1). xx |
---|
20 | ! must be monotonic, either increasing or decreasing. j = 0 or j = |
---|
21 | ! N is returned to indicate that x is out of range. This |
---|
22 | ! procedure should not be called with a zero-sized array argument. |
---|
23 | ! See notes. |
---|
24 | |
---|
25 | INTEGER n, jl, jm, ju |
---|
26 | LOGICAL ascnd |
---|
27 | |
---|
28 | !---------------------------- |
---|
29 | |
---|
30 | n = size(xx) |
---|
31 | ascnd = (xx(n) >= xx(1)) |
---|
32 | ! (True if ascending order of table, false otherwise.) |
---|
33 | ! Initialize lower and upper limits: |
---|
34 | jl = 0 |
---|
35 | ju = n + 1 |
---|
36 | do while (ju - jl > 1) |
---|
37 | jm = (ju + jl) / 2 ! Compute a midpoint, |
---|
38 | IF (ascnd .eqv. (x >= xx(jm))) THEN |
---|
39 | jl = jm ! and replace either the lower limit |
---|
40 | else |
---|
41 | ju = jm ! or the upper limit, as appropriate. |
---|
42 | end if |
---|
43 | END DO |
---|
44 | ! {ju == jl + 1} |
---|
45 | |
---|
46 | ! {(ascnd .AND. xx(jl) <= x < xx(jl+1)) |
---|
47 | ! .neqv. |
---|
48 | ! (.NOT. ascnd .AND. xx(jl+1) <= x < xx(jl))} |
---|
49 | |
---|
50 | ! Then set the output, being careful with the endpoints: |
---|
51 | IF (x == xx(1)) THEN |
---|
52 | locate = 1 |
---|
53 | ELSE IF (x == xx(n)) THEN |
---|
54 | locate = n - 1 |
---|
55 | else |
---|
56 | locate = jl |
---|
57 | end if |
---|
58 | |
---|
59 | END FUNCTION locate |
---|
60 | |
---|
61 | !*************************** |
---|
62 | |
---|
63 | pure SUBROUTINE hunt(xx, x, jlo) |
---|
64 | |
---|
65 | ! Given an array xx(1:N ), and given a value x, returns a value |
---|
66 | ! jlo such that x is between xx(jlo) and xx(jlo+1). xx must be |
---|
67 | ! monotonic, either increasing or decreasing. jlo = 0 or jlo = N is |
---|
68 | ! returned to indicate that x is out of range. jlo on input is taken as |
---|
69 | ! the initial guess for jlo on output. |
---|
70 | ! Modified so that it uses the information "jlo = 0" on input. |
---|
71 | |
---|
72 | INTEGER, INTENT(INOUT) :: jlo |
---|
73 | REAL, INTENT(IN) :: x |
---|
74 | REAL, DIMENSION(:), INTENT(IN) :: xx |
---|
75 | INTEGER n, inc, jhi, jm |
---|
76 | LOGICAL ascnd, hunt_up |
---|
77 | |
---|
78 | !----------------------------------------------------- |
---|
79 | |
---|
80 | n = size(xx) |
---|
81 | ascnd = (xx(n) >= xx(1)) |
---|
82 | ! (True if ascending order of table, false otherwise.) |
---|
83 | IF (jlo < 0 .OR. jlo > n) THEN |
---|
84 | ! Input guess not useful. Go immediately to bisection. |
---|
85 | jlo = 0 |
---|
86 | jhi = n + 1 |
---|
87 | else |
---|
88 | inc = 1 ! Set the hunting increment. |
---|
89 | IF (jlo == 0) THEN |
---|
90 | hunt_up = .TRUE. |
---|
91 | else |
---|
92 | hunt_up = x >= xx(jlo) .eqv. ascnd |
---|
93 | end if |
---|
94 | IF (hunt_up) then ! Hunt up: |
---|
95 | DO |
---|
96 | jhi = jlo + inc |
---|
97 | IF (jhi > n) then ! Done hunting, since off end of table. |
---|
98 | jhi = n + 1 |
---|
99 | exit |
---|
100 | else |
---|
101 | IF (x < xx(jhi) .eqv. ascnd) exit |
---|
102 | jlo = jhi ! Not done hunting, |
---|
103 | inc = inc + inc ! so double the increment |
---|
104 | end if |
---|
105 | END DO ! and try again. |
---|
106 | else ! Hunt down: |
---|
107 | jhi = jlo |
---|
108 | DO |
---|
109 | jlo = jhi - inc |
---|
110 | IF (jlo < 1) then ! Done hunting, since off end of table. |
---|
111 | jlo = 0 |
---|
112 | exit |
---|
113 | else |
---|
114 | IF (x >= xx(jlo) .eqv. ascnd) exit |
---|
115 | jhi = jlo ! Not done hunting, |
---|
116 | inc = inc + inc ! so double the increment |
---|
117 | end if |
---|
118 | END DO ! and try again. |
---|
119 | end if |
---|
120 | end if ! Done hunting, value bracketed. |
---|
121 | |
---|
122 | do ! Hunt is done, so begin the final bisection phase: |
---|
123 | IF (jhi - jlo <= 1) THEN |
---|
124 | IF (x == xx(n)) jlo = n - 1 |
---|
125 | IF (x == xx(1)) jlo = 1 |
---|
126 | exit |
---|
127 | else |
---|
128 | jm = (jhi + jlo) / 2 |
---|
129 | IF (x >= xx(jm) .eqv. ascnd) THEN |
---|
130 | jlo = jm |
---|
131 | else |
---|
132 | jhi = jm |
---|
133 | end if |
---|
134 | end if |
---|
135 | END DO |
---|
136 | |
---|
137 | END SUBROUTINE hunt |
---|
138 | |
---|
139 | END MODULE lmdz_interpolation |
---|