initialize_2d_specify_knots Subroutine

private pure subroutine initialize_2d_specify_knots(me, x, y, fcn, kx, ky, tx, ty, iflag, extrap)

Initialize a bspline_2d type (with user-specified knots). This is a wrapper for db2ink.

Type Bound

bspline_2d

Arguments

Type IntentOptional Attributes Name
class(bspline_2d), intent(inout) :: me
real(kind=wp), intent(in), dimension(:) :: x

(nx) array of abcissae. Must be strictly increasing.

real(kind=wp), intent(in), dimension(:) :: y

(ny) array of abcissae. Must be strictly increasing.

real(kind=wp), intent(in), dimension(:,:) :: fcn

(nx,ny) matrix of function values to interpolate. fcn(i,j) should contain the function value at the point (x(i),y(j))

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

The order of spline pieces in ( ) (order = polynomial degree + 1)

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

The order of spline pieces in ( ) (order = polynomial degree + 1)

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

The (nx+kx) knots in the direction for the spline interpolant. Must be non-decreasing.

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

The (ny+ky) knots in the direction for the spline interpolant. Must be non-decreasing.

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

status flag (see db2ink)

logical, intent(in), optional :: extrap

if true, then extrapolation is allowed (default is false)


Calls

proc~~initialize_2d_specify_knots~~CallsGraph proc~initialize_2d_specify_knots bspline_oo_module::bspline_2d%initialize_2d_specify_knots proc~check_knot_vectors_sizes bspline_oo_module::check_knot_vectors_sizes proc~initialize_2d_specify_knots->proc~check_knot_vectors_sizes proc~db2ink bspline_sub_module::db2ink proc~initialize_2d_specify_knots->proc~db2ink proc~destroy_2d bspline_oo_module::bspline_2d%destroy_2d proc~initialize_2d_specify_knots->proc~destroy_2d proc~set_extrap_flag bspline_oo_module::bspline_class%set_extrap_flag proc~initialize_2d_specify_knots->proc~set_extrap_flag proc~check_inputs bspline_sub_module::check_inputs proc~db2ink->proc~check_inputs proc~dbknot bspline_sub_module::dbknot proc~db2ink->proc~dbknot proc~dbtpcf bspline_sub_module::dbtpcf proc~db2ink->proc~dbtpcf proc~destroy_base bspline_oo_module::bspline_class%destroy_base proc~destroy_2d->proc~destroy_base proc~dbintk bspline_sub_module::dbintk proc~dbtpcf->proc~dbintk proc~dbnslv bspline_sub_module::dbnslv proc~dbtpcf->proc~dbnslv proc~dbintk->proc~dbnslv proc~dbnfac bspline_sub_module::dbnfac proc~dbintk->proc~dbnfac proc~dbspvn bspline_sub_module::dbspvn proc~dbintk->proc~dbspvn

Called by

proc~~initialize_2d_specify_knots~~CalledByGraph proc~initialize_2d_specify_knots bspline_oo_module::bspline_2d%initialize_2d_specify_knots proc~bspline_2d_constructor_specify_knots bspline_oo_module::bspline_2d_constructor_specify_knots proc~bspline_2d_constructor_specify_knots->proc~initialize_2d_specify_knots interface~bspline_2d bspline_oo_module::bspline_2d interface~bspline_2d->proc~bspline_2d_constructor_specify_knots

Source Code

    pure subroutine initialize_2d_specify_knots(me,x,y,fcn,kx,ky,tx,ty,iflag,extrap)

    implicit none

    class(bspline_2d),intent(inout)    :: me
    real(wp),dimension(:),intent(in)   :: x     !! `(nx)` array of \(x\) abcissae. Must be strictly increasing.
    real(wp),dimension(:),intent(in)   :: y     !! `(ny)` array of \(y\) abcissae. Must be strictly increasing.
    real(wp),dimension(:,:),intent(in) :: fcn   !! `(nx,ny)` matrix of function values to interpolate.
                                                !! `fcn(i,j)` should contain the function value at the
                                                !! point (`x(i)`,`y(j)`)
    integer(ip),intent(in)             :: kx    !! The order of spline pieces in \(x\)
                                                !! ( \( 2 \le k_x < n_x \) )
                                                !! (order = polynomial degree + 1)
    integer(ip),intent(in)             :: ky    !! The order of spline pieces in \(y\)
                                                !! ( \( 2 \le k_y < n_y \) )
                                                !! (order = polynomial degree + 1)
    real(wp),dimension(:),intent(in)   :: tx    !! The `(nx+kx)` knots in the \(x\) direction
                                                !! for the spline interpolant.
                                                !! Must be non-decreasing.
    real(wp),dimension(:),intent(in)   :: ty    !! The `(ny+ky)` knots in the \(y\) direction
                                                !! for the spline interpolant.
                                                !! Must be non-decreasing.
    integer(ip),intent(out)            :: iflag !! status flag (see [[db2ink]])
    logical,intent(in),optional      :: extrap  !! if true, then extrapolation is allowed
                                                !! (default is false)

    integer(ip) :: nx,ny

    call me%destroy()

    nx = size(x,kind=ip)
    ny = size(y,kind=ip)

    call check_knot_vectors_sizes(nx=nx,kx=kx,tx=tx,&
                                  ny=ny,ky=ky,ty=ty,&
                                  iflag=iflag)

    if (iflag == 0_ip) then

        me%nx = nx
        me%ny = ny

        me%kx = kx
        me%ky = ky

        allocate(me%tx(nx+kx))
        allocate(me%ty(ny+ky))
        allocate(me%bcoef(nx,ny))
        allocate(me%work_val_1(ky))
        allocate(me%work_val_2(3_ip*max(kx,ky)))

        me%tx = tx
        me%ty = ty

        call db2ink(x,nx,y,ny,fcn,kx,ky,1_ip,me%tx,me%ty,me%bcoef,iflag)

        call me%set_extrap_flag(extrap)

    end if

    me%initialized = iflag==0_ip
    me%iflag = iflag

    end subroutine initialize_2d_specify_knots