Statistiques
| Révision :

root / src / Splin1D.f90

Historique | Voir | Annoter | Télécharger (12,3 ko)

1
       SUBROUTINE spline(x,y,n,yp1,ypn,y2)
2
!Given arrays x(1:n) and y(1:n) containing a tabulated function,
3
! i.e., y i = f(xi), with x1<x2< :::<xN , and given values yp1 and ypn
4
!for the  rst derivative of the inter- polating function at points 1 and n,
5
! respectively, this routine returns an array y2(1:n) of length n
6
!which contains the second derivatives of the interpolating function
7
!at the tabulated points xi.
8
! Ifyp1 and/or ypn are equal to 1*10^30 or larger,
9
! the routine is signaled to set the corresponding boundary
10
!condition for a natural spline,
11
!with zero second derivative on that boundary.
12

    
13
!----------------------------------------------------------------------
14
!  Copyright 2003-2014 Ecole Normale Supérieure de Lyon, 
15
!  Centre National de la Recherche Scientifique,
16
!  Université Claude Bernard Lyon 1. All rights reserved.
17
!
18
!  This work is registered with the Agency for the Protection of Programs 
19
!  as IDDN.FR.001.100009.000.S.P.2014.000.30625
20
!
21
!  Authors: P. Fleurat-Lessard, P. Dayal
22
!  Contact: optnpath@gmail.com
23
!
24
! This file is part of "Opt'n Path".
25
!
26
!  "Opt'n Path" is free software: you can redistribute it and/or modify
27
!  it under the terms of the GNU Affero General Public License as
28
!  published by the Free Software Foundation, either version 3 of the License,
29
!  or (at your option) any later version.
30
!
31
!  "Opt'n Path" is distributed in the hope that it will be useful,
32
!  but WITHOUT ANY WARRANTY; without even the implied warranty of
33
!
34
!  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
35
!  GNU Affero General Public License for more details.
36
!
37
!  You should have received a copy of the GNU Affero General Public License
38
!  along with "Opt'n Path". If not, see <http://www.gnu.org/licenses/>.
39
!
40
! Contact The Office of Technology Licensing, valorisation@ens-lyon.fr,
41
! for commercial licensing opportunities.
42
!----------------------------------------------------------------------
43

    
44
         Use Vartypes
45

    
46
         IMPLICIT NONE
47

    
48
! Number of points
49
         INTEGER(KINT) :: n
50
! Coordinate to spline
51
         REAL(KREAL) :: x(n),y(n)
52
! Coefficients to compute
53
         REAL(KREAL) :: y2(n)
54
! End-points derivatives
55
         REAL(KREAL) ::yp1,ypn
56

    
57
       INTEGER(KINT), PARAMETER  :: NMAX=500
58

    
59
       INTEGER(KINT) :: i,k
60
       REAL(KREAL) :: p,qn,sig,un,u(NMAX)
61
       LOGICAL Debug
62

    
63
  INTERFACE
64
     function valid(string) result (isValid)
65
       CHARACTER(*), intent(in) :: string
66
       logical                  :: isValid
67
     END function VALID
68

    
69
  END INTERFACE
70

    
71
       Debug=valid("spline")
72

    
73
       IF (DEBUG) THEN
74
          WRITE(*,*) "Spline 1D",n
75
          WRITE(*,*) "x:",(x(i),i=1,n)
76
          WRITE(*,*) "y:",(y(i),i=1,n)
77
       END IF
78

    
79
       if (yp1.gt..99e30) then
80
! The lower boundary condition is set either to be \natural"
81
        y2(1)=0.
82
        u(1)=0.
83
       else
84
! or else to have a speci ed  rst derivative.
85
        y2(1)=-0.5
86
        u(1)=(3./(x(2)-x(1)))*((y(2)-y(1))/(x(2)-x(1))-yp1)
87
      endif
88
      do i=2,n-1
89
! This is the decomposition loop of the tridiagonal algorithm.
90
!y2 and u are used for temporary storage of the decomposed factors.
91
       sig=(x(i)-x(i-1))/(x(i+1)-x(i-1))
