splpak_type Derived Type

type, public :: splpak_type

Usage

The class contains four user entries: splcc, splcw, splfe, and splde.

The user first calls splcc by

    call me%initialize(ndim,xdata,l1xdat,ydata,ndata,
                       xmin,xmax,nodes,xtrap,coef,ncf,
                       work,nwrk,ierror)

or splcw by

    call me%initialize(ndim,xdata,l1xdata,ydata,wdata,
                       ndata,xmin,xmax,nodes,xtrap,
                       coef,ncf,work,nwrk,ierror)

The parameter NDATA in the call to splcw enables the user to weight some of the data points more heavily than others. Both routines return a set of coefficients in the array COEF. These coefficients are subsequently used in the computation of function values and partial derivatives. To compute values on the spline approximation the user then calls splfe or splde any number of times in any order provided that the values of the inputs, NDIM, COEF, XMIN, XMAX, and NODES, are preserved between calls.

splfe and splde are called in the following way:

    f = me%evaluate(ndim,x,coef,xmin,xmax,nodes,ierror)

or

    f = me%evaluate(ndim,x,nderiv,coef,xmin,xmax,nodes,ierror)

The routine splfe returns an interpolated value at the point defined by the array X. splde affords the user the additional capability of calculating an interpolated value for one of several partial derivatives specified by the array NDERIV.


Components

Type Visibility Attributes Name Initial
integer, private :: mdim = 0
real(kind=wp), private, dimension(:), allocatable :: dx
real(kind=wp), private, dimension(:), allocatable :: dxin
integer, private, dimension(:), allocatable :: ib
integer, private, dimension(:), allocatable :: ibmn
integer, private, dimension(:), allocatable :: ibmx
integer, private :: ilast = 0
integer, private :: isav = 0
integer, private :: iold = 0
integer, private :: np1 = 0
integer, private :: l = 0
integer, private :: il1 = 0
integer, private :: k = 0
integer, private :: k1 = 0
real(kind=wp), private :: errsum = 0.0_wp

Type-Bound Procedures

generic, public :: initialize => splcc, splcw

