root / src / Splin1D.f90 @ 12
Historique | Voir | Annoter | Télécharger (12,3 ko)
1 | 1 | pfleura2 | SUBROUTINE spline(x,y,n,yp1,ypn,y2) |
---|---|---|---|
2 | 1 | pfleura2 | !Given arrays x(1:n) and y(1:n) containing a tabulated function, |
3 | 1 | pfleura2 | ! i.e., y i = f(xi), with x1<x2< :::<xN , and given values yp1 and ypn |
4 | 1 | pfleura2 | !for the rst derivative of the inter- polating function at points 1 and n, |
5 | 1 | pfleura2 | ! respectively, this routine returns an array y2(1:n) of length n |
6 | 1 | pfleura2 | !which contains the second derivatives of the interpolating function |
7 | 1 | pfleura2 | !at the tabulated points xi. |
8 | 1 | pfleura2 | ! Ifyp1 and/or ypn are equal to 1*10^30 or larger, |
9 | 1 | pfleura2 | ! the routine is signaled to set the corresponding boundary |
10 | 1 | pfleura2 | !condition for a natural spline, |
11 | 1 | pfleura2 | !with zero second derivative on that boundary. |
12 | 1 | pfleura2 | |
13 | 12 | pfleura2 | !---------------------------------------------------------------------- |
14 | 12 | pfleura2 | ! Copyright 2003-2014 Ecole Normale Supérieure de Lyon, |
15 | 12 | pfleura2 | ! Centre National de la Recherche Scientifique, |
16 | 12 | pfleura2 | ! Université Claude Bernard Lyon 1. All rights reserved. |
17 | 12 | pfleura2 | ! |
18 | 12 | pfleura2 | ! This work is registered with the Agency for the Protection of Programs |
19 | 12 | pfleura2 | ! as IDDN.FR.001.100009.000.S.P.2014.000.30625 |
20 | 12 | pfleura2 | ! |
21 | 12 | pfleura2 | ! Authors: P. Fleurat-Lessard, P. Dayal |
22 | 12 | pfleura2 | ! Contact: optnpath@gmail.com |
23 | 12 | pfleura2 | ! |
24 | 12 | pfleura2 | ! This file is part of "Opt'n Path". |
25 | 12 | pfleura2 | ! |
26 | 12 | pfleura2 | ! "Opt'n Path" is free software: you can redistribute it and/or modify |
27 | 12 | pfleura2 | ! it under the terms of the GNU Affero General Public License as |
28 | 12 | pfleura2 | ! published by the Free Software Foundation, either version 3 of the License, |
29 | 12 | pfleura2 | ! or (at your option) any later version. |
30 | 12 | pfleura2 | ! |
31 | 12 | pfleura2 | ! "Opt'n Path" is distributed in the hope that it will be useful, |
32 | 12 | pfleura2 | ! but WITHOUT ANY WARRANTY; without even the implied warranty of |
33 | 12 | pfleura2 | ! |
34 | 12 | pfleura2 | ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the |
35 | 12 | pfleura2 | ! GNU Affero General Public License for more details. |
36 | 12 | pfleura2 | ! |
37 | 12 | pfleura2 | ! You should have received a copy of the GNU Affero General Public License |
38 | 12 | pfleura2 | ! along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>. |
39 | 12 | pfleura2 | ! |
40 | 12 | pfleura2 | ! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr, |
41 | 12 | pfleura2 | ! for commercial licensing opportunities. |
42 | 12 | pfleura2 | !---------------------------------------------------------------------- |
43 | 12 | pfleura2 | |
44 | 1 | pfleura2 | Use Vartypes |
45 | 1 | pfleura2 | |
46 | 1 | pfleura2 | IMPLICIT NONE |
47 | 1 | pfleura2 | |
48 | 1 | pfleura2 | ! Number of points |
49 | 1 | pfleura2 | INTEGER(KINT) :: n |
50 | 1 | pfleura2 | ! Coordinate to spline |
51 | 1 | pfleura2 | REAL(KREAL) :: x(n),y(n) |
52 | 1 | pfleura2 | ! Coefficients to compute |
53 | 1 | pfleura2 | REAL(KREAL) :: y2(n) |
54 | 1 | pfleura2 | ! End-points derivatives |
55 | 1 | pfleura2 | REAL(KREAL) ::yp1,ypn |
56 | 1 | pfleura2 | |
57 | 1 | pfleura2 | INTEGER(KINT), PARAMETER :: NMAX=500 |
58 | 1 | pfleura2 | |
59 | 1 | pfleura2 | INTEGER(KINT) :: i,k |
60 | 1 | pfleura2 | REAL(KREAL) :: p,qn,sig,un,u(NMAX) |
61 | 1 | pfleura2 | LOGICAL Debug |
62 | 1 | pfleura2 | |
63 | 1 | pfleura2 | INTERFACE |
64 | 1 | pfleura2 | function valid(string) result (isValid) |
65 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
66 | 1 | pfleura2 | logical :: isValid |
67 | 1 | pfleura2 | END function VALID |
68 | 1 | pfleura2 | |
69 | 1 | pfleura2 | END INTERFACE |
70 | 1 | pfleura2 | |
71 | 1 | pfleura2 | Debug=valid("spline") |
72 | 1 | pfleura2 | |
73 | 1 | pfleura2 | IF (DEBUG) THEN |
74 | 1 | pfleura2 | WRITE(*,*) "Spline 1D",n |
75 | 1 | pfleura2 | WRITE(*,*) "x:",(x(i),i=1,n) |
76 | 1 | pfleura2 | WRITE(*,*) "y:",(y(i),i=1,n) |
77 | 1 | pfleura2 | END IF |
78 | 1 | pfleura2 | |
79 | 1 | pfleura2 | if (yp1.gt..99e30) then |
80 | 1 | pfleura2 | ! The lower boundary condition is set either to be \natural" |
81 | 1 | pfleura2 | y2(1)=0. |
82 | 1 | pfleura2 | u(1)=0. |
83 | 1 | pfleura2 | else |
84 | 1 | pfleura2 | ! or else to have a speci ed rst derivative. |
85 | 1 | pfleura2 | y2(1)=-0.5 |
86 | 1 | pfleura2 | u(1)=(3./(x(2)-x(1)))*((y(2)-y(1))/(x(2)-x(1))-yp1) |
87 | 1 | pfleura2 | endif |
88 | 1 | pfleura2 | do i=2,n-1 |
89 | 1 | pfleura2 | ! This is the decomposition loop of the tridiagonal algorithm. |
90 | 1 | pfleura2 | !y2 and u are used for temporary storage of the decomposed factors. |
91 | 1 | pfleura2 | sig=(x(i)-x(i-1))/(x(i+1)-x(i-1)) |
92 | 1 | pfleura2 | p=sig*y2(i-1)+2. |
93 | 1 | pfleura2 | y2(i)=(sig-1.)/p |
94 | 1 | pfleura2 | u(i)=(6.*((y(i+1)-y(i))/(x(i+1)-x(i))-(y(i)-y(i-1)) & |
95 | 1 | pfleura2 | /(x(i)-x(i-1)))/(x(i+1)-x(i-1))-sig*u(i-1))/p |
96 | 1 | pfleura2 | enddo |
97 | 1 | pfleura2 | if (ypn.gt..99e30) then |
98 | 1 | pfleura2 | !The upper boundary condition is set either to be \natural" |
99 | 1 | pfleura2 | qn=0. |
100 | 1 | pfleura2 | un=0. |
101 | 1 | pfleura2 | else |
102 | 1 | pfleura2 | !or else to have a speci ed rst derivative. |
103 | 1 | pfleura2 | qn=0.5 |
104 | 1 | pfleura2 | un=(3./(x(n)-x(n-1)))*(ypn-(y(n)-y(n-1))/(x(n)-x(n-1))) |
105 | 1 | pfleura2 | endif |
106 | 1 | pfleura2 | y2(n)=(un-qn*u(n-1))/(qn*y2(n-1)+1.) |
107 | 1 | pfleura2 | do k=n-1,1,-1 |
108 | 1 | pfleura2 | y2(k)=y2(k)*y2(k+1)+u(k) |
109 | 1 | pfleura2 | enddo |
110 | 1 | pfleura2 | |
111 | 1 | pfleura2 | IF (DEBUG) WRITE(*,*) "y2:",(y2(i),i=1,n) |
112 | 1 | pfleura2 | return |
113 | 1 | pfleura2 | END |
114 | 1 | pfleura2 | |
115 | 1 | pfleura2 | |
116 | 1 | pfleura2 | SUBROUTINE splint(x,y,N,xa,ya,y2a) |
117 | 1 | pfleura2 | |
118 | 1 | pfleura2 | Use Vartypes |
119 | 1 | pfleura2 | |
120 | 1 | pfleura2 | IMPLICIT NONE |
121 | 1 | pfleura2 | |
122 | 1 | pfleura2 | ! Number of points |
123 | 1 | pfleura2 | INTEGER(KINT) :: n |
124 | 1 | pfleura2 | ! Spline coefficients |
125 | 1 | pfleura2 | REAL(KREAL) :: xa(n),ya(n), y2a(n) |
126 | 1 | pfleura2 | ! Y to compute for a given x |
127 | 1 | pfleura2 | REAL(KREAL) :: x,y |
128 | 1 | pfleura2 | |
129 | 1 | pfleura2 | |
130 | 1 | pfleura2 | LOGICAL debug |
131 | 1 | pfleura2 | |
132 | 1 | pfleura2 | ! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a |
133 | 1 | pfleura2 | ! function (with the xai's in order), and given the array y2a(1:n), |
134 | 1 | pfleura2 | !which is the output from spline above, and given a value of x, |
135 | 1 | pfleura2 | ! this routine returns a cubic-spline interpolated value y. |
136 | 1 | pfleura2 | INTEGER(KINT) :: k,khi,klo |
137 | 1 | pfleura2 | REAL(KREAL) :: a,b,h |
138 | 1 | pfleura2 | |
139 | 1 | pfleura2 | |
140 | 1 | pfleura2 | INTERFACE |
141 | 1 | pfleura2 | function valid(string) result (isValid) |
142 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
143 | 1 | pfleura2 | logical :: isValid |
144 | 1 | pfleura2 | END function VALID |
145 | 1 | pfleura2 | |
146 | 1 | pfleura2 | END INTERFACE |
147 | 1 | pfleura2 | |
148 | 1 | pfleura2 | Debug=valid("splint") |
149 | 1 | pfleura2 | |
150 | 1 | pfleura2 | |
151 | 1 | pfleura2 | ! if (debug) THEN |
152 | 1 | pfleura2 | ! WRITE(*,*) "Splint 1D",n |
153 | 1 | pfleura2 | ! WRITE(*,*) "xa:",(xa(i),i=1,n) |
154 | 1 | pfleura2 | ! WRITE(*,*) "ya:",(ya(i),i=1,n) |
155 | 1 | pfleura2 | ! WRITE(*,*) "y2a:",(y2a(i),i=1,n) |
156 | 1 | pfleura2 | ! END IF |
157 | 1 | pfleura2 | |
158 | 1 | pfleura2 | |
159 | 1 | pfleura2 | |
160 | 1 | pfleura2 | klo=1 |
161 | 1 | pfleura2 | !We will find the right place in the table by means of bisection. |
162 | 1 | pfleura2 | ! This is optimal if sequential calls to this routine are at |
163 | 1 | pfleura2 | !random values of x. If sequential calls are in order, and closely |
164 | 1 | pfleura2 | ! spaced, one would do better to store previous values of klo and khi |
165 | 1 | pfleura2 | ! and test if they remain appropriate on the next call. |
166 | 1 | pfleura2 | khi=n |
167 | 1 | pfleura2 | ! WRITE(*,*) xa(klo),xa(khi),n,x |
168 | 1 | pfleura2 | 1 if (khi-klo.gt.1) then |
169 | 1 | pfleura2 | k=(khi+klo)/2 |
170 | 1 | pfleura2 | if(xa(k).gt.x) then |
171 | 1 | pfleura2 | khi=k |
172 | 1 | pfleura2 | else |
173 | 1 | pfleura2 | klo=k |
174 | 1 | pfleura2 | endif |
175 | 1 | pfleura2 | goto 1 |
176 | 1 | pfleura2 | endif |
177 | 1 | pfleura2 | ! klo and khi now bracket the input value of x. |
178 | 1 | pfleura2 | h=xa(khi)-xa(klo) |
179 | 1 | pfleura2 | ! The xa's must be distinct. |
180 | 2 | pfleura2 | if (h.eq.0.) THEN |
181 | 2 | pfleura2 | WRITE(*,*) 'bad xa input in splint' |
182 | 2 | pfleura2 | STOP |
183 | 2 | pfleura2 | END IF |
184 | 1 | pfleura2 | ! Cubic spline polynomial is now evaluated. |
185 | 1 | pfleura2 | a=(xa(khi)-x)/h |
186 | 1 | pfleura2 | b=(x-xa(klo))/h |
187 | 1 | pfleura2 | y=a*ya(klo)+b*ya(khi)+ ((a**3-a)*y2a(klo)+(b**3-b)*y2a(khi)) & |
188 | 1 | pfleura2 | *(h**2)/6. |
189 | 1 | pfleura2 | |
190 | 1 | pfleura2 | ! WRITE(*,*) "Splint1D x,y",x,y |
191 | 1 | pfleura2 | return |
192 | 1 | pfleura2 | END |
193 | 1 | pfleura2 | |
194 | 1 | pfleura2 | |
195 | 1 | pfleura2 | ! SUBROUTINE splinder ************************************************* |
196 | 1 | pfleura2 | ! ********************************************************************* |
197 | 1 | pfleura2 | |
198 | 1 | pfleura2 | SUBROUTINE splinder(x,y,N,xa,ya,y2a) |
199 | 1 | pfleura2 | Use Vartypes |
200 | 1 | pfleura2 | |
201 | 1 | pfleura2 | IMPLICIT NONE |
202 | 1 | pfleura2 | |
203 | 1 | pfleura2 | ! Number of points |
204 | 1 | pfleura2 | INTEGER(KINT) :: n |
205 | 1 | pfleura2 | ! Spline coefficients |
206 | 1 | pfleura2 | REAL(KREAL) :: xa(n),ya(n), y2a(n) |
207 | 1 | pfleura2 | ! Y to compute for a given x |
208 | 1 | pfleura2 | REAL(KREAL) :: x,y |
209 | 1 | pfleura2 | |
210 | 1 | pfleura2 | |
211 | 1 | pfleura2 | LOGICAL debug |
212 | 1 | pfleura2 | |
213 | 1 | pfleura2 | ! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a |
214 | 1 | pfleura2 | ! function (with the xai's in order), and given the array y2a(1:n), |
215 | 1 | pfleura2 | ! which is the output from spline above, and given a value of x, |
216 | 1 | pfleura2 | ! this routine returns a cubic-spline interpolated value y first DERIVATIVE. |
217 | 1 | pfleura2 | ! this routine returns a cubic-spline interpolated value y. |
218 | 1 | pfleura2 | INTEGER(KINT) :: k,khi,klo |
219 | 1 | pfleura2 | REAL(KREAL) :: a,b,h |
220 | 1 | pfleura2 | |
221 | 1 | pfleura2 | |
222 | 1 | pfleura2 | INTERFACE |
223 | 1 | pfleura2 | function valid(string) result (isValid) |
224 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
225 | 1 | pfleura2 | logical :: isValid |
226 | 1 | pfleura2 | END function VALID |
227 | 1 | pfleura2 | |
228 | 1 | pfleura2 | END INTERFACE |
229 | 1 | pfleura2 | |
230 | 1 | pfleura2 | |
231 | 1 | pfleura2 | Debug=valid("splinder") |
232 | 1 | pfleura2 | |
233 | 1 | pfleura2 | |
234 | 1 | pfleura2 | |
235 | 1 | pfleura2 | klo=1 |
236 | 1 | pfleura2 | ! We will find the right place in the table by means of bisection. |
237 | 1 | pfleura2 | ! This is optimal if sequential calls to this routine are at |
238 | 1 | pfleura2 | !random values of x. If sequential calls are in order, and closely |
239 | 1 | pfleura2 | ! spaced, one would do better to store previous values of klo and khi |
240 | 1 | pfleura2 | ! and test if they remain appropriate on the next call. |
241 | 1 | pfleura2 | khi=n |
242 | 1 | pfleura2 | ! WRITE(*,*) xa(klo),xa(khi),n,x |
243 | 1 | pfleura2 | 1 if (khi-klo.gt.1) then |
244 | 1 | pfleura2 | k=(khi+klo)/2 |
245 | 1 | pfleura2 | if(xa(k).gt.x) then |
246 | 1 | pfleura2 | khi=k |
247 | 1 | pfleura2 | else |
248 | 1 | pfleura2 | klo=k |
249 | 1 | pfleura2 | endif |
250 | 1 | pfleura2 | goto 1 |
251 | 1 | pfleura2 | endif |
252 | 1 | pfleura2 | ! klo and khi now bracket the input value of x. |
253 | 1 | pfleura2 | h=xa(khi)-xa(klo) |
254 | 1 | pfleura2 | ! The xa's must be distinct. |
255 | 2 | pfleura2 | if (h.eq.0.) THEN |
256 | 2 | pfleura2 | WRITE(*,*) 'bad xa input in splinder' |
257 | 2 | pfleura2 | STOP |
258 | 2 | pfleura2 | END IF |
259 | 1 | pfleura2 | ! Cubic spline polynomial is now evaluated. |
260 | 1 | pfleura2 | a=(xa(khi)-x)/h |
261 | 1 | pfleura2 | b=(x-xa(klo))/h |
262 | 1 | pfleura2 | ! Formula taken from the Numerical Recipies book. |
263 | 1 | pfleura2 | y=(ya(khi)-ya(klo))/h - (3*a**2-1)/6.*h*y2a(klo)+ & |
264 | 1 | pfleura2 | (3*b**2-1)/6.*h*y2a(khi) |
265 | 1 | pfleura2 | return |
266 | 1 | pfleura2 | END |
267 | 1 | pfleura2 | |
268 | 1 | pfleura2 | |
269 | 1 | pfleura2 | |
270 | 1 | pfleura2 | ! SUBROUTINE splintder ************************************************* |
271 | 1 | pfleura2 | ! ********************************************************************* |
272 | 1 | pfleura2 | |
273 | 1 | pfleura2 | SUBROUTINE splintDer(x,y,der,N,xa,ya,y2a) |
274 | 1 | pfleura2 | |
275 | 1 | pfleura2 | ! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a |
276 | 1 | pfleura2 | ! function (with the xai's in order), and given the array y2a(1:n), |
277 | 1 | pfleura2 | ! which is the output from spline above, and given a value of x, |
278 | 1 | pfleura2 | ! this routine returns a cubic-spline interpolated value y. |
279 | 1 | pfleura2 | ! and the derivative der. |
280 | 1 | pfleura2 | |
281 | 1 | pfleura2 | Use Vartypes |
282 | 1 | pfleura2 | |
283 | 1 | pfleura2 | IMPLICIT NONE |
284 | 1 | pfleura2 | |
285 | 1 | pfleura2 | ! Number of points |
286 | 1 | pfleura2 | INTEGER(KINT) :: n |
287 | 1 | pfleura2 | ! Spline coefficients |
288 | 1 | pfleura2 | REAL(KREAL) :: xa(n),ya(n), y2a(n) |
289 | 1 | pfleura2 | ! Y to compute for a given x |
290 | 1 | pfleura2 | REAL(KREAL) :: x,y, der |
291 | 1 | pfleura2 | |
292 | 1 | pfleura2 | |
293 | 1 | pfleura2 | LOGICAL debug |
294 | 1 | pfleura2 | |
295 | 1 | pfleura2 | INTEGER(KINT) :: k,khi,klo |
296 | 1 | pfleura2 | REAL(KREAL) :: a,b,h |
297 | 1 | pfleura2 | |
298 | 1 | pfleura2 | INTERFACE |
299 | 1 | pfleura2 | function valid(string) result (isValid) |
300 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
301 | 1 | pfleura2 | logical :: isValid |
302 | 1 | pfleura2 | END function VALID |
303 | 1 | pfleura2 | |
304 | 1 | pfleura2 | END INTERFACE |
305 | 1 | pfleura2 | |
306 | 1 | pfleura2 | Debug=valid("splintder") |
307 | 1 | pfleura2 | |
308 | 1 | pfleura2 | |
309 | 1 | pfleura2 | ! if (debug) THEN |
310 | 1 | pfleura2 | ! WRITE(*,*) "SplintDer 1D",n |
311 | 1 | pfleura2 | ! WRITE(*,*) "xa:",(xa(i),i=1,n) |
312 | 1 | pfleura2 | ! WRITE(*,*) "ya:",(ya(i),i=1,n) |
313 | 1 | pfleura2 | ! WRITE(*,*) "y2a:",(y2a(i),i=1,n) |
314 | 1 | pfleura2 | ! END IF |
315 | 1 | pfleura2 | |
316 | 1 | pfleura2 | |
317 | 1 | pfleura2 | |
318 | 1 | pfleura2 | klo=1 |
319 | 1 | pfleura2 | ! We will find the right place in the table by means of bisection. |
320 | 1 | pfleura2 | ! This is optimal if sequential calls to this routine are at |
321 | 1 | pfleura2 | ! random values of x. If sequential calls are in order, and closely |
322 | 1 | pfleura2 | ! spaced, one would do better to store previous values of klo and khi |
323 | 1 | pfleura2 | ! and test if they remain appropriate on the next call. |
324 | 1 | pfleura2 | khi=n |
325 | 1 | pfleura2 | ! WRITE(*,*) xa(klo),xa(khi),n,x |
326 | 1 | pfleura2 | 1 if (khi-klo.gt.1) then |
327 | 1 | pfleura2 | k=(khi+klo)/2 |
328 | 1 | pfleura2 | if(xa(k).gt.x) then |
329 | 1 | pfleura2 | khi=k |
330 | 1 | pfleura2 | else |
331 | 1 | pfleura2 | klo=k |
332 | 1 | pfleura2 | endif |
333 | 1 | pfleura2 | goto 1 |
334 | 1 | pfleura2 | endif |
335 | 1 | pfleura2 | ! klo and khi now bracket the input value of x. |
336 | 1 | pfleura2 | h=xa(khi)-xa(klo) |
337 | 1 | pfleura2 | ! The xa's must be distinct. |
338 | 2 | pfleura2 | if (h.eq.0.) THEN |
339 | 2 | pfleura2 | WRITE(*,*) 'bad xa input in splintDer' |
340 | 2 | pfleura2 | STOP |
341 | 2 | pfleura2 | END IF |
342 | 2 | pfleura2 | |
343 | 1 | pfleura2 | ! Cubic spline polynomial is now evaluated. |
344 | 1 | pfleura2 | a=(xa(khi)-x)/h |
345 | 1 | pfleura2 | b=(x-xa(klo))/h |
346 | 1 | pfleura2 | y=a*ya(klo)+b*ya(khi)+ ((a**3-a)*y2a(klo)+(b**3-b)*y2a(khi)) & |
347 | 1 | pfleura2 | *(h**2)/6. |
348 | 1 | pfleura2 | ! Formula taken from the Numerical Recipies book. |
349 | 1 | pfleura2 | der=(ya(khi)-ya(klo))/h - (3*a**2-1)/6.*h*y2a(klo)+ & |
350 | 1 | pfleura2 | (3*b**2-1)/6.*h*y2a(khi) |
351 | 1 | pfleura2 | return |
352 | 1 | pfleura2 | END SUBROUTINE splintDer |
353 | 1 | pfleura2 | |
354 | 1 | pfleura2 | |
355 | 1 | pfleura2 | |
356 | 1 | pfleura2 | SUBROUTINE LinearInt(x,y,der,N,xa,ya) |
357 | 1 | pfleura2 | |
358 | 1 | pfleura2 | ! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a |
359 | 2 | pfleura2 | ! function (with the xai's in order), and given a value of x, |
360 | 2 | pfleura2 | ! this routine returns a linear interpolated value y and its derivative der |
361 | 1 | pfleura2 | |
362 | 1 | pfleura2 | Use Vartypes |
363 | 1 | pfleura2 | |
364 | 1 | pfleura2 | IMPLICIT NONE |
365 | 1 | pfleura2 | |
366 | 1 | pfleura2 | ! Number of points |
367 | 1 | pfleura2 | INTEGER(KINT) :: n |
368 | 1 | pfleura2 | ! Spline coefficients |
369 | 1 | pfleura2 | REAL(KREAL) :: xa(n),ya(n) |
370 | 1 | pfleura2 | ! Y to compute for a given x |
371 | 1 | pfleura2 | REAL(KREAL) :: x,y, der |
372 | 1 | pfleura2 | |
373 | 1 | pfleura2 | |
374 | 1 | pfleura2 | LOGICAL debug |
375 | 1 | pfleura2 | |
376 | 1 | pfleura2 | INTEGER(KINT) :: k,khi,klo |
377 | 1 | pfleura2 | REAL(KREAL) :: a,b,h |
378 | 1 | pfleura2 | |
379 | 1 | pfleura2 | INTERFACE |
380 | 1 | pfleura2 | function valid(string) result (isValid) |
381 | 1 | pfleura2 | CHARACTER(*), intent(in) :: string |
382 | 1 | pfleura2 | logical :: isValid |
383 | 1 | pfleura2 | END function VALID |
384 | 1 | pfleura2 | |
385 | 1 | pfleura2 | END INTERFACE |
386 | 1 | pfleura2 | |
387 | 1 | pfleura2 | Debug=valid("linearint") |
388 | 1 | pfleura2 | |
389 | 1 | pfleura2 | |
390 | 1 | pfleura2 | ! if (debug) THEN |
391 | 1 | pfleura2 | ! WRITE(*,*) "SplintDer 1D",n |
392 | 1 | pfleura2 | ! WRITE(*,*) "xa:",(xa(i),i=1,n) |
393 | 1 | pfleura2 | ! WRITE(*,*) "ya:",(ya(i),i=1,n) |
394 | 1 | pfleura2 | ! WRITE(*,*) "y2a:",(y2a(i),i=1,n) |
395 | 1 | pfleura2 | ! END IF |
396 | 1 | pfleura2 | |
397 | 1 | pfleura2 | |
398 | 1 | pfleura2 | |
399 | 1 | pfleura2 | klo=1 |
400 | 1 | pfleura2 | ! We will find the right place in the table by means of bisection. |
401 | 1 | pfleura2 | ! This is optimal if sequential calls to this routine are at |
402 | 1 | pfleura2 | ! random values of x. If sequential calls are in order, and closely |
403 | 1 | pfleura2 | ! spaced, one would do better to store previous values of klo and khi |
404 | 1 | pfleura2 | ! and test if they remain appropriate on the next call. |
405 | 1 | pfleura2 | khi=n |
406 | 1 | pfleura2 | ! WRITE(*,*) xa(klo),xa(khi),n,x |
407 | 1 | pfleura2 | 1 if (khi-klo.gt.1) then |
408 | 1 | pfleura2 | k=(khi+klo)/2 |
409 | 1 | pfleura2 | if(xa(k).gt.x) then |
410 | 1 | pfleura2 | khi=k |
411 | 1 | pfleura2 | else |
412 | 1 | pfleura2 | klo=k |
413 | 1 | pfleura2 | endif |
414 | 1 | pfleura2 | goto 1 |
415 | 1 | pfleura2 | endif |
416 | 1 | pfleura2 | ! klo and khi now bracket the input value of x. |
417 | 1 | pfleura2 | h=xa(khi)-xa(klo) |
418 | 1 | pfleura2 | ! The xa's must be distinct. |
419 | 2 | pfleura2 | if (h.eq.0.) THEN |
420 | 2 | pfleura2 | WRITE(*,*) 'bad xa input in LinearIntDer' |
421 | 2 | pfleura2 | STOP |
422 | 2 | pfleura2 | END IF |
423 | 2 | pfleura2 | |
424 | 1 | pfleura2 | ! Linear int now evaluated. |
425 | 1 | pfleura2 | a=(xa(khi)-x)/h |
426 | 1 | pfleura2 | b=(x-xa(klo))/h |
427 | 1 | pfleura2 | y=a*ya(klo)+b*ya(khi) |
428 | 1 | pfleura2 | ! Formula taken from the Numerical Recipies book. |
429 | 1 | pfleura2 | der=a+b |
430 | 1 | pfleura2 | return |
431 | 1 | pfleura2 | END SUBROUTINE LinearInt |