db2val Subroutine

public subroutine db2val(xval, yval, idx, idy, tx, ty, nx, ny, kx, ky, bcoef, f, iflag, inbvx, inbvy, iloy)

Evaluates the tensor product piecewise polynomial interpolant constructed by the routine db2ink or one of its derivatives at the point (xval,yval).

To evaluate the interpolant itself, set idx=idy=0, to evaluate the first partial with respect to x, set idx=1,idy=0, and so on.

db2val returns 0.0 if (xval,yval) is out of range. that is, if

   xval < tx(1) .or. xval > tx(nx+kx) .or.
   yval < ty(1) .or. yval > ty(ny+ky)

if the knots tx and ty were chosen by db2ink, then this is equivalent to:

   xval < x(1) .or. xval > x(nx)+epsx .or.
   yval < y(1) .or. yval > y(ny)+epsy

where

   epsx = 0.1*(x(nx)-x(nx-1))
   epsy = 0.1*(y(ny)-y(ny-1))

The input quantities tx, ty, nx, ny, kx, ky, and bcoef should be unchanged since the last call of db2ink.

History

  • Boisvert, Ronald, NBS : 25 may 1982 : Author of original routine.
  • JEC : 000330 modified array declarations.
  • Jacob Williams, 2/24/2015 : extensive refactoring of CMLIB routine.

Arguments

Type IntentOptional Attributes Name
real(kind=wp), intent(in) :: xval

x coordinate of evaluation point.

real(kind=wp), intent(in) :: yval

y coordinate of evaluation point.

integer, intent(in) :: idx

x derivative of piecewise polynomial to evaluate.

integer, intent(in) :: idy

y derivative of piecewise polynomial to evaluate.

real(kind=wp), intent(in), dimension(nx+kx) :: tx

sequence of knots defining the piecewise polynomial in the x direction. (same as in last call to db2ink)

real(kind=wp), intent(in), dimension(ny+ky) :: ty

sequence of knots defining the piecewise polynomial in the y direction. (same as in last call to db2ink)

integer, intent(in) :: nx

the number of interpolation points in x. (same as in last call to db2ink)

integer, intent(in) :: ny

the number of interpolation points in y. (same as in last call to db2ink)

integer, intent(in) :: kx

order of polynomial pieces in x. (same as in last call to db2ink)

integer, intent(in) :: ky

order of polynomial pieces in y. (same as in last call to db2ink)

real(kind=wp), intent(in), dimension(nx,ny) :: bcoef

the b-spline coefficients computed by db2ink.

real(kind=wp), intent(out) :: f

interpolated value

integer, intent(out) :: iflag

status flag: 0 : no errors, /=0 : error

integer, intent(inout) :: inbvx

initialization parameter which must be set to 1 the first time this routine is called, and must not be changed by the user.

integer, intent(inout) :: inbvy

initialization parameter which must be set to 1 the first time this routine is called, and must not be changed by the user.

integer, intent(inout) :: iloy

initialization parameter which must be set to 1 the first time this routine is called, and must not be changed by the user.


Calls

proc~~db2val~~CallsGraph proc~db2val db2val proc~dbvalu dbvalu proc~db2val->proc~dbvalu proc~dintrv dintrv proc~db2val->proc~dintrv proc~dbvalu->proc~dintrv

Called by

proc~~db2val~~CalledByGraph proc~db2val db2val proc~interp_surf interp_surf proc~interp_surf->proc~db2val program~test_bspline test_bspline program~test_bspline->proc~interp_surf

Source Code

    subroutine db2val(xval,yval,idx,idy,tx,ty,nx,ny,kx,ky,bcoef,f,iflag,inbvx,inbvy,iloy)

    implicit none

    integer,intent(in)                   :: idx      !! x derivative of piecewise polynomial to evaluate.
    integer,intent(in)                   :: idy      !! y derivative of piecewise polynomial to evaluate.
    integer,intent(in)                   :: nx       !! the number of interpolation points in x. (same as in last call to [[db2ink]])
    integer,intent(in)                   :: ny       !! the number of interpolation points in y. (same as in last call to [[db2ink]])
    integer,intent(in)                   :: kx       !! order of polynomial pieces in x. (same as in last call to [[db2ink]])
    integer,intent(in)                   :: ky       !! order of polynomial pieces in y. (same as in last call to [[db2ink]])
    real(wp),intent(in)                  :: xval     !! x coordinate of evaluation point.
    real(wp),intent(in)                  :: yval     !! y coordinate of evaluation point.
    real(wp),dimension(nx+kx),intent(in) :: tx       !! sequence of knots defining the piecewise polynomial in the x direction. (same as in last call to [[db2ink]])
    real(wp),dimension(ny+ky),intent(in) :: ty       !! sequence of knots defining the piecewise polynomial in the y direction. (same as in last call to [[db2ink]])
    real(wp),dimension(nx,ny),intent(in) :: bcoef    !! the b-spline coefficients computed by [[db2ink]].
    real(wp),intent(out)                 :: f        !! interpolated value
    integer,intent(out)                  :: iflag    !! status flag: 0 : no errors, /=0 : error
    integer,intent(inout)                :: inbvx    !! initialization parameter which must be set to 1 the first time this routine is called, and must not be changed by the user.
    integer,intent(inout)                :: inbvy    !! initialization parameter which must be set to 1 the first time this routine is called, and must not be changed by the user.
    integer,intent(inout)                :: iloy     !! initialization parameter which must be set to 1 the first time this routine is called, and must not be changed by the user.

    integer :: k, lefty, mflag, kcol
    real(wp),dimension(ky) :: temp
    real(wp),dimension(3*max(kx,ky)) :: work

    f = 0.0_wp

    if (xval<tx(1) .or. xval>tx(nx+kx)) then
        write(error_unit,'(A)') 'db2val - x value out of bounds'
        iflag = 1
        return
    endif
    if (yval<ty(1) .or. yval>ty(ny+ky)) then
        write(error_unit,'(A)') 'db2val - y value out of bounds'
        iflag = 2
        return
    endif

    iflag = -1
    call dintrv(ty,ny+ky,yval,iloy,lefty,mflag); if (mflag /= 0) return

    kcol = lefty - ky
    do k=1,ky
        kcol = kcol + 1
        temp(k) = dbvalu(tx,bcoef(:,kcol),nx,kx,idx,xval,inbvx,work,iflag)
        if (iflag/=0) return !error
    enddo

    kcol = lefty - ky + 1
    f = dbvalu(ty(kcol:),temp,ky,ky,idy,yval,inbvy,work,iflag)

    endsubroutine db2val