compute the spline coefficients

  • private subroutine splcc(me, ndim, xdata, l1xdat, ydata, ndata, xmin, xmax, nodes, xtrap, coef, ncf, work, nwrk, ierror)

    N-dimensional cubic spline coefficient calculation by least squares.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: ndim
    real(kind=wp), intent(in) :: xdata(l1xdat,ndata)
    integer, intent(in) :: l1xdat
    real(kind=wp), intent(in) :: ydata(ndata)
    integer, intent(in) :: ndata
    real(kind=wp), intent(in) :: xmin(ndim)
    real(kind=wp), intent(in) :: xmax(ndim)
    integer, intent(in) :: nodes(ndim)
    real(kind=wp), intent(in) :: xtrap
    real(kind=wp), intent(out) :: coef(ncf)
    integer, intent(in) :: ncf
    real(kind=wp) :: work(nwrk)
    integer, intent(in) :: nwrk
    integer, intent(out) :: ierror
  • private subroutine splcw(me, ndim, xdata, l1xdat, ydata, wdata, ndata, xmin, xmax, nodes, xtrap, coef, ncf, work, nwrk, ierror)

    N-dimensional cubic spline coefficient calculation by weighted least squares on arbitrarily located data.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: ndim

    The dimensionality of the problem. The spline is a function of NDIM variables or coordinates and thus a point in the independent variable space is an NDIM vector. NDIM must be >= 1.

    real(kind=wp), intent(in) :: xdata(l1xdat,ndata)

    A collection of locations for the data values, i.e., points from the independent variable space. This collection is a 2-dimensional array whose 1st dimension indexes the NDIM coordinates of a given point and whose 2nd dimension labels the data point. For example, the data point with label IDATA is located at the point (XDATA(1,IDATA),...,XDATA(NDIM,IDATA)) where the elements of this vector are the values of the NDIM coordinates. The location, number and ordering of the data points is arbitrary. The dimension of XDATA is assumed to be XDATA(L1XDAT,NDATA).

    integer, intent(in) :: l1xdat

    The length of the 1st dimension of XDATA in the calling program. L1XDAT must be >= NDIM.

    Read more…
    real(kind=wp), intent(in) :: ydata(ndata)

    A collection of data values corresponding to the points in XDATA. YDATA(IDATA) is the data value associated with the point (XDATA(1,IDATA),...,XDATA(NDIM,IDATA)) in the independent variable space. The spline whose coefficients are computed by this routine approximates these data values in the least squares sense. The dimension is assumed to be YDATA(NDATA).

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

    A collection of weights. WDATA(IDATA) is a weight associated with the data point labelled IDATA. It should be non-negative, but may be of any magnitude. The weights have the effect of forcing greater or lesser accuracy at a given point as follows: this routine chooses coefficients to minimize the sum over all data points of the quantity

    Read more…
    integer, intent(in) :: ndata

    The number of data points mentioned in the above arguments.

    real(kind=wp), intent(in) :: xmin(ndim)

    A vector describing the lower extreme corner of the node grid. A set of evenly spaced nodes is formed along each coordinate axis and XMIN(IDIM) is the location of the first node along the IDIM axis. The dimension is assumed to be XMIN(NDIM).

    real(kind=wp), intent(in) :: xmax(ndim)

    A vector describing the upper extreme corner of the node grid. A set of evenly spaced nodes is formed along each coordinate axis and XMAX(IDIM) is the location of the last node along the IDIM axis. The dimension is assumed to be XMAX(NDIM).

    integer, intent(in) :: nodes(ndim)

    A vector of integers describing the number of nodes along each axis. NODES(IDIM) is the number of nodes (counting endpoints) along the IDIM axis and determines the flexibility of the spline in that coordinate direction. NODES(IDIM) must be >= 4, but may be as large as the arrays COEF and WORK allow. The dimension is assumed to be NODES(NDIM).

    Read more…
    real(kind=wp), intent(in) :: xtrap

    A parameter to control extrapolation to data sparse areas. The region described by XMIN and XMAX is divided into rectangles, the number of which is determined by NODES, and any rectangle containing a disproportionately small number of data points is considered to be data sparse (rectangle is used here to mean NDIM-dimensional rectangle). If XTRAP is nonzero the least squares problem is augmented with derivative constraints in the data sparse areas to prevent the matrix from becoming poorly conditioned. XTRAP serves as a weight for these constraints, and thus may be used to control smoothness in data sparse areas. Experience indicates that unity is a good first guess for this parameter.

    Read more…
    real(kind=wp), intent(out) :: coef(ncf)

    The array of coefficients computed by this routine. Each coefficient corresponds to a particular basis function which in turn corresponds to a node in the node grid. This correspondence between the node grid and the array COEF is as if COEF were an NDIM-dimensional Fortran array with dimensions NODES(1),...,NODES(NDIM), i.e., to store the array linearly, the leftmost indices are incremented most frequently. Hence the length of the COEF array must equal or exceed the total number of nodes, which is NODES(1)*...*NODES(NDIM). The computed array COEF may be used with function SPLFE (or SPLDE) to evaluate the spline (or its derivatives) at an arbitrary point in NDIM space. The dimension is assumed to be COEF(NCF).

    integer, intent(in) :: ncf

    The length of the array COEF in the calling program. If NCF is < NODES(1)*...*NODES(NDIM), a fatal error is diagnosed.

    real(kind=wp) :: work(nwrk)

    A workspace array for solving the least squares matrix generated by this routine. Its required size is a function of the total number of nodes in the node grid. This total, NCOL = NODES(1)*...*NODES(NDIM), is also the number of columns in the least squares matrix. The length of the array WORK must equal or exceed NCOL*(NCOL+1).

    integer, intent(in) :: nwrk

    The length of the array WORK in the calling program. If NCOL = NODES(1)*...*NODES(NDIM) is the total number of nodes, then a fatal error is diagnosed if NWRK is less than NCOL*(NCOL+1).

    integer, intent(out) :: ierror

    An error flag with the following meanings:

    Read more…

generic, public :: evaluate => splfe, splde

evaluate the spline

  • private function splfe(me, ndim, x, coef, xmin, xmax, nodes, ierror)

    N-dimensional cubic spline function evaluation.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: ndim
    real(kind=wp), intent(in) :: x(ndim)
    real(kind=wp), intent(out) :: coef(*)
    real(kind=wp), intent(in) :: xmin(ndim)
    real(kind=wp), intent(in) :: xmax(ndim)
    integer, intent(in) :: nodes(ndim)
    integer, intent(out) :: ierror

    Return Value real(kind=wp)

  • private function splde(me, ndim, x, nderiv, coef, xmin, xmax, nodes, ierror)

    N-dimensional cubic spline derivative evaluation.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: ndim

    the dimensionality of the problem. the spline is a function of ndim variables or coordinates and thus a point in the independent variable space is an ndim vector. ndim must be in the range 1 <= ndim <= 4.

    real(kind=wp), intent(in) :: x(ndim)

    an ndim vector describing the point in the independent variable space at which the spline is to be evaluated.

    integer, intent(in) :: nderiv(ndim)

    an ndim vector of integers specifying the partial derivative to be evaluated. the order of the derivative along the idim axis is nderiv(idim). these integers must be in the range 0 <= nderiv(idim) <= 2.

    real(kind=wp), intent(out) :: coef(*)

    the array of coefficients which determine the spline. each coefficient corresponds to a particular basis function which in turn corresponds to a node in the node grid. this correspondence between the node grid and the array coef is as if coef were an ndim-dimensional fortran array with dimensions nodes(1),...,nodes(ndim), i.e., to store the array linearly, the leftmost indices are incremented most frequently. coef may be computed by using routines splcc or splcw.

    Read more…
    real(kind=wp), intent(in) :: xmin(ndim)

    a vector describing the lower extreme corner of the node grid. a set of evenly spaced nodes is formed along each coordinate axis and xmin(idim) is the location of the first node along the idim axis.

    real(kind=wp), intent(in) :: xmax(ndim)

    a vector describing the upper extreme corner of the node grid. a set of evenly spaced nodes is formed along each coordinate axis and xmax(idim) is the location of the last node along the idim axis.

    integer, intent(in) :: nodes(ndim)

    a vector of integers describing the number of nodes along each axis. nodes(idim) is the the number of nodes (counting endpoints) along the idim axis and determines the flexibility of the spline in that coordinate direction. nodes(idim) must be >= 4 but may be as large as the arrays coef and work allow.

    Read more…
    integer, intent(out) :: ierror

    an error flag with the following meanings:

    Read more…

    Return Value real(kind=wp)

    the function value returned is the partial derivative (indicated by nderiv) of the spline evaluated at x.

procedure, public :: destroy => destroy_splpak

destory the internal class variables

  • private subroutine destroy_splpak(me, ndim)

    Destroy the internal class variables.

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in), optional :: ndim

procedure, private :: splcc

  • private subroutine splcc(me, ndim, xdata, l1xdat, ydata, ndata, xmin, xmax, nodes, xtrap, coef, ncf, work, nwrk, ierror)

    N-dimensional cubic spline coefficient calculation by least squares.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: ndim
    real(kind=wp), intent(in) :: xdata(l1xdat,ndata)
    integer, intent(in) :: l1xdat
    real(kind=wp), intent(in) :: ydata(ndata)
    integer, intent(in) :: ndata
    real(kind=wp), intent(in) :: xmin(ndim)
    real(kind=wp), intent(in) :: xmax(ndim)
    integer, intent(in) :: nodes(ndim)
    real(kind=wp), intent(in) :: xtrap
    real(kind=wp), intent(out) :: coef(ncf)
    integer, intent(in) :: ncf
    real(kind=wp) :: work(nwrk)
    integer, intent(in) :: nwrk
    integer, intent(out) :: ierror

procedure, private :: splcw

  • private subroutine splcw(me, ndim, xdata, l1xdat, ydata, wdata, ndata, xmin, xmax, nodes, xtrap, coef, ncf, work, nwrk, ierror)

    N-dimensional cubic spline coefficient calculation by weighted least squares on arbitrarily located data.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: ndim

    The dimensionality of the problem. The spline is a function of NDIM variables or coordinates and thus a point in the independent variable space is an NDIM vector. NDIM must be >= 1.

    real(kind=wp), intent(in) :: xdata(l1xdat,ndata)

    A collection of locations for the data values, i.e., points from the independent variable space. This collection is a 2-dimensional array whose 1st dimension indexes the NDIM coordinates of a given point and whose 2nd dimension labels the data point. For example, the data point with label IDATA is located at the point (XDATA(1,IDATA),...,XDATA(NDIM,IDATA)) where the elements of this vector are the values of the NDIM coordinates. The location, number and ordering of the data points is arbitrary. The dimension of XDATA is assumed to be XDATA(L1XDAT,NDATA).

    integer, intent(in) :: l1xdat

    The length of the 1st dimension of XDATA in the calling program. L1XDAT must be >= NDIM.

    Read more…
    real(kind=wp), intent(in) :: ydata(ndata)

    A collection of data values corresponding to the points in XDATA. YDATA(IDATA) is the data value associated with the point (XDATA(1,IDATA),...,XDATA(NDIM,IDATA)) in the independent variable space. The spline whose coefficients are computed by this routine approximates these data values in the least squares sense. The dimension is assumed to be YDATA(NDATA).

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

    A collection of weights. WDATA(IDATA) is a weight associated with the data point labelled IDATA. It should be non-negative, but may be of any magnitude. The weights have the effect of forcing greater or lesser accuracy at a given point as follows: this routine chooses coefficients to minimize the sum over all data points of the quantity

    Read more…
    integer, intent(in) :: ndata

    The number of data points mentioned in the above arguments.

    real(kind=wp), intent(in) :: xmin(ndim)

    A vector describing the lower extreme corner of the node grid. A set of evenly spaced nodes is formed along each coordinate axis and XMIN(IDIM) is the location of the first node along the IDIM axis. The dimension is assumed to be XMIN(NDIM).

    real(kind=wp), intent(in) :: xmax(ndim)

    A vector describing the upper extreme corner of the node grid. A set of evenly spaced nodes is formed along each coordinate axis and XMAX(IDIM) is the location of the last node along the IDIM axis. The dimension is assumed to be XMAX(NDIM).

    integer, intent(in) :: nodes(ndim)

    A vector of integers describing the number of nodes along each axis. NODES(IDIM) is the number of nodes (counting endpoints) along the IDIM axis and determines the flexibility of the spline in that coordinate direction. NODES(IDIM) must be >= 4, but may be as large as the arrays COEF and WORK allow. The dimension is assumed to be NODES(NDIM).

    Read more…
    real(kind=wp), intent(in) :: xtrap

    A parameter to control extrapolation to data sparse areas. The region described by XMIN and XMAX is divided into rectangles, the number of which is determined by NODES, and any rectangle containing a disproportionately small number of data points is considered to be data sparse (rectangle is used here to mean NDIM-dimensional rectangle). If XTRAP is nonzero the least squares problem is augmented with derivative constraints in the data sparse areas to prevent the matrix from becoming poorly conditioned. XTRAP serves as a weight for these constraints, and thus may be used to control smoothness in data sparse areas. Experience indicates that unity is a good first guess for this parameter.

    Read more…
    real(kind=wp), intent(out) :: coef(ncf)

    The array of coefficients computed by this routine. Each coefficient corresponds to a particular basis function which in turn corresponds to a node in the node grid. This correspondence between the node grid and the array COEF is as if COEF were an NDIM-dimensional Fortran array with dimensions NODES(1),...,NODES(NDIM), i.e., to store the array linearly, the leftmost indices are incremented most frequently. Hence the length of the COEF array must equal or exceed the total number of nodes, which is NODES(1)*...*NODES(NDIM). The computed array COEF may be used with function SPLFE (or SPLDE) to evaluate the spline (or its derivatives) at an arbitrary point in NDIM space. The dimension is assumed to be COEF(NCF).

    integer, intent(in) :: ncf

    The length of the array COEF in the calling program. If NCF is < NODES(1)*...*NODES(NDIM), a fatal error is diagnosed.

    real(kind=wp) :: work(nwrk)

    A workspace array for solving the least squares matrix generated by this routine. Its required size is a function of the total number of nodes in the node grid. This total, NCOL = NODES(1)*...*NODES(NDIM), is also the number of columns in the least squares matrix. The length of the array WORK must equal or exceed NCOL*(NCOL+1).

    integer, intent(in) :: nwrk

    The length of the array WORK in the calling program. If NCOL = NODES(1)*...*NODES(NDIM) is the total number of nodes, then a fatal error is diagnosed if NWRK is less than NCOL*(NCOL+1).

    integer, intent(out) :: ierror

    An error flag with the following meanings:

    Read more…

procedure, private :: splfe

  • private function splfe(me, ndim, x, coef, xmin, xmax, nodes, ierror)

    N-dimensional cubic spline function evaluation.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: ndim
    real(kind=wp), intent(in) :: x(ndim)
    real(kind=wp), intent(out) :: coef(*)
    real(kind=wp), intent(in) :: xmin(ndim)
    real(kind=wp), intent(in) :: xmax(ndim)
    integer, intent(in) :: nodes(ndim)
    integer, intent(out) :: ierror

    Return Value real(kind=wp)

procedure, private :: splde

  • private function splde(me, ndim, x, nderiv, coef, xmin, xmax, nodes, ierror)

    N-dimensional cubic spline derivative evaluation.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: ndim

    the dimensionality of the problem. the spline is a function of ndim variables or coordinates and thus a point in the independent variable space is an ndim vector. ndim must be in the range 1 <= ndim <= 4.

    real(kind=wp), intent(in) :: x(ndim)

    an ndim vector describing the point in the independent variable space at which the spline is to be evaluated.

    integer, intent(in) :: nderiv(ndim)

    an ndim vector of integers specifying the partial derivative to be evaluated. the order of the derivative along the idim axis is nderiv(idim). these integers must be in the range 0 <= nderiv(idim) <= 2.

    real(kind=wp), intent(out) :: coef(*)

    the array of coefficients which determine the spline. each coefficient corresponds to a particular basis function which in turn corresponds to a node in the node grid. this correspondence between the node grid and the array coef is as if coef were an ndim-dimensional fortran array with dimensions nodes(1),...,nodes(ndim), i.e., to store the array linearly, the leftmost indices are incremented most frequently. coef may be computed by using routines splcc or splcw.

    Read more…
    real(kind=wp), intent(in) :: xmin(ndim)

    a vector describing the lower extreme corner of the node grid. a set of evenly spaced nodes is formed along each coordinate axis and xmin(idim) is the location of the first node along the idim axis.

    real(kind=wp), intent(in) :: xmax(ndim)

    a vector describing the upper extreme corner of the node grid. a set of evenly spaced nodes is formed along each coordinate axis and xmax(idim) is the location of the last node along the idim axis.

    integer, intent(in) :: nodes(ndim)

    a vector of integers describing the number of nodes along each axis. nodes(idim) is the the number of nodes (counting endpoints) along the idim axis and determines the flexibility of the spline in that coordinate direction. nodes(idim) must be >= 4 but may be as large as the arrays coef and work allow.

    Read more…
    integer, intent(out) :: ierror

    an error flag with the following meanings:

    Read more…

    Return Value real(kind=wp)

    the function value returned is the partial derivative (indicated by nderiv) of the spline evaluated at x.

procedure, private :: bascmp

  • private subroutine bascmp(me, x, nderiv, xmin, nodes, icol, basm)

    This routine does basis function computations for natural splines. This routine is called by routines SPLCW and SPLDE to compute ICOL and BASM, which are defined as follows:

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    real(kind=wp), intent(in) :: x(:)
    integer, intent(in) :: nderiv(:)
    real(kind=wp), intent(in) :: xmin(:)
    integer, intent(in) :: nodes(:)
    integer, intent(out) :: icol
    real(kind=wp), intent(out) :: basm

procedure, private :: suprls

  • private subroutine suprls(me, i, rowi, n, bi, a, nn, soln, err, ier)

    To determine the least squares solution of a large overdetermined linear system.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(splpak_type), intent(inout) :: me
    integer, intent(in) :: i

    the index of the row being entered. (i is 1 for the first call, increases by 1 for each call, and is m when the final row is entered). After the final row has been entered, suprls is called with i = 0 to complete the reduction and solution.

    real(kind=wp), intent(in) :: rowi(n)

    a vector which on the ith call contains the n components of the ith row of the matrix. the dimension of rowi in calling program must be at least n.

    integer, intent(in) :: n

    the length of the rows of the matrix (i.e., the number of columns). n <= m, where m is the number of rows.

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

    on the ith call, bi contains the ith element of the right hand side vector b.

    real(kind=wp), intent(inout) :: a(nn)

    a working array which must not be changed between the successive calls to suprls.

    integer, intent(in) :: nn

    length of scratch array a. nn must be at least n*(n+5)/2+1. For speed, nn should be as large as possible up to a maximum of (n+1)*m.

    real(kind=wp), intent(out) :: soln(n)

    the n-components of the solution vector are returned in this array after the final call to suprls.

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

    the euclidean norm of the residual is returned in err after the final call to suprls.

    integer, intent(out) :: ier

    error parameter. fatal errors:

    Read more…

Source Code

    type,public :: splpak_type

        !!### Usage
        !!
        !!  The class contains four user entries:
        !!  [[splcc]], [[splcw]], [[splfe]], and [[splde]].
        !!
        !!  The user first calls [[splcc]] by
        !!```fortran
        !!    call me%initialize(ndim,xdata,l1xdat,ydata,ndata,
        !!                       xmin,xmax,nodes,xtrap,coef,ncf,
        !!                       work,nwrk,ierror)
        !!```
        !!  or [[splcw]] by
        !!```fortran
        !!    call me%initialize(ndim,xdata,l1xdata,ydata,wdata,
        !!                       ndata,xmin,xmax,nodes,xtrap,
        !!                       coef,ncf,work,nwrk,ierror)
        !!```
        !!  The parameter `NDATA` in the call to [[splcw]]
        !!  enables the user to weight some of the data
        !!  points more heavily than others.  Both
        !!  routines return a set of coefficients in the
        !!  array `COEF`.  These coefficients are
        !!  subsequently used in the computation of
        !!  function values and partial derivatives.
        !!  To compute values on the spline approximation
        !!  the user then calls [[splfe]] or [[splde]] any
        !!  number of times in any order provided that
        !!  the values of the inputs, `NDIM`, `COEF`, `XMIN`,
        !!  `XMAX`, and `NODES`, are preserved between calls.
        !!
        !!  [[splfe]] and [[splde]] are called in the following way:
        !!```fortran
        !!    f = me%evaluate(ndim,x,coef,xmin,xmax,nodes,ierror)
        !!```
        !!  or
        !!```fortran
        !!    f = me%evaluate(ndim,x,nderiv,coef,xmin,xmax,nodes,ierror)
        !!```
        !!  The routine [[splfe]] returns an interpolated
        !!  value at the point defined by the array `X`.
        !!  [[splde]] affords the user the additional
        !!  capability of calculating an interpolated
        !!  value for one of several partial derivatives
        !!  specified by the array `NDERIV`.

        private

        ! formerly in splcomd common block:
        integer :: mdim = 0
        real(wp),dimension(:),allocatable :: dx ! originally these were all size 4
        real(wp),dimension(:),allocatable :: dxin
        integer,dimension(:),allocatable  :: ib
        integer,dimension(:),allocatable  :: ibmn
        integer,dimension(:),allocatable  :: ibmx

        ! formerly saved variables in suprls
        integer :: ilast = 0
        integer :: isav  = 0
        integer :: iold  = 0
        integer :: np1   = 0
        integer :: l     = 0
        integer :: il1   = 0
        integer :: k     = 0
        integer :: k1    = 0
        real(wp) :: errsum = 0.0_wp

        contains

        private

        generic,public   :: initialize => splcc, splcw !! compute the spline coefficients
        generic,public   :: evaluate   => splfe, splde !! evaluate the spline
        procedure,public :: destroy    => destroy_splpak !! destory the internal class variables
        procedure,private :: splcc
        procedure,private :: splcw
        procedure,private :: splfe
        procedure,private :: splde
        procedure,private :: bascmp
        procedure,private :: suprls

    end type splpak_type