bspline_1d Derived Type

type, public, extends(bspline_class) :: bspline_1d

Class for 1d b-spline interpolation.

Note

The 1D class also contains two methods for computing definite integrals.


Inherits

type~~bspline_1d~~InheritsGraph type~bspline_1d bspline_1d type~bspline_class bspline_class type~bspline_1d->type~bspline_class

Components

Type Visibility Attributes Name Initial
integer(kind=ip), private :: nx = 0_ip

Number of abcissae

integer(kind=ip), private :: kx = 0_ip

The order of spline pieces in

real(kind=wp), private, dimension(:), allocatable :: bcoef

array of coefficients of the b-spline interpolant

real(kind=wp), private, dimension(:), allocatable :: tx

The knots in the direction for the spline interpolant

real(kind=wp), private, dimension(:), allocatable :: work_val_1

[[db1val] work array of dimension 3*kx


Constructor

public interface bspline_1d

Constructor for bspline_1d

  • private pure elemental function bspline_1d_constructor_empty() result(me)

    It returns an empty bspline_1d type. Note that INITIALIZE still needs to be called before it can be used. Not really that useful except perhaps in some OpenMP applications.

    Arguments

    None

    Return Value type(bspline_1d)

  • private pure function bspline_1d_constructor_auto_knots(x, fcn, kx, extrap) result(me)

    Constructor for a bspline_1d type (auto knots). This is a wrapper for initialize_1d_auto_knots.

    Arguments

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

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

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

    (nx) array of function values to interpolate. fcn(i) should contain the function value at the point x(i)

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

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

    logical, intent(in), optional :: extrap

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

    Return Value type(bspline_1d)

  • private pure function bspline_1d_constructor_specify_knots(x, fcn, kx, tx, extrap) result(me)

    Constructor for a bspline_1d type (user-specified knots). This is a wrapper for initialize_1d_specify_knots.

    Arguments

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

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

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

    (nx) array of function values to interpolate. fcn(i) should contain the function value at the point x(i)

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

    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.

    logical, intent(in), optional :: extrap

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

    Return Value type(bspline_1d)


Finalization Procedures

final :: finalize_1d


Type-Bound Procedures

procedure, public, non_overridable :: status_ok

returns true if the last iflag status code was =0.

  • private elemental function status_ok(me) result(ok)

    This routines returns true if the iflag code from the last routine called was =0. Maybe of the routines have output iflag variables, so they can be checked explicitly, or this routine can be used.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(bspline_class), intent(in) :: me

    Return Value logical

procedure, public, non_overridable :: status_message => get_bspline_status_message

retrieve the last status message

  • private pure function get_bspline_status_message(me, iflag) result(msg)

    Get the status message from a bspline_class routine call.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(bspline_class), intent(in) :: me
    integer(kind=ip), intent(in), optional :: iflag

    the corresponding status code

    Return Value character(len=:), allocatable

    status message associated with the flag

procedure, public, non_overridable :: clear_flag => clear_bspline_flag

to reset the iflag saved in the class.

  • private elemental subroutine clear_bspline_flag(me)

    This sets the iflag variable in the class to 0 (which indicates that everything is OK). It can be used after an error is encountered.

    Arguments

    Type IntentOptional Attributes Name
    class(bspline_class), intent(inout) :: me

generic, public :: initialize => initialize_1d_auto_knots, initialize_1d_specify_knots

  • private pure subroutine initialize_1d_auto_knots(me, x, fcn, kx, iflag, extrap)

    Initialize a bspline_1d type (with automatically-computed knots). This is a wrapper for db1ink.

    Arguments

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

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

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

    (nx) array of function values to interpolate. fcn(i) should contain the function value at the point x(i)

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

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

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

    status flag (see db1ink)

    logical, intent(in), optional :: extrap

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

  • private pure subroutine initialize_1d_specify_knots(me, x, fcn, kx, tx, iflag, extrap)

    Initialize a bspline_1d type (with user-specified knots). This is a wrapper for db1ink.

    Arguments

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

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

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

    (nx) array of function values to interpolate. fcn(i) should contain the function value at the point x(i)

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

    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.

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

    status flag (see db1ink)

    logical, intent(in), optional :: extrap

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

procedure, private :: initialize_1d_auto_knots

  • private pure subroutine initialize_1d_auto_knots(me, x, fcn, kx, iflag, extrap)

    Initialize a bspline_1d type (with automatically-computed knots). This is a wrapper for db1ink.

    Arguments

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

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

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

    (nx) array of function values to interpolate. fcn(i) should contain the function value at the point x(i)

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

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

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

    status flag (see db1ink)

    logical, intent(in), optional :: extrap

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

procedure, private :: initialize_1d_specify_knots

  • private pure subroutine initialize_1d_specify_knots(me, x, fcn, kx, tx, iflag, extrap)

    Initialize a bspline_1d type (with user-specified knots). This is a wrapper for db1ink.

    Arguments

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

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

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

    (nx) array of function values to interpolate. fcn(i) should contain the function value at the point x(i)

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

    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.

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

    status flag (see db1ink)

    logical, intent(in), optional :: extrap

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

procedure, public :: evaluate => evaluate_1d

  • private pure subroutine evaluate_1d(me, xval, idx, f, iflag)

    Evaluate a bspline_1d interpolate. This is a wrapper for db1val.

    Arguments

    Type IntentOptional Attributes Name
    class(bspline_1d), intent(inout) :: me
    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(out) :: f

    interpolated value

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

    status flag (see db1val)

procedure, public :: destroy => destroy_1d

  • private pure subroutine destroy_1d(me)

    Destructor for bspline_1d class.

    Arguments

    Type IntentOptional Attributes Name
    class(bspline_1d), intent(inout) :: me

procedure, public :: size_of => size_1d

  • private pure function size_1d(me) result(s)

    Actual size of a bspline_1d structure in bits.

    Arguments

    Type IntentOptional Attributes Name
    class(bspline_1d), intent(in) :: me

    Return Value integer(kind=ip)

    size of the structure in bits

procedure, public :: integral => integral_1d

  • private pure subroutine integral_1d(me, x1, x2, f, iflag)

    Evaluate a bspline_1d definite integral. This is a wrapper for db1sqad.

    Arguments

    Type IntentOptional Attributes Name
    class(bspline_1d), intent(inout) :: me
    real(kind=wp), intent(in) :: x1

    left point of interval

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

    right point of interval

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

    integral of the b-spline over

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

    status flag (see db1sqad)

procedure, public :: fintegral => fintegral_1d

  • private subroutine fintegral_1d(me, fun, idx, x1, x2, tol, f, iflag)

    Evaluate a bspline_1d definite integral. This is a wrapper for db1fqad.

    Arguments

    Type IntentOptional Attributes Name
    class(bspline_1d), intent(inout) :: me
    procedure(b1fqad_func) :: fun

    external function of one argument for the integrand bf(x)=fun(x)*dbvalu(tx,bcoef,nx,kx,idx,x,inbv)

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

    order of the spline derivative, 0 <= idx <= k-1 idx=0 gives the spline function

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

    left point of interval

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

    right point of interval

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

    desired accuracy for the quadrature

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

    integral of bf(x) over

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

    status flag (see db1sqad)

Source Code

    type,extends(bspline_class),public :: bspline_1d
        !! Class for 1d b-spline interpolation.
        !!
        !!@note The 1D class also contains two methods
        !!      for computing definite integrals.
        private
        integer(ip) :: nx = 0_ip  !! Number of \(x\) abcissae
        integer(ip) :: kx = 0_ip  !! The order of spline pieces in \(x\)
        real(wp),dimension(:),allocatable :: bcoef  !! array of coefficients of the b-spline interpolant
        real(wp),dimension(:),allocatable :: tx  !! The knots in the \(x\) direction for the spline interpolant
        real(wp),dimension(:),allocatable :: work_val_1   !! [[db1val] work array of dimension `3*kx`
        contains
        private
        generic,public :: initialize => initialize_1d_auto_knots,initialize_1d_specify_knots
        procedure :: initialize_1d_auto_knots
        procedure :: initialize_1d_specify_knots
        procedure,public :: evaluate => evaluate_1d
        procedure,public :: destroy => destroy_1d
        procedure,public :: size_of => size_1d
        procedure,public :: integral => integral_1d
        procedure,public :: fintegral => fintegral_1d
        final :: finalize_1d
    end type bspline_1d