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

Comparing trunk/OOPSE-4/src/utils/interpolation.F90 (file contents):
Revision 2710 by chrisfen, Fri Apr 14 21:06:55 2006 UTC vs.
Revision 2711 by gezelter, Fri Apr 14 21:49:54 2006 UTC

# Line 43 | Line 43
43   !!
44   !!  Created by Charles F. Vardeman II on 03 Apr 2006.
45   !!
46 < !!  PURPOSE: Generic Spline interplelation routines. These routines assume that we are on a uniform grid for
47 < !!           precomputation of spline parameters.
46 > !!  PURPOSE: Generic Spline interpolation routines. These routines
47 > !!           assume that we are on a uniform grid for precomputation of
48 > !!           spline parameters.
49   !!
50   !! @author Charles F. Vardeman II
51 < !! @version $Id: interpolation.F90,v 1.3 2006-04-14 21:06:55 chrisfen Exp $
51 > !! @version $Id: interpolation.F90,v 1.4 2006-04-14 21:49:54 gezelter Exp $
52  
53  
54   module  INTERPOLATION
# Line 60 | Line 61 | module  INTERPOLATION
61  
62    type, public :: cubicSpline
63       private
64 +     logical :: isUniform = .false.
65       integer :: np = 0
64     real(kind=dp) :: dx
66       real(kind=dp) :: dx_i
67       real (kind=dp), pointer,dimension(:)   :: x => null()
68       real (kind=dp), pointer,dimension(:,:) :: c => null()
69    end type cubicSpline
70  
71 <  interface newSpline
71 <     module procedure newSpline
72 <  end interface
73 <
71 >  public :: newSpline
72    public :: deleteSpline
73 <
73 >  public :: lookup_spline
74 >  public :: lookup_uniform_spline
75 >  public :: lookup_nonuniform_spline
76 >  
77   contains
78 +  
79  
80 <
81 <  subroutine newSpline(cs, x, y, yp1, ypn)
80 <
80 >  subroutine newSpline(cs, x, y, yp1, ypn, isUniform)
81 >    
82      !************************************************************************
83      !
84 <    ! newSplineWithoutDerivs solves for slopes defining a cubic spline.
84 >    ! newSpline solves for slopes defining a cubic spline.
85      !
86      !  Discussion:
87      !
# Line 103 | Line 104 | contains
104      !    Input, real y(I), contains the function value at x(I) for
105      !      I = 1, N.
106      !
107 <    !    yp1 contains the slope at x(1) and ypn contains
108 <    !    the slope at x(N).
107 >    !    Input, real yp1 contains the slope at x(1)
108 >    !    Input, real ypn contains the slope at x(N)
109      !
110 <    !    On output, the intermediate slopes at x(I) have been
111 <    !    stored in cs%C(2,I), for I = 2 to N-1.
110 >    !    On output, the slopes at x(I) have been stored in
111 >    !               cs%C(2,I), for I = 1 to N.
112  
113      implicit none
114  
115      type (cubicSpline), intent(inout) :: cs
116      real( kind = DP ), intent(in) :: x(:), y(:)
117      real( kind = DP ), intent(in) :: yp1, ypn
118 +    logical, intent(in) :: isUniform
119      real( kind = DP ) :: g, divdif1, divdif3, dx
120      integer :: i, alloc_error, np
121  
122      alloc_error = 0
123  
124      if (cs%np .ne. 0) then
125 <       call handleWarning("interpolation::newSplineWithoutDerivs", &
126 <            "Type was already created")
125 >       call handleWarning("interpolation::newSpline", &
126 >            "cubicSpline struct was already created")
127         call deleteSpline(cs)
128      end if
129  
130      ! make sure the sizes match
131  
132 <    if (size(x) .ne. size(y)) then
133 <       call handleError("interpolation::newSplineWithoutDerivs", &
132 >    np = size(x)
133 >
134 >    if ( size(y) .ne. np ) then
135 >       call handleError("interpolation::newSpline", &
136              "Array size mismatch")
137      end if
138 <
135 <    np = size(x)
138 >    
139      cs%np = np
140 +    cs%isUniform = isUniform
141  
142      allocate(cs%x(np), stat=alloc_error)
143      if(alloc_error .ne. 0) then
144 <       call handleError("interpolation::newSplineWithoutDerivs", &
144 >       call handleError("interpolation::newSpline", &
145              "Error in allocating storage for x")
146      endif
147  
148      allocate(cs%c(4,np), stat=alloc_error)
149      if(alloc_error .ne. 0) then
150 <       call handleError("interpolation::newSplineWithoutDerivs", &
150 >       call handleError("interpolation::newSpline", &
151              "Error in allocating storage for c")
152      endif
153        
# Line 158 | Line 162 | contains
162      cs%c(2,1) = yp1
163      cs%c(2,np) = ypn
164      
161
165      !
166      !  Set up the right hand side of the linear system.
167      !
168 +
169      do i = 2, cs%np - 1
170         cs%c(2,i) = 3.0_DP * ( &
171              (x(i) - x(i-1)) * (cs%c(1,i+1) - cs%c(1,i)) / (x(i+1) - x(i)) + &
172              (x(i+1) - x(i)) * (cs%c(1,i) - cs%c(1,i-1)) / (x(i) - x(i-1)))
173      end do
174 +
175      !
176      !  Set the diagonal coefficients.
177      !
# Line 211 | Line 216 | contains
216      cs%c(3,cs%np) = 0.0_DP
217      cs%c(4,cs%np) = 0.0_DP
218  
214    cs%dx = dx
219      cs%dx_i = 1.0_DP / dx
220 +
221      return
222    end subroutine newSplineWithoutDerivs
223  
# Line 331 | Line 336 | contains
336      
337      return
338    end subroutine lookup_uniform_spline
339 +
340 +  subroutine lookup_spline(cs, xval, yval)
341 +
342 +    type (cubicSpline), intent(in) :: cs
343 +    real( kind = DP ), intent(inout) :: xval
344 +    real( kind = DP ), intent(inout) :: yval
345 +    
346 +    if (cs%isUniform) then
347 +       call lookup_uniform_spline(cs, xval, yval)
348 +    else
349 +       call lookup_nonuniform_spline(cs, xval, yval)
350 +    endif
351 +
352 +    return
353 +  end subroutine lookup_spline
354    
355   end module INTERPOLATION

Diff Legend

Removed lines
+ Added lines
< Changed lines
> Changed lines