ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/group/trunk/OOPSE-3.0/src/utils/interpolation.F90
(Generate patch)

Comparing trunk/OOPSE-3.0/src/utils/interpolation.F90 (file contents):
Revision 2709 by gezelter, Fri Apr 14 20:04:31 2006 UTC vs.
Revision 2710 by chrisfen, Fri Apr 14 21:06:55 2006 UTC

# Line 47 | Line 47
47   !!           precomputation of spline parameters.
48   !!
49   !! @author Charles F. Vardeman II
50 < !! @version $Id: interpolation.F90,v 1.2 2006-04-14 20:04:31 gezelter Exp $
50 > !! @version $Id: interpolation.F90,v 1.3 2006-04-14 21:06:55 chrisfen Exp $
51  
52  
53   module  INTERPOLATION
# Line 68 | Line 68 | module  INTERPOLATION
68    end type cubicSpline
69  
70    interface newSpline
71 <     module procedure newSplineWithoutDerivs
72 <     module procedure newSplineWithDerivs
71 >     module procedure newSpline
72    end interface
73  
74    public :: deleteSpline
# Line 77 | Line 76 | contains
76   contains
77  
78  
79 <  subroutine newSplineWithoutDerivs(cs, x, y, yp1, ypn, boundary)
79 >  subroutine newSpline(cs, x, y, yp1, ypn)
80  
81      !************************************************************************
82      !
# Line 98 | Line 97 | contains
97      !  Parameters:
98      !
99      !    Input, real x(N), the abscissas or X values of
100 <    !    the data points.  The entries of TAU are assumed to be
100 >    !    the data points.  The entries of x are assumed to be
101      !    strictly increasing.
102      !
103      !    Input, real y(I), contains the function value at x(I) for
# Line 115 | Line 114 | contains
114      type (cubicSpline), intent(inout) :: cs
115      real( kind = DP ), intent(in) :: x(:), y(:)
116      real( kind = DP ), intent(in) :: yp1, ypn
118    character(len=*), intent(in) :: boundary
117      real( kind = DP ) :: g, divdif1, divdif3, dx
118      integer :: i, alloc_error, np
119  
# Line 154 | Line 152 | contains
152         cs%c(1,i) = y(i)      
153      enddo
154  
155 <    if ((boundary.eq.'l').or.(boundary.eq.'L').or. &
156 <         (boundary.eq.'b').or.(boundary.eq.'B')) then
159 <       cs%c(2,1) = yp1
160 <    else
161 <       cs%c(2,1) = 0.0_DP
162 <    endif
163 <    if ((boundary.eq.'u').or.(boundary.eq.'U').or. &
164 <         (boundary.eq.'b').or.(boundary.eq.'B')) then
165 <       cs%c(2,1) = ypn
166 <    else
167 <       cs%c(2,1) = 0.0_DP
168 <    endif
155 >    ! Set the first derivative of the function to the second coefficient of
156 >    ! each of the endpoints
157  
158 +    cs%c(2,1) = yp1
159 +    cs%c(2,np) = ypn
160 +    
161 +
162      !
163      !  Set up the right hand side of the linear system.
164      !
# Line 223 | Line 215 | contains
215      cs%dx_i = 1.0_DP / dx
216      return
217    end subroutine newSplineWithoutDerivs
226
227  subroutine newSplineWithDerivs(cs, x, y, yp)
228
229    !************************************************************************
230    !
231    ! newSplineWithDerivs
232
233    implicit none
234
235    type (cubicSpline), intent(inout) :: cs
236    real( kind = DP ), intent(in) :: x(:), y(:), yp(:)
237    real( kind = DP ) :: g, divdif1, divdif3, dx
238    integer :: i, alloc_error, np
239
240    alloc_error = 0
241
242    if (cs%np .ne. 0) then
243       call handleWarning("interpolation::newSplineWithDerivs", &
244            "Type was already created")
245       call deleteSpline(cs)
246    end if
247
248    ! make sure the sizes match
249
250    if ((size(x) .ne. size(y)).or.(size(x) .ne. size(yp))) then
251       call handleError("interpolation::newSplineWithDerivs", &
252            "Array size mismatch")
253    end if
254    
255    np = size(x)
256    cs%np = np
257
258    allocate(cs%x(np), stat=alloc_error)
259    if(alloc_error .ne. 0) then
260       call handleError("interpolation::newSplineWithDerivs", &
261            "Error in allocating storage for x")
262    endif
263    
264    allocate(cs%c(4,np), stat=alloc_error)
265    if(alloc_error .ne. 0) then
266       call handleError("interpolation::newSplineWithDerivs", &
267            "Error in allocating storage for c")
268    endif
269    
270    do i = 1, np
271       cs%x(i) = x(i)
272       cs%c(1,i) = y(i)      
273       cs%c(2,i) = yp(i)
274    enddo
275    !
276    !  Set the diagonal coefficients.
277    !
278    cs%c(4,1) = 1.0_DP
279    do i = 2, cs%np - 1
280       cs%c(4,i) = 2.0_DP * ( x(i+1) - x(i-1) )
281    end do
282    cs%c(4,cs%np) = 1.0_DP
283    !
284    !  Set the off-diagonal coefficients.
285    !
286    cs%c(3,1) = 0.0_DP
287    do i = 2, cs%np
288       cs%c(3,i) = x(i) - x(i-1)
289    end do
290    !
291    !  Forward elimination.
292    !
293    do i = 2, cs%np - 1
294       g = -cs%c(3,i+1) / cs%c(4,i-1)
295       cs%c(4,i) = cs%c(4,i) + g * cs%c(3,i-1)
296       cs%c(2,i) = cs%c(2,i) + g * cs%c(2,i-1)
297    end do
298    !
299    !  Back substitution for the interior slopes.
300    !
301    do i = cs%np - 1, 2, -1
302       cs%c(2,i) = ( cs%c(2,i) - cs%c(3,i) * cs%c(2,i+1) ) / cs%c(4,i)
303    end do
304    !
305    !  Now compute the quadratic and cubic coefficients used in the
306    !  piecewise polynomial representation.
307    !
308    do i = 1, cs%np - 1
309       dx = x(i+1) - x(i)
310       divdif1 = ( cs%c(1,i+1) - cs%c(1,i) ) / dx
311       divdif3 = cs%c(2,i) + cs%c(2,i+1) - 2.0_DP * divdif1
312       cs%c(3,i) = ( divdif1 - cs%c(2,i) - divdif3 ) / dx
313       cs%c(4,i) = divdif3 / ( dx * dx )
314    end do
218  
316    cs%c(3,cs%np) = 0.0_DP
317    cs%c(4,cs%np) = 0.0_DP
318
319    cs%dx = dx
320    cs%dx_i = 1.0_DP / dx
321
322    return
323  end subroutine newSplineWithDerivs
324
219    subroutine deleteSpline(this)
220  
221      type(cubicSpline) :: this

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines