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.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=wp), | intent(in) | :: | xval |
coordinate of evaluation point. |
||
real(kind=wp), | intent(in) | :: | yval |
coordinate of evaluation point. |
||
integer(kind=ip), | intent(in) | :: | idx |
derivative of piecewise polynomial to evaluate. |
||
integer(kind=ip), | intent(in) | :: | idy |
derivative of piecewise polynomial to evaluate. |
||
real(kind=wp), | intent(in), | dimension(nx+kx) | :: | tx |
sequence of knots defining the piecewise polynomial in the 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 direction. (same as in last call to db2ink) |
|
integer(kind=ip), | intent(in) | :: | nx |
the number of interpolation points in . (same as in last call to db2ink) |
||
integer(kind=ip), | intent(in) | :: | ny |
the number of interpolation points in . (same as in last call to db2ink) |
||
integer(kind=ip), | intent(in) | :: | kx |
order of polynomial pieces in . (same as in last call to db2ink) |
||
integer(kind=ip), | intent(in) | :: | ky |
order of polynomial pieces in . (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(kind=ip), | intent(out) | :: | iflag |
status flag:
|
||
integer(kind=ip), | 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(kind=ip), | 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(kind=ip), | 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. |
||
real(kind=wp), | intent(inout), | dimension(ky) | :: | w1 |
work array |
|
real(kind=wp), | intent(inout), | dimension(3_ip*max(kx,ky)) | :: | w0 |
work array |
|
logical, | intent(in), | optional | :: | extrap |
if extrapolation is allowed (if not present, default is False) |
pure subroutine db2val(xval,yval,idx,idy,tx,ty,nx,ny,kx,ky,bcoef,f,iflag,inbvx,inbvy,iloy,w1,w0,extrap) implicit none integer(ip),intent(in) :: idx !! \(x\) derivative of piecewise polynomial to evaluate. integer(ip),intent(in) :: idy !! \(y\) derivative of piecewise polynomial to evaluate. integer(ip),intent(in) :: nx !! the number of interpolation points in \(x\). !! (same as in last call to [[db2ink]]) integer(ip),intent(in) :: ny !! the number of interpolation points in \(y\). !! (same as in last call to [[db2ink]]) integer(ip),intent(in) :: kx !! order of polynomial pieces in \(x\). !! (same as in last call to [[db2ink]]) integer(ip),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(ip),intent(out) :: iflag !! status flag: !! !! * \( = 0 \) : no errors !! * \( \ne 0 \) : error integer(ip),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(ip),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(ip),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. real(wp),dimension(ky),intent(inout) :: w1 !! work array real(wp),dimension(3_ip*max(kx,ky)),intent(inout) :: w0 !! work array logical,intent(in),optional :: extrap !! if extrapolation is allowed !! (if not present, default is False) integer(ip) :: k, lefty, kcol f = 0.0_wp iflag = check_value(xval,tx,1_ip,extrap); if (iflag/=0_ip) return iflag = check_value(yval,ty,2_ip,extrap); if (iflag/=0_ip) return call dintrv(ty,ny+ky,yval,iloy,lefty,iflag,extrap); if (iflag/=0_ip) return kcol = lefty - ky do k=1_ip,ky kcol = kcol + 1_ip call dbvalu(tx,bcoef(:,kcol),nx,kx,idx,xval,inbvx,w0,iflag,w1(k),extrap) if (iflag/=0_ip) return !error end do kcol = lefty - ky + 1_ip call dbvalu(ty(kcol:),w1,ky,ky,idy,yval,inbvy,w0,iflag,f,extrap) end subroutine db2val