db1val_default Subroutine

private pure subroutine db1val_default(xval, idx, tx, nx, kx, bcoef, f, iflag, inbvx, w0, extrap)

Evaluates the tensor product piecewise polynomial interpolant constructed by the routine db1ink or one of its derivatives at the point xval.

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

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

   xval < tx(1) .or. xval > tx(nx+kx)

if the knots tx were chosen by db1ink, then this is equivalent to:

   xval < x(1) .or. xval > x(nx)+epsx

where

   epsx = 0.1*(x(nx)-x(nx-1))

The input quantities tx, nx, kx, and bcoef should be unchanged since the last call of db1ink.

History

  • Jacob Williams, 10/30/2015 : Created 1D routine.

Arguments

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

coordinate of evaluation point.

integer(kind=ip), intent(in) :: idx

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 db1ink)

integer(kind=ip), intent(in) :: nx

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

integer(kind=ip), intent(in) :: kx

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

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

the b-spline coefficients computed by db1ink.

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

interpolated value

integer(kind=ip), intent(out) :: iflag

status flag:

  • : no errors
  • : error
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.

real(kind=wp), intent(inout), dimension(3_ip*kx) :: w0

work array

logical, intent(in), optional :: extrap

if extrapolation is allowed (if not present, default is False)


Calls

proc~~db1val_default~~CallsGraph proc~db1val_default bspline_sub_module::db1val_default proc~check_value bspline_sub_module::check_value proc~db1val_default->proc~check_value proc~dbvalu bspline_sub_module::dbvalu proc~db1val_default->proc~dbvalu proc~dintrv bspline_sub_module::dintrv proc~dbvalu->proc~dintrv proc~get_temp_x_for_extrap bspline_sub_module::get_temp_x_for_extrap proc~dintrv->proc~get_temp_x_for_extrap

Called by

proc~~db1val_default~~CalledByGraph proc~db1val_default bspline_sub_module::db1val_default interface~db1val bspline_sub_module::db1val interface~db1val->proc~db1val_default proc~evaluate_1d bspline_oo_module::bspline_1d%evaluate_1d proc~evaluate_1d->interface~db1val

Source Code

    pure subroutine db1val_default(xval,idx,tx,nx,kx,bcoef,f,iflag,inbvx,w0,extrap)

    implicit none

    integer(ip),intent(in)               :: idx      !! \(x\) derivative of piecewise polynomial to evaluate.
    integer(ip),intent(in)               :: nx       !! the number of interpolation points in \(x\).
                                                     !! (same as in last call to [[db1ink]])
    integer(ip),intent(in)               :: kx       !! order of polynomial pieces in \(x\).
                                                     !! (same as in last call to [[db1ink]])
    real(wp),intent(in)                  :: xval     !! \(x\) 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 [[db1ink]])
    real(wp),dimension(nx),intent(in)    :: bcoef    !! the b-spline coefficients computed by [[db1ink]].
    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.
    real(wp),dimension(3_ip*kx),intent(inout) :: w0  !! work array
    logical,intent(in),optional          :: extrap   !! if extrapolation is allowed
                                                     !! (if not present, default is False)

    f = 0.0_wp

    iflag = check_value(xval,tx,1_ip,extrap); if (iflag/=0_ip) return

    call dbvalu(tx,bcoef,nx,kx,idx,xval,inbvx,w0,iflag,f,extrap)

    end subroutine db1val_default