Evaluates the tensor product piecewise polynomial
interpolant constructed by the routine db3ink or one of its
derivatives at the point (xval
,yval
,zval
).
To evaluate the
interpolant itself, set idx=idy=idz=0
, to evaluate the first
partial with respect to x
, set idx=1
,idy=idz=0
, and so on.
db3val returns 0.0 if (xval
,yval
,zval
) is out of range. that is,
xval<tx(1) .or. xval>tx(nx+kx) .or.
yval<ty(1) .or. yval>ty(ny+ky) .or.
zval<tz(1) .or. zval>tz(nz+kz)
if the knots tx
, ty
, and tz
were chosen by db3ink, then this is
equivalent to
xval<x(1) .or. xval>x(nx)+epsx .or.
yval<y(1) .or. yval>y(ny)+epsy .or.
zval<z(1) .or. zval>z(nz)+epsz
where
epsx = 0.1*(x(nx)-x(nx-1))
epsy = 0.1*(y(ny)-y(ny-1))
epsz = 0.1*(z(nz)-z(nz-1))
The input quantities tx
, ty
, tz
, nx
, ny
, nz
, kx
, ky
, kz
, and bcoef
should remain unchanged since the last call of db3ink.
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. |
||
real(kind=wp), | intent(in) | :: | zval |
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. |
||
integer(kind=ip), | intent(in) | :: | idz |
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 db3ink) |
|
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 db3ink) |
|
real(kind=wp), | intent(in), | dimension(nz+kz) | :: | tz |
sequence of knots defining the piecewise polynomial in the direction. (same as in last call to db3ink) |
|
integer(kind=ip), | intent(in) | :: | nx |
the number of interpolation points in . (same as in last call to db3ink) |
||
integer(kind=ip), | intent(in) | :: | ny |
the number of interpolation points in . (same as in last call to db3ink) |
||
integer(kind=ip), | intent(in) | :: | nz |
the number of interpolation points in . (same as in last call to db3ink) |
||
integer(kind=ip), | intent(in) | :: | kx |
order of polynomial pieces in . (same as in last call to db3ink) |
||
integer(kind=ip), | intent(in) | :: | ky |
order of polynomial pieces in . (same as in last call to db3ink) |
||
integer(kind=ip), | intent(in) | :: | kz |
order of polynomial pieces in . (same as in last call to db3ink) |
||
real(kind=wp), | intent(in), | dimension(nx,ny,nz) | :: | bcoef |
the b-spline coefficients computed by db3ink. |
|
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) | :: | inbvz |
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. |
||
integer(kind=ip), | intent(inout) | :: | iloz |
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,kz) | :: | w2 |
work array |
|
real(kind=wp), | intent(inout), | dimension(kz) | :: | w1 |
work array |
|
real(kind=wp), | intent(inout), | dimension(3_ip*max(kx,ky,kz)) | :: | w0 |
work array |
|
logical, | intent(in), | optional | :: | extrap |
if extrapolation is allowed (if not present, default is False) |
pure subroutine db3val(xval,yval,zval,idx,idy,idz,& tx,ty,tz,& nx,ny,nz,kx,ky,kz,bcoef,f,iflag,& inbvx,inbvy,inbvz,iloy,iloz,w2,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) :: idz !! \(z\) derivative of piecewise polynomial to evaluate. integer(ip),intent(in) :: nx !! the number of interpolation points in \(x\). !! (same as in last call to [[db3ink]]) integer(ip),intent(in) :: ny !! the number of interpolation points in \(y\). !! (same as in last call to [[db3ink]]) integer(ip),intent(in) :: nz !! the number of interpolation points in \(z\). !! (same as in last call to [[db3ink]]) integer(ip),intent(in) :: kx !! order of polynomial pieces in \(z\). !! (same as in last call to [[db3ink]]) integer(ip),intent(in) :: ky !! order of polynomial pieces in \(y\). !! (same as in last call to [[db3ink]]) integer(ip),intent(in) :: kz !! order of polynomial pieces in \(z\). !! (same as in last call to [[db3ink]]) real(wp),intent(in) :: xval !! \(x\) coordinate of evaluation point. real(wp),intent(in) :: yval !! \(y\) coordinate of evaluation point. real(wp),intent(in) :: zval !! \(z\) 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 [[db3ink]]) 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 [[db3ink]]) real(wp),dimension(nz+kz),intent(in) :: tz !! sequence of knots defining the piecewise polynomial !! in the \(z\) direction. (same as in last call to [[db3ink]]) real(wp),dimension(nx,ny,nz),intent(in) :: bcoef !! the b-spline coefficients computed by [[db3ink]]. 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) :: inbvz !! 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. integer(ip),intent(inout) :: iloz !! 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,kz),intent(inout) :: w2 !! work array real(wp),dimension(kz),intent(inout) :: w1 !! work array real(wp),dimension(3_ip*max(kx,ky,kz)),intent(inout) :: w0 !! work array logical,intent(in),optional :: extrap !! if extrapolation is allowed !! (if not present, default is False) integer(ip) :: lefty, leftz, kcoly, kcolz, j, k 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 iflag = check_value(zval,tz,3_ip,extrap); if (iflag/=0_ip) return call dintrv(ty,ny+ky,yval,iloy,lefty,iflag,extrap); if (iflag/=0_ip) return call dintrv(tz,nz+kz,zval,iloz,leftz,iflag,extrap); if (iflag/=0_ip) return iflag = 0_ip kcolz = leftz - kz do k=1_ip,kz kcolz = kcolz + 1_ip kcoly = lefty - ky do j=1_ip,ky kcoly = kcoly + 1_ip call dbvalu(tx,bcoef(:,kcoly,kcolz),nx,kx,idx,xval,inbvx,w0,iflag,w2(j,k),extrap) if (iflag/=0_ip) return end do end do kcoly = lefty - ky + 1_ip do k=1_ip,kz call dbvalu(ty(kcoly:),w2(:,k),ky,ky,idy,yval,inbvy,w0,iflag,w1(k),extrap) if (iflag/=0_ip) return end do kcolz = leftz - kz + 1_ip call dbvalu(tz(kcolz:),w1,kz,kz,idz,zval,inbvz,w0,iflag,f,extrap) end subroutine db3val