hgeometry-0.12.0.4: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Data.Geometry.BezierSpline

Description

 
Synopsis

Documentation

newtype BezierSpline n d r Source #

Datatype representing a Bezier curve of degree \(n\) in \(d\)-dimensional space.

Constructors

BezierSpline (LSeq (1 + n) (Point d r)) 

Instances

Instances details
Arity d => Functor (BezierSpline n d) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

Methods

fmap :: (a -> b) -> BezierSpline n d a -> BezierSpline n d b #

(<$) :: a -> BezierSpline n d b -> BezierSpline n d a #

Arity d => Foldable (BezierSpline n d) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

Methods

fold :: Monoid m => BezierSpline n d m -> m #

foldMap :: Monoid m => (a -> m) -> BezierSpline n d a -> m #

foldMap' :: Monoid m => (a -> m) -> BezierSpline n d a -> m #

foldr :: (a -> b -> b) -> b -> BezierSpline n d a -> b #

foldr' :: (a -> b -> b) -> b -> BezierSpline n d a -> b #

foldl :: (b -> a -> b) -> b -> BezierSpline n d a -> b #

foldl' :: (b -> a -> b) -> b -> BezierSpline n d a -> b #

foldr1 :: (a -> a -> a) -> BezierSpline n d a -> a #

foldl1 :: (a -> a -> a) -> BezierSpline n d a -> a #

toList :: BezierSpline n d a -> [a] #

null :: BezierSpline n d a -> Bool #

length :: BezierSpline n d a -> Int #

elem :: Eq a => a -> BezierSpline n d a -> Bool #

maximum :: Ord a => BezierSpline n d a -> a #

minimum :: Ord a => BezierSpline n d a -> a #

sum :: Num a => BezierSpline n d a -> a #

product :: Num a => BezierSpline n d a -> a #

Arity d => Traversable (BezierSpline n d) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

Methods

traverse :: Applicative f => (a -> f b) -> BezierSpline n d a -> f (BezierSpline n d b) #

sequenceA :: Applicative f => BezierSpline n d (f a) -> f (BezierSpline n d a) #

mapM :: Monad m => (a -> m b) -> BezierSpline n d a -> m (BezierSpline n d b) #

sequence :: Monad m => BezierSpline n d (m a) -> m (BezierSpline n d a) #

PointFunctor (BezierSpline n d) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

Methods

pmap :: (Point (Dimension (BezierSpline n d r)) r -> Point (Dimension (BezierSpline n d s)) s) -> BezierSpline n d r -> BezierSpline n d s Source #

(Arity d, Eq r) => Eq (BezierSpline n d r) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

Methods

(==) :: BezierSpline n d r -> BezierSpline n d r -> Bool #

(/=) :: BezierSpline n d r -> BezierSpline n d r -> Bool #

(Arity d, Show r) => Show (BezierSpline n d r) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

Methods

showsPrec :: Int -> BezierSpline n d r -> ShowS #

show :: BezierSpline n d r -> String #

showList :: [BezierSpline n d r] -> ShowS #

(Arity n, Arity d, Arbitrary r) => Arbitrary (BezierSpline n d r) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

Methods

arbitrary :: Gen (BezierSpline n d r) #

shrink :: BezierSpline n d r -> [BezierSpline n d r] #

(Fractional r, Arity d, Arity (d + 1), Arity n) => IsTransformable (BezierSpline n d r) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

type NumType (BezierSpline n d r) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

type NumType (BezierSpline n d r) = r
type Dimension (BezierSpline n d r) Source # 
Instance details

Defined in Data.Geometry.BezierSpline

type Dimension (BezierSpline n d r) = d

controlPoints :: Iso (BezierSpline n1 d1 r1) (BezierSpline n2 d2 r2) (LSeq (1 + n1) (Point d1 r1)) (LSeq (1 + n2) (Point d2 r2)) Source #

Bezier control points. With n degrees, there are n+1 control points.

fromPointSeq :: Seq (Point d r) -> BezierSpline n d r Source #

Constructs the Bezier Spline from a given sequence of points.

evaluate :: (Arity d, Ord r, Num r) => BezierSpline n d r -> r -> Point d r Source #

Evaluate a BezierSpline curve at time t in [0, 1]

pre: \(t \in [0,1]\)

split :: forall n d r. (KnownNat n, Arity d, Ord r, Num r) => r -> BezierSpline n d r -> (BezierSpline n d r, BezierSpline n d r) Source #

Split a Bezier curve at time t in [0, 1] into two pieces.

subBezier :: (KnownNat n, Arity d, Ord r, Num r) => r -> r -> BezierSpline n d r -> BezierSpline n d r Source #

Restrict a Bezier curve to th,e piece between parameters t < u in [0, 1].

tangent :: (Arity d, Num r, 1 <= n) => BezierSpline n d r -> Vector d r Source #

Tangent to the bezier spline at the starting point.

approximate :: forall n d r. (KnownNat n, Arity d, Ord r, Fractional r) => r -> BezierSpline n d r -> [Point d r] Source #

Approximate Bezier curve by Polyline with given resolution.

parameterOf :: (Arity d, Ord r, Fractional r) => BezierSpline n d r -> Point d r -> r Source #

Given a point on (or close to) a Bezier curve, return the corresponding parameter value. (For points far away from the curve, the function will return the parameter value of an approximate locally closest point to the input point.)

snap :: (Arity d, Ord r, Fractional r) => BezierSpline n d r -> Point d r -> Point d r Source #

Snap a point close to a Bezier curve to the curve.

pattern Bezier2 :: Point d r -> Point d r -> Point d r -> BezierSpline 2 d r Source #

Quadratic Bezier Spline

pattern Bezier3 :: Point d r -> Point d r -> Point d r -> Point d r -> BezierSpline 3 d r Source #

Cubic Bezier Spline

colinear :: (Ord r, Fractional r) => r -> BezierSpline 3 2 r -> Bool Source #

Return True if the curve is definitely completely covered by a line of thickness twice the given tolerance. May return false negatives but not false positives.

lineApproximate :: (Ord r, Fractional r) => r -> BezierSpline 3 2 r -> [Point 2 r] Source #

Approximate curve as line segments where no point on the curve is further away from the nearest line segment than the given tolerance.

quadToCubic :: Fractional r => BezierSpline 2 2 r -> BezierSpline 3 2 r Source #

Convert a quadratic bezier to a cubic bezier.