Copyright | Written by David Himmelstrup |
---|---|
License | Unlicense |
Maintainer | lemmih@gmail.com |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Convenience wrapper around CubicBezier
Synopsis
- newtype AnyBezier a = AnyBezier (Vector (V2 a))
- data CubicBezier a = CubicBezier {}
- data QuadBezier a = QuadBezier {}
- data OpenPath a = OpenPath [(V2 a, PathJoin a)] (V2 a)
- newtype ClosedPath a = ClosedPath [(V2 a, PathJoin a)]
- data PathJoin a
- newtype ClosedMetaPath a = ClosedMetaPath [(V2 a, MetaJoin a)]
- data OpenMetaPath a = OpenMetaPath [(V2 a, MetaJoin a)] (V2 a)
- data MetaJoin a
- data MetaNodeType a
- data FillRule
- data Tension a
- = Tension {
- tensionValue :: a
- | TensionAtLeast {
- tensionValue :: a
- = Tension {
- quadToCubic :: Fractional a => QuadBezier a -> CubicBezier a
- arcLength :: CubicBezier Double -> Double -> Double -> Double
- arcLengthParam :: CubicBezier Double -> Double -> Double -> Double
- splitBezier :: (Unbox a, Fractional a, GenericBezier b) => b a -> a -> (b a, b a)
- colinear :: CubicBezier Double -> Double -> Bool
- evalBezier :: (GenericBezier b, Unbox a, Fractional a) => b a -> a -> V2 a
- evalBezierDeriv :: (Unbox a, Fractional a, GenericBezier b) => b a -> a -> (V2 a, V2 a)
- bezierHoriz :: CubicBezier Double -> [Double]
- bezierVert :: CubicBezier Double -> [Double]
- bezierSubsegment :: (Ord a, Unbox a, Fractional a, GenericBezier b) => b a -> a -> a -> b a
- reorient :: (GenericBezier b, Unbox a) => b a -> b a
- closedPathCurves :: Fractional a => ClosedPath a -> [CubicBezier a]
- openPathCurves :: Fractional a => OpenPath a -> [CubicBezier a]
- curvesToClosed :: [CubicBezier a] -> ClosedPath a
- closest :: CubicBezier Double -> V2 Double -> Double -> Double
- unmetaOpen :: OpenMetaPath Double -> OpenPath Double
- unmetaClosed :: ClosedMetaPath Double -> ClosedPath Double
- union :: [ClosedPath Double] -> FillRule -> Double -> [ClosedPath Double]
- bezierIntersection :: CubicBezier Double -> CubicBezier Double -> Double -> [(Double, Double)]
- interpolateVector :: Num a => V2 a -> V2 a -> a -> V2 a
- vectorDistance :: Floating a => V2 a -> V2 a -> a
- findBezierInflection :: CubicBezier Double -> [Double]
- findBezierCusp :: CubicBezier Double -> [Double]
Documentation
A bezier curve of any degree.
data CubicBezier a Source #
A cubic bezier curve.
Instances
GenericBezier CubicBezier Source # | |
Defined in Geom2D.CubicBezier.Linear degree :: Unbox a => CubicBezier a -> Int # toVector :: Unbox a => CubicBezier a -> Vector (a, a) # unsafeFromVector :: Unbox a => Vector (a, a) -> CubicBezier a # | |
Eq a => Eq (CubicBezier a) Source # | |
Defined in Geom2D.CubicBezier.Linear (==) :: CubicBezier a -> CubicBezier a -> Bool # (/=) :: CubicBezier a -> CubicBezier a -> Bool # | |
Show a => Show (CubicBezier a) Source # | |
Defined in Geom2D.CubicBezier.Linear showsPrec :: Int -> CubicBezier a -> ShowS # show :: CubicBezier a -> String # showList :: [CubicBezier a] -> ShowS # |
data QuadBezier a Source #
A quadratic bezier curve.
Instances
GenericBezier QuadBezier Source # | |
Defined in Geom2D.CubicBezier.Linear degree :: Unbox a => QuadBezier a -> Int # toVector :: Unbox a => QuadBezier a -> Vector (a, a) # unsafeFromVector :: Unbox a => Vector (a, a) -> QuadBezier a # | |
Eq a => Eq (QuadBezier a) Source # | |
Defined in Geom2D.CubicBezier.Linear (==) :: QuadBezier a -> QuadBezier a -> Bool # (/=) :: QuadBezier a -> QuadBezier a -> Bool # | |
Show a => Show (QuadBezier a) Source # | |
Defined in Geom2D.CubicBezier.Linear showsPrec :: Int -> QuadBezier a -> ShowS # show :: QuadBezier a -> String # showList :: [QuadBezier a] -> ShowS # |
Open cubicbezier path.
newtype ClosedPath a Source #
Closed cubicbezier path.
ClosedPath [(V2 a, PathJoin a)] |
Instances
Eq a => Eq (ClosedPath a) Source # | |
Defined in Geom2D.CubicBezier.Linear (==) :: ClosedPath a -> ClosedPath a -> Bool # (/=) :: ClosedPath a -> ClosedPath a -> Bool # | |
Show a => Show (ClosedPath a) Source # | |
Defined in Geom2D.CubicBezier.Linear showsPrec :: Int -> ClosedPath a -> ShowS # show :: ClosedPath a -> String # showList :: [ClosedPath a] -> ShowS # |
Join two points with either a straight line or a bezier curve with two control points.
newtype ClosedMetaPath a Source #
Closed meta path.
ClosedMetaPath [(V2 a, MetaJoin a)] |
Instances
Eq a => Eq (ClosedMetaPath a) Source # | |
Defined in Geom2D.CubicBezier.Linear (==) :: ClosedMetaPath a -> ClosedMetaPath a -> Bool # (/=) :: ClosedMetaPath a -> ClosedMetaPath a -> Bool # | |
Show a => Show (ClosedMetaPath a) Source # | |
Defined in Geom2D.CubicBezier.Linear showsPrec :: Int -> ClosedMetaPath a -> ShowS # show :: ClosedMetaPath a -> String # showList :: [ClosedMetaPath a] -> ShowS # |
data OpenMetaPath a Source #
Open meta path
OpenMetaPath [(V2 a, MetaJoin a)] (V2 a) |
Instances
Eq a => Eq (OpenMetaPath a) Source # | |
Defined in Geom2D.CubicBezier.Linear (==) :: OpenMetaPath a -> OpenMetaPath a -> Bool # (/=) :: OpenMetaPath a -> OpenMetaPath a -> Bool # | |
Show a => Show (OpenMetaPath a) Source # | |
Defined in Geom2D.CubicBezier.Linear showsPrec :: Int -> OpenMetaPath a -> ShowS # show :: OpenMetaPath a -> String # showList :: [OpenMetaPath a] -> ShowS # |
Join two meta points with either a bezier curve or tension contraints.
MetaJoin | |
| |
Controls (V2 a) (V2 a) |
data MetaNodeType a Source #
Node constraint type.
Instances
Eq a => Eq (MetaNodeType a) Source # | |
Defined in Geom2D.CubicBezier.Linear (==) :: MetaNodeType a -> MetaNodeType a -> Bool # (/=) :: MetaNodeType a -> MetaNodeType a -> Bool # | |
Show a => Show (MetaNodeType a) Source # | |
Defined in Geom2D.CubicBezier.Linear showsPrec :: Int -> MetaNodeType a -> ShowS # show :: MetaNodeType a -> String # showList :: [MetaNodeType a] -> ShowS # |
Describe the possile filling algorithms. Map the values of the `fill-rule` attributes.
FillEvenOdd | Correspond to the |
FillNonZero | Correspond to the |
The tension value specifies how tense the curve is. A higher value means the curve approaches a line segment, while a lower value means the curve is more round. Metafont doesn't allow values below 3/4.
Tension | |
| |
TensionAtLeast | Like Tension, but keep the segment inside the bounding triangle defined by the control points, if there is one. |
|
Instances
Functor Tension Source # | |
Foldable Tension Source # | |
Defined in Geom2D.CubicBezier.Linear fold :: Monoid m => Tension m -> m # foldMap :: Monoid m => (a -> m) -> Tension a -> m # foldr :: (a -> b -> b) -> b -> Tension a -> b # foldr' :: (a -> b -> b) -> b -> Tension a -> b # foldl :: (b -> a -> b) -> b -> Tension a -> b # foldl' :: (b -> a -> b) -> b -> Tension a -> b # foldr1 :: (a -> a -> a) -> Tension a -> a # foldl1 :: (a -> a -> a) -> Tension a -> a # elem :: Eq a => a -> Tension a -> Bool # maximum :: Ord a => Tension a -> a # minimum :: Ord a => Tension a -> a # | |
Traversable Tension Source # | |
Eq a => Eq (Tension a) Source # | |
Show a => Show (Tension a) Source # | |
quadToCubic :: Fractional a => QuadBezier a -> CubicBezier a Source #
Convert a quadratic bezier to a cubic 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) #
Split a bezier curve into two curves.
colinear :: CubicBezier Double -> Double -> Bool Source #
Return False
if some points fall outside a line with a thickness of the given tolerance.
evalBezier :: (GenericBezier b, Unbox a, Fractional a) => b a -> a -> V2 a Source #
Calculate a value on the bezier curve.
evalBezierDeriv :: (Unbox a, Fractional a, GenericBezier b) => b a -> a -> (V2 a, V2 a) Source #
Calculate a value and the first derivative on the curve.
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.
bezierSubsegment :: (Ord a, Unbox a, Fractional a, GenericBezier b) => b a -> a -> a -> b a #
Return the subsegment between the two parameters.
reorient :: (GenericBezier b, Unbox a) => b a -> b a #
Reorient to the curve B(1-t).
closedPathCurves :: Fractional a => ClosedPath a -> [CubicBezier a] Source #
Return the closed path as a list of curves.
openPathCurves :: Fractional a => OpenPath a -> [CubicBezier a] Source #
Return the open path as a list of curves.
curvesToClosed :: [CubicBezier a] -> ClosedPath a Source #
Make an open path from a list of curves. The last control point of each curve is ignored.
closest :: CubicBezier Double -> V2 Double -> Double -> Double Source #
Find the closest value on the bezier to the given point, within tolerance. Return the first value found.
unmetaOpen :: OpenMetaPath Double -> OpenPath Double Source #
Create a normal path from a metapath.
unmetaClosed :: ClosedMetaPath Double -> ClosedPath Double Source #
Create a normal path from a metapath.
union :: [ClosedPath Double] -> FillRule -> Double -> [ClosedPath Double] Source #
`O((n+m)*log(n+m))`, for n segments and m intersections. Union of paths, removing overlap and rounding to the given tolerance.
bezierIntersection :: CubicBezier Double -> CubicBezier Double -> Double -> [(Double, Double)] Source #
Find the intersections between two Bezier curves, using the Bezier Clip algorithm. Returns the parameters for both curves.
findBezierInflection :: CubicBezier Double -> [Double] Source #
Find inflection points on the curve.
findBezierCusp :: CubicBezier Double -> [Double] Source #
Find the cusps of a bezier.