92
        p=sig*y2(i-1)+2.
93
       y2(i)=(sig-1.)/p
94
       u(i)=(6.*((y(i+1)-y(i))/(x(i+1)-x(i))-(y(i)-y(i-1)) &
95
                /(x(i)-x(i-1)))/(x(i+1)-x(i-1))-sig*u(i-1))/p
96
       enddo
97
       if (ypn.gt..99e30) then
98
!The upper boundary condition is set either to be \natural"
99
         qn=0.
100
         un=0.
101
        else
102
!or else to have a speci ed  rst derivative.
103
         qn=0.5
104
         un=(3./(x(n)-x(n-1)))*(ypn-(y(n)-y(n-1))/(x(n)-x(n-1)))
105
         endif
106
        y2(n)=(un-qn*u(n-1))/(qn*y2(n-1)+1.)
107
        do k=n-1,1,-1
108
         y2(k)=y2(k)*y2(k+1)+u(k)
109
        enddo
110

    
111
        IF (DEBUG)  WRITE(*,*) "y2:",(y2(i),i=1,n)
112
         return
113
        END
114

    
115

    
116
      SUBROUTINE splint(x,y,N,xa,ya,y2a)
117

    
118
         Use Vartypes
119

    
120
         IMPLICIT NONE
121

    
122
! Number of points
123
         INTEGER(KINT) :: n
124
! Spline coefficients
125
         REAL(KREAL) :: xa(n),ya(n), y2a(n)
126
! Y to compute for a given x
127
         REAL(KREAL) :: x,y
128

    
129

    
130
       LOGICAL debug
131

    
132
! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a
133
! function (with the xai's in order), and given the array y2a(1:n),
134
!which is the output from spline above, and given a value of x,
135
! this routine returns a cubic-spline interpolated value y.
136
       INTEGER(KINT) :: k,khi,klo
137
       REAL(KREAL) :: a,b,h
138

    
139

    
140
  INTERFACE
141
     function valid(string) result (isValid)
142
       CHARACTER(*), intent(in) :: string
143
       logical                  :: isValid
144
     END function VALID
145

    
146
  END INTERFACE
147

    
148
       Debug=valid("splint")
149

    
150

    
151
!           if (debug) THEN
152
!       WRITE(*,*) "Splint 1D",n
153
!       WRITE(*,*) "xa:",(xa(i),i=1,n)
154
!       WRITE(*,*) "ya:",(ya(i),i=1,n)
155
!       WRITE(*,*) "y2a:",(y2a(i),i=1,n)
156
!        END IF
157

    
158

    
159

    
160
          klo=1
161
!We will  find the right place in the table by means of bisection.
162
! This is optimal if sequential calls to this routine are at
163
!random values of x. If sequential calls are in order, and closely
164
! spaced, one would do better to store previous values of klo and khi
165
! and test if they remain appropriate on the next call.
166
          khi=n
167
 !         WRITE(*,*) xa(klo),xa(khi),n,x
168
 1        if (khi-klo.gt.1) then
169
             k=(khi+klo)/2
170
             if(xa(k).gt.x) then
171
                khi=k
172
             else
173
                klo=k
174
             endif
175
          goto 1
176
          endif
177
! klo and khi now bracket the input value of x.
178
          h=xa(khi)-xa(klo)
179
! The xa's must be distinct.
180
          if (h.eq.0.) THEN
181
             WRITE(*,*) 'bad xa input in splint'
182
             STOP
183
          END IF
184
! Cubic spline polynomial is now evaluated.
185
           a=(xa(khi)-x)/h
186
           b=(x-xa(klo))/h
187
           y=a*ya(klo)+b*ya(khi)+ ((a**3-a)*y2a(klo)+(b**3-b)*y2a(khi)) &
188
                *(h**2)/6.
189

    
190
!           WRITE(*,*) "Splint1D x,y",x,y
191
          return
192
          END
193

    
194

    
195
! SUBROUTINE splinder *************************************************
196
! *********************************************************************
197

    
198
      SUBROUTINE splinder(x,y,N,xa,ya,y2a)
199
         Use Vartypes
200

    
201
         IMPLICIT NONE
202

    
203
! Number of points
204
         INTEGER(KINT) :: n
205
! Spline coefficients
206
         REAL(KREAL) :: xa(n),ya(n), y2a(n)
207
! Y to compute for a given x
208
         REAL(KREAL) :: x,y
209

    
210

    
211
       LOGICAL debug
212

    
213
! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a
214
! function (with the xai's in order), and given the array y2a(1:n),
215
! which is the output from spline above, and given a value of x,
216
! this routine returns a cubic-spline interpolated value y first DERIVATIVE.
217
! this routine returns a cubic-spline interpolated value y.
218
       INTEGER(KINT) :: k,khi,klo
219
       REAL(KREAL) :: a,b,h
220

    
221

    
222
  INTERFACE
223
     function valid(string) result (isValid)
224
       CHARACTER(*), intent(in) :: string
225
       logical                  :: isValid
226
     END function VALID
227

    
228
  END INTERFACE
229

    
230
 
231
       Debug=valid("splinder")
232

    
233

    
234

    
235
          klo=1
236
! We will  find the right place in the table by means of bisection.
237
! This is optimal if sequential calls to this routine are at
238
!random values of x. If sequential calls are in order, and closely
239
! spaced, one would do better to store previous values of klo and khi
240
! and test if they remain appropriate on the next call.
241
          khi=n
242
 !         WRITE(*,*) xa(klo),xa(khi),n,x
243
 1        if (khi-klo.gt.1) then
244
             k=(khi+klo)/2
245
             if(xa(k).gt.x) then
246
                khi=k
247
             else
248
                klo=k
249
             endif
250
          goto 1
251
          endif
252
! klo and khi now bracket the input value of x.
253
          h=xa(khi)-xa(klo)
254
! The xa's must be distinct.
255
          if (h.eq.0.) THEN
256
             WRITE(*,*) 'bad xa input in splinder'
257
             STOP
258
          END IF
259
! Cubic spline polynomial is now evaluated.
260
           a=(xa(khi)-x)/h
261
           b=(x-xa(klo))/h
262
! Formula taken from the Numerical Recipies book.
263
           y=(ya(khi)-ya(klo))/h - (3*a**2-1)/6.*h*y2a(klo)+ &
264
                (3*b**2-1)/6.*h*y2a(khi)
265
          return
266
          END
267

    
268

    
269

    
270
! SUBROUTINE splintder *************************************************
271
! *********************************************************************
272

    
273
      SUBROUTINE splintDer(x,y,der,N,xa,ya,y2a)
274

    
275
! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a
276
! function (with the xai's in order), and given the array y2a(1:n),
277
! which is the output from spline above, and given a value of x,
278
! this routine returns a cubic-spline interpolated value y.
279
! and the derivative der.
280

    
281
         Use Vartypes
282

    
283
         IMPLICIT NONE
284

    
285
! Number of points
286
         INTEGER(KINT) :: n
287
! Spline coefficients
288
         REAL(KREAL) :: xa(n),ya(n), y2a(n)
289
! Y to compute for a given x
290
         REAL(KREAL) :: x,y, der
291

    
292

    
293
       LOGICAL debug
294

    
295
       INTEGER(KINT) :: k,khi,klo
296
       REAL(KREAL) :: a,b,h
297

    
298
  INTERFACE
299
     function valid(string) result (isValid)
300
       CHARACTER(*), intent(in) :: string
301
       logical                  :: isValid
302
     END function VALID
303

    
304
  END INTERFACE
305

    
306
       Debug=valid("splintder")
307

    
308

    
309
!           if (debug) THEN
310
!       WRITE(*,*) "SplintDer 1D",n
311
!       WRITE(*,*) "xa:",(xa(i),i=1,n)
312
!       WRITE(*,*) "ya:",(ya(i),i=1,n)
313
!       WRITE(*,*) "y2a:",(y2a(i),i=1,n)
314
!        END IF
315

    
316

    
317

    
318
          klo=1
319
! We will  find the right place in the table by means of bisection.
320
! This is optimal if sequential calls to this routine are at
321
! random values of x. If sequential calls are in order, and closely
322
! spaced, one would do better to store previous values of klo and khi
323
! and test if they remain appropriate on the next call.
324
          khi=n
325
 !         WRITE(*,*) xa(klo),xa(khi),n,x
326
 1        if (khi-klo.gt.1) then
327
             k=(khi+klo)/2
328
             if(xa(k).gt.x) then
329
                khi=k
330
             else
331
                klo=k
332
             endif
333
          goto 1
334
          endif
335
! klo and khi now bracket the input value of x.
336
          h=xa(khi)-xa(klo)
337
! The xa's must be distinct.
338
          if (h.eq.0.) THEN
339
             WRITE(*,*) 'bad xa input in splintDer'
340
             STOP
341
          END IF
342

    
343
! Cubic spline polynomial is now evaluated.
344
           a=(xa(khi)-x)/h
345
           b=(x-xa(klo))/h
346
           y=a*ya(klo)+b*ya(khi)+ ((a**3-a)*y2a(klo)+(b**3-b)*y2a(khi)) &
347
                *(h**2)/6.
348
! Formula taken from the Numerical Recipies book.
349
           der=(ya(khi)-ya(klo))/h - (3*a**2-1)/6.*h*y2a(klo)+ &
350
                (3*b**2-1)/6.*h*y2a(khi)
351
          return
352
        END SUBROUTINE splintDer
353

    
354

    
355

    
356
      SUBROUTINE LinearInt(x,y,der,N,xa,ya)
357

    
358
! Given the arrays xa(1:n) and ya(1:n) of length n, which tabulate a
359
! function (with the xai's in order),  and given a value of x,
360
! this routine returns a linear interpolated value y and its derivative der
361

    
362
         Use Vartypes
363

    
364
         IMPLICIT NONE
365

    
366
! Number of points
367
         INTEGER(KINT) :: n
368
! Spline coefficients
369
         REAL(KREAL) :: xa(n),ya(n)
370
! Y to compute for a given x
371
         REAL(KREAL) :: x,y, der
372

    
373

    
374
       LOGICAL debug
375

    
376
       INTEGER(KINT) :: k,khi,klo
377
       REAL(KREAL) :: a,b,h
378

    
379
  INTERFACE
380
     function valid(string) result (isValid)
381
       CHARACTER(*), intent(in) :: string
382
       logical                  :: isValid
383
     END function VALID
384

    
385
  END INTERFACE
386

    
387
       Debug=valid("linearint")
388

    
389

    
390
!           if (debug) THEN
391
!       WRITE(*,*) "SplintDer 1D",n
392
!       WRITE(*,*) "xa:",(xa(i),i=1,n)
393
!       WRITE(*,*) "ya:",(ya(i),i=1,n)
394
!       WRITE(*,*) "y2a:",(y2a(i),i=1,n)
395
!        END IF
396

    
397

    
398

    
399
          klo=1
400
! We will  find the right place in the table by means of bisection.
401
! This is optimal if sequential calls to this routine are at
402
! random values of x. If sequential calls are in order, and closely
403
! spaced, one would do better to store previous values of klo and khi
404
! and test if they remain appropriate on the next call.
405
          khi=n
406
 !         WRITE(*,*) xa(klo),xa(khi),n,x
407
 1        if (khi-klo.gt.1) then
408
             k=(khi+klo)/2
409
             if(xa(k).gt.x) then
410
                khi=k
411
             else
412
                klo=k
413
             endif
414
          goto 1
415
          endif
416
! klo and khi now bracket the input value of x.
417
          h=xa(khi)-xa(klo)
418
! The xa's must be distinct.
419
          if (h.eq.0.) THEN
420
             WRITE(*,*) 'bad xa input in LinearIntDer'
421
             STOP
422
          END IF
423

    
424
! Linear int now evaluated.
425
           a=(xa(khi)-x)/h
426
           b=(x-xa(klo))/h
427
           y=a*ya(klo)+b*ya(khi)
428
! Formula taken from the Numerical Recipies book.
429
           der=a+b
430
          return
431
        END SUBROUTINE LinearInt