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

Safe HaskellNone

Math.Spline.Knots

Synopsis

Documentation

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) 

empty :: Knots aSource

An empty knot vector

knot :: Ord a => a -> Knots aSource

Create a knot vector consisting of one knot.

multipleKnot :: Ord a => a -> Int -> Knots aSource

Create a knot vector consisting of one knot with the specified multiplicity.

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

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

fromList :: Ord k => [(k, Int)] -> Knots kSource

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

numKnots :: Knots t -> IntSource

Returns the number of knots (not necessarily distinct) in a knot vector.

toList :: Eq k => Knots k -> [(k, Int)]Source

Returns a list of all distinct knots in ascending order along with their multiplicities.

numDistinctKnots :: Eq t => Knots t -> IntSource

Returns the number of distinct knots in a knot vector.

knots :: Knots t -> [t]Source

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

knotsVector :: Knots t -> Vector tSource

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

distinctKnots :: Eq t => Knots t -> [t]Source

Returns a list of all distinct knots of a knot vector in ascending order

distinctKnotsVector :: Eq t => Knots t -> Vector tSource

Returns a vector of all distinct knots of a knot vector in ascending order

distinctKnotsSet :: Eq k => Knots k -> Set kSource

Returns a Set of all distinct knots of a knot vector

toMap :: Ord k => Knots k -> Map k IntSource

fromMap :: Eq k => Map k Int -> Knots kSource

toVector :: Eq k => Knots k -> Vector (k, Int)Source

fromVector :: Ord k => Vector (k, Int) -> Knots kSource

splitLookup :: Int -> Knots a -> (Knots a, Maybe a, Knots a)Source

splitLookup n kts: Split a knot vector kts into 3 parts (pre, mbKt, post) such that:

  • All the keys in pre, mbKt (viewed as a knot vector of either 0 or 1 knot), and post are disjoint and ordered * Putting the 3 parts back together yields exactly the original knot vector * The n'th knot, if one exists, will be in mbKt along with its multiplicity

splitDistinctKnotsAt :: (Ord a, Eq a) => Int -> Knots a -> (Knots a, Knots a)Source

knotMultiplicity :: Ord k => k -> Knots k -> IntSource

Looks up the multiplicity of a knot (which is 0 if the point is not a knot)

setKnotMultiplicity :: Ord k => k -> Int -> Knots k -> Knots kSource

Returns a new knot vector with the given knot set to the specified multiplicity and all other knots unchanged.

splitFind :: Ord k => k -> Knots k -> (Knots k, Knots k, Knots k)Source

fromAscList :: Eq k => [(k, Int)] -> Knots kSource

Create a knot vector consisting of all the knots and corresponding multiplicities in a list ordered by the knots' Ord instance. The ordering precondition is not checked.

fromDistinctAscList :: Eq k => [(k, Int)] -> Knots kSource

Create a knot vector consisting of all the knots and corresponding multiplicities in a list ordered by the knots' Ord instance with no duplicates. The preconditions are not checked.

valid :: (Ord k, Num k) => Knots k -> BoolSource

Check the internal consistency of a knot vector

knotSpan :: Knots a -> Int -> Int -> Maybe (a, a)Source

knotSpan kts i j returns the knot span extending from the i'th knot to the j'th knot, if i <= j and both knots exist.

knotsInSpan :: Knots a -> Int -> Int -> Knots aSource

knotsInSpan kts i j returns the knots in the knot span extending from the i'th knot to the j'th knot

knotSpans :: Knots a -> Int -> [(a, a)]Source

knotSpans kts width returns all knot spans of a given width in ascending order.

For example, knotSpans (mkKnots [1..5]) 2 yields [(1,3), (2,4), (3,5)].

knotDomain :: Knots a -> Int -> Maybe (a, a)Source

knotDomain kts p returns the domain of a B-spline or NURBS with knot vector kts and degree p. This is the subrange spanned by all except the first and last p knots. Outside this domain, the spline does not have a complete basis set. De Boor's algorithm assumes that the basis functions sum to 1, which is only true on this range, and so this is also precisely the domain on which de Boor's algorithm is valid.

uniform :: (Ord s, Fractional s) => Int -> Int -> (s, s) -> Knots sSource

uniform deg nPts (lo,hi) constructs a uniformly-spaced knot vector over the interval from lo to hi which, when used to construct a B-spline with nPts control points will yield a clamped spline with degree deg.

minKnot :: Eq a => Knots a -> Maybe (a, Int)Source

maxKnot :: Eq a => Knots a -> Maybe (a, Int)Source