cubicbezier-0.4.0.2: Efficient manipulating of 2D cubic bezier curves.

Safe HaskellNone
LanguageHaskell98

Geom2D.CubicBezier.Basic

Synopsis

Documentation

data CubicBezier a Source

A cubic bezier curve.

Constructors

CubicBezier 

Fields

cubicC0 :: !(Point a)
 
cubicC1 :: !(Point a)
 
cubicC2 :: !(Point a)
 
cubicC3 :: !(Point a)
 

data QuadBezier a Source

A quadratic bezier curve.

Constructors

QuadBezier 

Fields

quadC0 :: !(Point a)
 
quadC1 :: !(Point a)
 
quadC2 :: !(Point a)
 

data AnyBezier a Source

A bezier curve of any degree.

Constructors

AnyBezier (Vector (a, a)) 

data PathJoin a Source

Constructors

JoinLine 
JoinCurve (Point a) (Point a) 

Instances

data ClosedPath a Source

Constructors

ClosedPath [(Point a, PathJoin a)] 

Instances

data OpenPath a Source

Constructors

OpenPath [(Point a, PathJoin a)] (Point a) 

Instances

class AffineTransform a b | a -> b where Source

Methods

transform :: Transform b -> a -> a Source

anyToCubic :: Unbox a => AnyBezier a -> Maybe (CubicBezier a) Source

safely convert from AnyBezier to CubicBezier

anyToQuad :: Unbox a => AnyBezier a -> Maybe (QuadBezier a) Source

safely convert from AnyBezier to QuadBezier

openPathCurves :: Fractional a => OpenPath a -> [CubicBezier a] Source

Return the open path as a list of curves.

closedPathCurves :: Fractional a => ClosedPath a -> [CubicBezier a] Source

Return the closed path as a list of curves

curvesToOpen :: [CubicBezier a] -> OpenPath a Source

Make an open path from a list of curves. The last control point of each curve except the last is ignored.

curvesToClosed :: [CubicBezier a] -> ClosedPath a Source

Make an open path from a list of curves. The last control point of each curve is ignored.

bezierParam :: (Ord a, Num a) => a -> Bool Source

Return True if the param lies on the curve, iff it's in the interval [0, 1].

bezierParamTolerance :: GenericBezier b => b Double -> Double -> Double Source

Convert a tolerance from the codomain to the domain of the bezier curve, by dividing by the maximum velocity on the curve. The estimate is conservative, but holds for any value on the curve.

reorient :: (GenericBezier b, Unbox a) => b a -> b a Source

Reorient to the curve B(1-t).

bezierToBernstein :: (GenericBezier b, Unbox a) => b a -> (BernsteinPoly a, BernsteinPoly a) Source

Give the bernstein polynomial for each coordinate.

evalBezierDerivs :: (GenericBezier b, Unbox a, Fractional a) => b a -> a -> [Point a] Source

Evaluate the bezier and all its derivatives using the modified horner algorithm.

evalBezier :: (GenericBezier b, Unbox a, Fractional a) => b a -> a -> Point a Source

Calculate a value on the bezier curve.

evalBezierDeriv :: (Unbox a, Fractional a) => GenericBezier b => b a -> a -> (Point a, Point a) Source

Calculate a value and the first derivative on the curve.

findBezierTangent :: DPoint -> CubicBezier Double -> [Double] Source

findBezierTangent p b finds the parameters where the tangent of the bezier curve b has the same direction as vector p.

quadToCubic :: Fractional a => QuadBezier a -> CubicBezier a Source

Convert a quadratic bezier to a cubic bezier.

bezierHoriz :: CubicBezier Double -> [Double] Source

Find the parameter where the bezier curve is horizontal.

bezierVert :: CubicBezier Double -> [Double] Source

Find the parameter where the bezier curve is vertical.

findBezierInflection :: CubicBezier Double -> [Double] Source

Find inflection points on the curve. Use the formula B_x''(t) * B_y'(t) - B_y''(t) * B_x'(t) = 0 with B_x'(t) the x value of the first derivative at t, B_y''(t) the y value of the second derivative at t

findBezierCusp :: CubicBezier Double -> [Double] Source

Find the cusps of a bezier.

arcLength :: CubicBezier Double -> Double -> Double -> Double Source

@arcLength c t tol finds the arclength of the bezier c at t, within given tolerance tol.

arcLengthParam :: CubicBezier Double -> Double -> Double -> Double Source

arcLengthParam c len tol finds the parameter where the curve c has the arclength len, within tolerance tol.

splitBezier :: (Unbox a, Fractional a) => GenericBezier b => b a -> a -> (b a, b a) Source

Split a bezier curve into two curves.

bezierSubsegment :: (Ord a, Unbox a, Fractional a) => GenericBezier b => b a -> a -> a -> b a Source

Return the subsegment between the two parameters.

splitBezierN :: (Ord a, Unbox a, Fractional a) => GenericBezier b => b a -> [a] -> [b a] Source

Split a bezier curve into a list of beziers The parameters should be in ascending order or the result is unpredictable.

colinear :: CubicBezier Double -> Double -> Bool Source

Return False if some points fall outside a line with a thickness of the given tolerance.