hgeometry-0.13: 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)) 

Bundled Patterns

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

Quadratic Bezier Spline

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

Cubic Bezier Spline

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.

endPoints :: BezierSpline n d r -> (Point d r, Point d r) Source #

Return the endpoints of the Bezier spline.

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

Reverse a BezierSpline

evaluate :: (Arity d, Eq 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.

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

Split a Bezier curve into many pieces. Todo: filter out duplicate parameter values!

splitMonotone :: (Arity d, Ord r, Enum r, Floating r) => Int -> BezierSpline 3 d r -> [BezierSpline 3 d r] Source #

Cut a Bezier curve into $x_i$-monotone pieces. Can only be solved exactly for degree 4 or smaller. Only gives rational result for degree 2 or smaller. Currentlly implemented for degree 3.

splitByPoints :: (KnownNat n, Ord r, RealFrac r) => r -> [Point 2 r] -> BezierSpline n 2 r -> [BezierSpline n 2 r] Source #

Subdivide a curve based on a sequence of points. Assumes these points are all supposed to lie on the curve, and snaps endpoints of pieces to these points. (higher dimensions would work, but depends on convex hull)

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

Extend a Bezier curve to a parameter value t outside the interval [0,1]. For t < 0, returns a Bezier representation of the section of the underlying curve from parameter value t until paramater value 0. For t > 1, the same from 1 to t.

pre: t outside [0,1]

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

Extend a Bezier curve to a parameter value t outside the interval [0,1]. For t < 0, returns a Bezier representation of the section of the underlying curve from parameter value t until paramater value 1. For t > 1, the same from 0 to t.

pre: t outside [0,1]

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

Extend a Bezier curve to a point not on the curve, but on / close to the extended underlying curve.

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

Merge two Bezier pieces. Assumes they can be merged into a single piece of the same degree (as would e.g. be the case for the result of a split operation). Does not test whether this is the case!

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 the piece between parameters t < u in [0, 1].

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

Extract a tangent vector from the first to the second control point.

approximate :: (KnownNat n, Arity d, Ord r, Fractional r) => r -> BezierSpline n d r -> PolyLine d () r Source #

Approximate Bezier curve by Polyline with given resolution. That is, every point on the approximation will have distance at most res to the Bezier curve.

parameterOf :: (KnownNat n, Ord r, RealFrac r) => r -> BezierSpline n 2 r -> Point 2 r -> r Source #

Given a point on (or within distance treshold to) a Bezier curve, return the parameter value of some point on the curve within distance treshold from p. For points farther than treshold from the curve, the function will attempt to return the parameter value of an approximate locally closest point to the input point, but no guarantees.

snap :: (KnownNat n, Ord r, RealFrac r) => r -> BezierSpline n 2 r -> Point 2 r -> Point 2 r Source #

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

intersectB :: (KnownNat n, Ord r, RealFrac r) => r -> BezierSpline n 2 r -> BezierSpline n 2 r -> [Point 2 r] Source #

Given two Bezier curves, list all intersection points. Not exact, since for degree >= 3 there is no closed form. (In principle, this algorithm works in any dimension but this requires convexHull, area/volume, and intersect.)

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.

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

Convert a quadratic bezier to a cubic bezier.