reanimate-1.1.2.1: Animation library based on SVGs.

CopyrightWritten by David Himmelstrup
LicenseUnlicense
Maintainerlemmih@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Geom2D.CubicBezier.Linear

Description

Convenience wrapper around CubicBezier

Synopsis

Documentation

newtype AnyBezier a Source #

A bezier curve of any degree.

Constructors

AnyBezier (Vector (V2 a)) 
Instances
GenericBezier AnyBezier Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

degree :: Unbox a => AnyBezier a -> Int #

toVector :: Unbox a => AnyBezier a -> Vector (a, a) #

unsafeFromVector :: Unbox a => Vector (a, a) -> AnyBezier a #

data CubicBezier a Source #

A cubic bezier curve.

Constructors

CubicBezier 

Fields

Instances
GenericBezier CubicBezier Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

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 # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Show a => Show (CubicBezier a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

data QuadBezier a Source #

A quadratic bezier curve.

Constructors

QuadBezier 

Fields

Instances
GenericBezier QuadBezier Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

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 # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

(==) :: QuadBezier a -> QuadBezier a -> Bool #

(/=) :: QuadBezier a -> QuadBezier a -> Bool #

Show a => Show (QuadBezier a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

data OpenPath a Source #

Open cubicbezier path.

Constructors

OpenPath [(V2 a, PathJoin a)] (V2 a) 
Instances
Eq a => Eq (OpenPath a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

(==) :: OpenPath a -> OpenPath a -> Bool #

(/=) :: OpenPath a -> OpenPath a -> Bool #

Show a => Show (OpenPath a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

showsPrec :: Int -> OpenPath a -> ShowS #

show :: OpenPath a -> String #

showList :: [OpenPath a] -> ShowS #

newtype ClosedPath a Source #

Closed cubicbezier path.

Constructors

ClosedPath [(V2 a, PathJoin a)] 
Instances
Eq a => Eq (ClosedPath a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

(==) :: ClosedPath a -> ClosedPath a -> Bool #

(/=) :: ClosedPath a -> ClosedPath a -> Bool #

Show a => Show (ClosedPath a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

data PathJoin a Source #

Join two points with either a straight line or a bezier curve with two control points.

Constructors

JoinLine 
JoinCurve (V2 a) (V2 a) 
Instances
Eq a => Eq (PathJoin a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

(==) :: PathJoin a -> PathJoin a -> Bool #

(/=) :: PathJoin a -> PathJoin a -> Bool #

Show a => Show (PathJoin a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

showsPrec :: Int -> PathJoin a -> ShowS #

show :: PathJoin a -> String #

showList :: [PathJoin a] -> ShowS #

newtype ClosedMetaPath a Source #

Closed meta path.

Constructors

ClosedMetaPath [(V2 a, MetaJoin a)] 
Instances
Eq a => Eq (ClosedMetaPath a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Show a => Show (ClosedMetaPath a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

data OpenMetaPath a Source #

Open meta path

Constructors

OpenMetaPath [(V2 a, MetaJoin a)] (V2 a) 
Instances
Eq a => Eq (OpenMetaPath a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Show a => Show (OpenMetaPath a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

data MetaJoin a Source #

Join two meta points with either a bezier curve or tension contraints.

Constructors

MetaJoin 
Controls (V2 a) (V2 a) 
Instances
Eq a => Eq (MetaJoin a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

(==) :: MetaJoin a -> MetaJoin a -> Bool #

(/=) :: MetaJoin a -> MetaJoin a -> Bool #

Show a => Show (MetaJoin a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

showsPrec :: Int -> MetaJoin a -> ShowS #

show :: MetaJoin a -> String #

showList :: [MetaJoin a] -> ShowS #

data MetaNodeType a Source #

Node constraint type.

Constructors

Open 
Curl 

Fields

Direction 

Fields

Instances
Eq a => Eq (MetaNodeType a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Show a => Show (MetaNodeType a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

data FillRule #

Describe the possile filling algorithms. Map the values of the `fill-rule` attributes.

Constructors

FillEvenOdd

Correspond to the evenodd value.

FillNonZero

Correspond to the nonzero value.

Instances
Eq FillRule 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Show FillRule 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Generic FillRule 
Instance details

Defined in Graphics.SvgTree.Types.Basic

Associated Types

type Rep FillRule :: Type -> Type #

Methods

from :: FillRule -> Rep FillRule x #

to :: Rep FillRule x -> FillRule #

ParseableAttribute FillRule 
Instance details

Defined in Graphics.SvgTree.XmlParser

type Rep FillRule 
Instance details

Defined in Graphics.SvgTree.Types.Basic

type Rep FillRule = D1 (MetaData "FillRule" "Graphics.SvgTree.Types.Basic" "reanimate-svg-0.13.0.0-2UGCAcpfXo8JwCuKbyXS6O" False) (C1 (MetaCons "FillEvenOdd" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FillNonZero" PrefixI False) (U1 :: Type -> Type))

data Tension a Source #

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.

Constructors

Tension 

Fields

TensionAtLeast

Like Tension, but keep the segment inside the bounding triangle defined by the control points, if there is one.

Fields

Instances
Functor Tension Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

fmap :: (a -> b) -> Tension a -> Tension b #

(<$) :: a -> Tension b -> Tension a #

Foldable Tension Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

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 #

toList :: Tension a -> [a] #

null :: Tension a -> Bool #

length :: Tension a -> Int #

elem :: Eq a => a -> Tension a -> Bool #

maximum :: Ord a => Tension a -> a #

minimum :: Ord a => Tension a -> a #

sum :: Num a => Tension a -> a #

product :: Num a => Tension a -> a #

Traversable Tension Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

traverse :: Applicative f => (a -> f b) -> Tension a -> f (Tension b) #

sequenceA :: Applicative f => Tension (f a) -> f (Tension a) #

mapM :: Monad m => (a -> m b) -> Tension a -> m (Tension b) #

sequence :: Monad m => Tension (m a) -> m (Tension a) #

Eq a => Eq (Tension a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

(==) :: Tension a -> Tension a -> Bool #

(/=) :: Tension a -> Tension a -> Bool #

Show a => Show (Tension a) Source # 
Instance details

Defined in Geom2D.CubicBezier.Linear

Methods

showsPrec :: Int -> Tension a -> ShowS #

show :: Tension a -> String #

showList :: [Tension a] -> ShowS #

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.

interpolateVector :: Num a => V2 a -> V2 a -> a -> V2 a Source #

Interpolate between two vectors.

vectorDistance :: Floating a => V2 a -> V2 a -> a Source #

Distance between two vectors.

findBezierInflection :: CubicBezier Double -> [Double] Source #

Find inflection points on the curve.

findBezierCusp :: CubicBezier Double -> [Double] Source #

Find the cusps of a bezier.