ViewVC Help
View File | Revision Log | Show Annotations | View Changeset | Root Listing
root/OpenMD/branches/development/src/utils/interpolation.F90
(Generate patch)

Comparing trunk/src/utils/interpolation.F90 (file contents):
Revision 931 by gezelter, Fri Apr 14 19:57:04 2006 UTC vs.
Revision 933 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.1 2006-04-14 19:57:04 gezelter Exp $
50 > !! @version $Id: interpolation.F90,v 1.3 2006-04-14 21:06:55 chrisfen Exp $
51  
52  
53   module  INTERPOLATION
# Line 64 | Line 64 | module  INTERPOLATION
64       real(kind=dp) :: dx
65       real(kind=dp) :: dx_i
66       real (kind=dp), pointer,dimension(:)   :: x => null()
67 <     real (kind=dp), pointer,dimension(4,:) :: c => null()
67 >     real (kind=dp), pointer,dimension(:,:) :: c => null()
68    end type cubicSpline
69  
70  interface splineLookup
71     module procedure multiSplint
72     module procedure splintd
73     module procedure splintd1
74     module procedure splintd2
75  end interface
76
70    interface newSpline
71 <     module procedure newSplineWithoutDerivs
79 <     module procedure newSplineWithDerivs
71 >     module procedure newSpline
72    end interface
73  
74    public :: deleteSpline
# Line 84 | 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 105 | 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 122 | 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
125    character(len=*), intent(in) :: boundary
117      real( kind = DP ) :: g, divdif1, divdif3, dx
118      integer :: i, alloc_error, np
119  
# Line 161 | 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
166 <       cs%c(2,1) = yp1
167 <    else
168 <       cs%c(2,1) = 0.0_DP
169 <    endif
170 <    if ((boundary.eq.'u').or.(boundary.eq.'U').or. &
171 <         (boundary.eq.'b').or.(boundary.eq.'B')) then
172 <       cs%c(2,1) = ypn
173 <    else
174 <       cs%c(2,1) = 0.0_DP
175 <    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 189 | Line 174 | contains
174      do i = 2, cs%np - 1
175         cs%c(4,i) = 2.0_DP * ( x(i+1) - x(i-1) )
176      end do
177 <    cs%c(4,n) = 1.0_DP
193 <    !
194 <    !  Set the off-diagonal coefficients.
195 <    !
196 <    cs%c(3,1) = 0.0_DP
197 <    do i = 2, cs%np
198 <       cs%c(3,i) = x(i) - x(i-1)
199 <    end do
200 <    !
201 <    !  Forward elimination.
202 <    !
203 <    do i = 2, cs%np - 1
204 <       g = -cs%c(3,i+1) / cs%c(4,i-1)
205 <       cs%c(4,i) = cs%c(4,i) + g * cs%c(3,i-1)
206 <       cs%c(2,i) = cs%c(2,i) + g * cs%c(2,i-1)
207 <    end do
208 <    !
209 <    !  Back substitution for the interior slopes.
210 <    !
211 <    do i = cs%np - 1, 2, -1
212 <       cs%c(2,i) = ( cs%c(2,i) - cs%c(3,i) * cs%c(2,i+1) ) / cs%c(4,i)
213 <    end do
214 <    !
215 <    !  Now compute the quadratic and cubic coefficients used in the
216 <    !  piecewise polynomial representation.
217 <    !
218 <    do i = 1, cs%np - 1
219 <       dx = x(i+1) - x(i)
220 <       divdif1 = ( cs%c(1,i+1) - cs%c(1,i) ) / dx
221 <       divdif3 = cs%c(2,i) + cs%c(2,i+1) - 2.0_DP * divdif1
222 <       cs%c(3,i) = ( divdif1 - cs%c(2,i) - divdif3 ) / dx
223 <       cs%c(4,i) = divdif3 / ( dx * dx )
224 <    end do
225 <
226 <    cs%c(3,np) = 0.0_DP
227 <    cs%c(4,np) = 0.0_DP
228 <
229 <    cs%dx = dx
230 <    cs%dxi = 1.0_DP / dx
231 <    return
232 <  end subroutine newSplineWithoutDerivs
233 <
234 <  subroutine newSplineWithDerivs(cs, x, y, yp)
235 <
236 <    !************************************************************************
177 >    cs%c(4,cs%np) = 1.0_DP
178      !
238    ! newSplineWithDerivs
239
240    implicit none
241
242    type (cubicSpline), intent(inout) :: cs
243    real( kind = DP ), intent(in) :: x(:), y(:), yp(:)
244    real( kind = DP ) :: g, divdif1, divdif3, dx
245    integer :: i, alloc_error, np
246
247    alloc_error = 0
248
249    if (cs%np .ne. 0) then
250       call handleWarning("interpolation::newSplineWithDerivs", &
251            "Type was already created")
252       call deleteSpline(cs)
253    end if
254
255    ! make sure the sizes match
256
257    if ((size(x) .ne. size(y)).or.(size(x) .ne. size(yp))) then
258       call handleError("interpolation::newSplineWithDerivs", &
259            "Array size mismatch")
260    end if
261    
262    np = size(x)
263    cs%np = np
264
265    allocate(cs%x(np), stat=alloc_error)
266    if(alloc_error .ne. 0) then
267       call handleError("interpolation::newSplineWithDerivs", &
268            "Error in allocating storage for x")
269    endif
270    
271    allocate(cs%c(4,np), stat=alloc_error)
272    if(alloc_error .ne. 0) then
273       call handleError("interpolation::newSplineWithDerivs", &
274            "Error in allocating storage for c")
275    endif
276    
277    do i = 1, np
278       cs%x(i) = x(i)
279       cs%c(1,i) = y(i)      
280       cs%c(2,i) = yp(i)
281    enddo
282    !
283    !  Set the diagonal coefficients.
284    !
285    cs%c(4,1) = 1.0_DP
286    do i = 2, cs%np - 1
287       cs%c(4,i) = 2.0_DP * ( x(i+1) - x(i-1) )
288    end do
289    cs%c(4,n) = 1.0_DP
290    !
179      !  Set the off-diagonal coefficients.
180      !
181      cs%c(3,1) = 0.0_DP
# Line 320 | Line 208 | contains
208         cs%c(4,i) = divdif3 / ( dx * dx )
209      end do
210  
211 <    cs%c(3,np) = 0.0_DP
212 <    cs%c(4,np) = 0.0_DP
211 >    cs%c(3,cs%np) = 0.0_DP
212 >    cs%c(4,cs%np) = 0.0_DP
213  
214      cs%dx = dx
215 <    cs%dxi = 1.0_DP / dx
328 <
215 >    cs%dx_i = 1.0_DP / dx
216      return
217    end subroutine newSplineWithoutDerivs
218  
# Line 375 | Line 262 | contains
262      type (cubicSpline), intent(in) :: cs
263      real( kind = DP ), intent(in)  :: xval
264      real( kind = DP ), intent(out) :: yval
265 +    real( kind = DP ) :: dx
266      integer :: i, j
267      !
268      !  Find the interval J = [ cs%x(J), cs%x(J+1) ] that contains
# Line 429 | Line 317 | contains
317      type (cubicSpline), intent(in) :: cs
318      real( kind = DP ), intent(in)  :: xval
319      real( kind = DP ), intent(out) :: yval
320 +    real( kind = DP ) :: dx
321      integer :: i, j
322      !
323      !  Find the interval J = [ cs%x(J), cs%x(J+1) ] that contains
324      !  or is nearest to xval.
325  
326 <    j = MAX(1, MIN(cs%np, idint((xval-cs%x(1)) * cs%dxi) + 1))
326 >    j = MAX(1, MIN(cs%np, idint((xval-cs%x(1)) * cs%dx_i) + 1))
327  
328      dx = xval - cs%x(j)
329  

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines