splines-0.5.0.1: B-Splines, other splines, and NURBS.

Safe HaskellNone

Math.Spline

Synopsis

Documentation

class (VectorSpace v, Fractional (Scalar v), Ord (Scalar v)) => Spline s v whereSource

A spline is a piecewise polynomial vector-valued function. The necessary and sufficient instance definition is toBSpline.

Methods

splineDomain :: s v -> Maybe (Scalar v, Scalar v)Source

Returns the domain of a spline. In the case of B-splines, this is the domain on which a spline with this degree and knot vector has a full basis set. In other cases, it should be no larger than splineDomain . toBSpline, but may be smaller. Within this domain, evalSpline should agree with evalSpline . toBSpline (not necessarily exactly, but up to reasonable expectations of numerical accuracy).

evalSpline :: s v -> Scalar v -> vSource

splineDegree :: s v -> IntSource

knotVector :: s v -> Knots (Scalar v)Source

toBSpline :: s v -> BSpline Vector vSource

data Knots a Source

Knot vectors - multisets of points in a 1-dimensional space.

Instances

Foldable Knots 
Eq a => Eq (Knots a) 
Ord a => Ord (Knots a) 
Show a => Show (Knots a) 
Ord a => Monoid (Knots a) 

mkKnots :: Ord a => [a] -> Knots aSource

Create a knot vector consisting of all the knots in a list.

knots :: Knots t -> [t]Source

Returns a list of all knots (not necessarily distinct) of a knot vector in ascending order

data BezierCurve t Source

A Bezier curve on 0 <= x <= 1.

bezierCurve :: Vector t -> BezierCurve tSource

Construct a Bezier curve from a list of control points. The degree of the curve is one less than the number of control points.

data BSpline v t Source

A B-spline, defined by a knot vector (see Knots) and a sequence of control points.

Instances

(Spline (BSpline v) a, Vector v a) => ControlPoints (BSpline v) a 
Spline (BSpline Vector) a => ControlPoints (BSpline Vector) a 
(VectorSpace a, Fractional (Scalar a), Ord (Scalar a), Vector v a, Vector v (Scalar a)) => Spline (BSpline v) a 
(VectorSpace v, Fractional (Scalar v), Ord (Scalar v)) => Spline (BSpline Vector) v 
(Eq (Scalar a), Eq (v a)) => Eq (BSpline v a) 
(Ord (Scalar a), Ord (v a)) => Ord (BSpline v a) 
(Show (Scalar a), Show a, Show (v a)) => Show (BSpline v a) 

bSpline :: Vector v a => Knots (Scalar a) -> v a -> BSpline v aSource

bSpline kts cps creates a B-spline with the given knot vector and control points. The degree is automatically inferred as the difference between the number of spans in the knot vector (numKnots kts - 1) and the number of control points (length cps).

data MSpline v Source

M-Splines are B-splines normalized so that the integral of each basis function over the spline domain is 1.

Instances

Spline MSpline v => ControlPoints MSpline v 
(VectorSpace v, Fractional (Scalar v), Ord (Scalar v)) => Spline MSpline v 
(Eq (Scalar v), Eq v) => Eq (MSpline v) 
(Ord (Scalar v), Ord v) => Ord (MSpline v) 
(Show (Scalar v), Show v) => Show (MSpline v) 

mSpline :: Knots (Scalar a) -> Vector a -> MSpline aSource

mSpline kts cps creates a M-spline with the given knot vector and control points. The degree is automatically inferred as the difference between the number of spans in the knot vector (numKnots kts - 1) and the number of control points (length cps).

toMSpline :: Spline s v => s v -> MSpline vSource

data ISpline v Source

The I-Spline basis functions are the integrals of the M-splines, or alternatively the integrals of the B-splines normalized to the range [0,1]. Every I-spline basis function increases monotonically from 0 to 1, thus it is useful as a basis for monotone functions. An I-Spline curve is monotone if and only if every non-zero control point has the same sign.

Instances

Spline ISpline v => ControlPoints ISpline v 
(VectorSpace v, Fractional (Scalar v), Ord (Scalar v)) => Spline ISpline v 
(Eq (Scalar v), Eq v) => Eq (ISpline v) 
(Ord (Scalar v), Ord v) => Ord (ISpline v) 
(Show (Scalar v), Show v) => Show (ISpline v) 

iSpline :: Knots (Scalar a) -> Vector a -> ISpline aSource

iSpline kts cps creates an I-spline with the given knot vector and control points. The degree is automatically inferred as the difference between the number of spans in the knot vector (numKnots kts - 1) and the number of control points (length cps).

toISpline :: (Spline s v, Eq v) => s v -> ISpline vSource

data CSpline a Source

Cubic Hermite splines. These are cubic splines defined by a sequence of control points and derivatives at those points.

Instances

cSpline :: Ord (Scalar a) => [(Scalar a, a, a)] -> CSpline aSource

Cubic splines specified by a list of control points, where each control point is given by a triple of parameter value, position of the spline at that parameter value, and derivative of the spline at that parameter value.