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

Safe HaskellNone
LanguageHaskell98

Geom2D.CubicBezier.MetaPath

Description

This module implements an extension to paths as used in D.E.Knuth's Metafont. Metafont gives an alternate way to specify paths using bezier curves. I'll give a brief overview of the metafont curves. A more in depth explanation can be found in The MetafontBook.

Each spline has a tension parameter, which is a relative measure of the length of the curve. You can specify the tension for the left side and the right side of the spline separately. By default metafont gives a tension of 1, which gives a good looking curve. Tensions shouldn't be less than 3/4, but this implementation doesn't check for it. If you want to avoid points of inflection on the spline, you can use TensionAtLeast instead of Tension, which will adjust the length of the control points so they fall into the bounding triangle, if such a triangle exist.

You can either give directions for each node, or let metafont find them. Metafont will solve a set of equations to find the directions. You can also let metafont find directions at corner points by setting the curl, which is how much the point curls at that point. At endpoints a curl of 1 is implied when it is not given.

Metafont will then find the control points from the path for you. You can also specify the control points explicitly.

Here is an example path from the metafont program text:

z0..z1..tension atleast 1..{curl 2}z2..z3{-1,-2}..tension 3 and 4..z4..controls z45 and z54..z5

This path is equivalent to:

z0{curl 1}..tension atleast 1 and atleast 1..{curl 2}z2{curl 2}..tension 1 and 1..
{-1,-2}z3{-1,-2}..tension 3 and 4..z4..controls z45 and z54..z5

This path can be used with the following datatype:

OpenMetaPath [ (z0, MetaJoin Open (Tension 1) (Tension 1) Open)
             , (z1, MetaJoin Open (TensionAtLeast 1) (TensionAtLeast 1) (Curl 2))
             , (z2, MetaJoin Open (Tension 1) (Tension 1) Open)
             , (z3, MetaJoin (Direction (Point (-1) (-2))) (Tension 3) (Tension 4) Open)
             , (z4, Controls z45 z54)
             ] z5

Cyclic paths are similar, but use the CyclicMetaPath contructor. There is no ending point, since the ending point will be the same as the first point.

Synopsis

Documentation

unmetaOpen :: OpenMetaPath Double -> OpenPath Double Source #

Create a normal path from a metapath.

data ClosedMetaPath a Source #

Constructors

ClosedMetaPath [(Point a, MetaJoin a)]

A metapath with cycles. The last join joins the last point with the first.

Instances

Functor ClosedMetaPath Source # 

Methods

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

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

Foldable ClosedMetaPath Source # 

Methods

fold :: Monoid m => ClosedMetaPath m -> m #

foldMap :: Monoid m => (a -> m) -> ClosedMetaPath a -> m #

foldr :: (a -> b -> b) -> b -> ClosedMetaPath a -> b #

foldr' :: (a -> b -> b) -> b -> ClosedMetaPath a -> b #

foldl :: (b -> a -> b) -> b -> ClosedMetaPath a -> b #

foldl' :: (b -> a -> b) -> b -> ClosedMetaPath a -> b #

foldr1 :: (a -> a -> a) -> ClosedMetaPath a -> a #

foldl1 :: (a -> a -> a) -> ClosedMetaPath a -> a #

toList :: ClosedMetaPath a -> [a] #

null :: ClosedMetaPath a -> Bool #

length :: ClosedMetaPath a -> Int #

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

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

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

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

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

Traversable ClosedMetaPath Source # 

Methods

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

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

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

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

Eq a => Eq (ClosedMetaPath a) Source # 
(Show a, Real a) => Show (ClosedMetaPath a) Source # 

data OpenMetaPath a Source #

Constructors

OpenMetaPath [(Point a, MetaJoin a)] (Point a)

A metapath with endpoints

Instances

Functor OpenMetaPath Source # 

Methods

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

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

Foldable OpenMetaPath Source # 

Methods

fold :: Monoid m => OpenMetaPath m -> m #

foldMap :: Monoid m => (a -> m) -> OpenMetaPath a -> m #

foldr :: (a -> b -> b) -> b -> OpenMetaPath a -> b #

foldr' :: (a -> b -> b) -> b -> OpenMetaPath a -> b #

foldl :: (b -> a -> b) -> b -> OpenMetaPath a -> b #

foldl' :: (b -> a -> b) -> b -> OpenMetaPath a -> b #

foldr1 :: (a -> a -> a) -> OpenMetaPath a -> a #

foldl1 :: (a -> a -> a) -> OpenMetaPath a -> a #

toList :: OpenMetaPath a -> [a] #

null :: OpenMetaPath a -> Bool #

length :: OpenMetaPath a -> Int #

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

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

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

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

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

Traversable OpenMetaPath Source # 

Methods

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

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

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

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

(Show a, Real a) => Show (OpenMetaPath a) Source # 

data MetaJoin a Source #

Constructors

MetaJoin 

Fields

  • metaTypeL :: MetaNodeType a

    The nodetype going out of the previous point. The metafont default is Open.

  • tensionL :: Tension a

    The tension going out of the previous point. The metafont default is 1.

  • tensionR :: Tension a

    The tension going into the next point. The metafont default is 1.

  • metaTypeR :: MetaNodeType a

    The nodetype going into the next point. The metafont default is Open.

Controls (Point a) (Point a)

Specify the control points explicitly.

Instances

Functor MetaJoin Source # 

Methods

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

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

Foldable MetaJoin Source # 

Methods

fold :: Monoid m => MetaJoin m -> m #

foldMap :: Monoid m => (a -> m) -> MetaJoin a -> m #

foldr :: (a -> b -> b) -> b -> MetaJoin a -> b #

foldr' :: (a -> b -> b) -> b -> MetaJoin a -> b #

foldl :: (b -> a -> b) -> b -> MetaJoin a -> b #

foldl' :: (b -> a -> b) -> b -> MetaJoin a -> b #

foldr1 :: (a -> a -> a) -> MetaJoin a -> a #

foldl1 :: (a -> a -> a) -> MetaJoin a -> a #

toList :: MetaJoin a -> [a] #

null :: MetaJoin a -> Bool #

length :: MetaJoin a -> Int #

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

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

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

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

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

Traversable MetaJoin Source # 

Methods

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

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

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

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

Eq a => Eq (MetaJoin a) Source # 

Methods

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

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

Show a => Show (MetaJoin a) Source # 

Methods

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

show :: MetaJoin a -> String #

showList :: [MetaJoin a] -> ShowS #

data MetaNodeType a Source #

Constructors

Open

An open node has no direction specified. If it is an internal node, the curve will keep the same direction going into and going out from the node. If it is an endpoint or corner point, it will have curl of 1.

Curl

The node becomes and endpoint or a corner point. The curl specifies how much the segment curves. A curl of gamma means that the curvature is gamma times that of the following node.

Fields

Direction

The node has a given direction.

Fields

Instances

Functor MetaNodeType Source # 

Methods

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

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

Foldable MetaNodeType Source # 

Methods

fold :: Monoid m => MetaNodeType m -> m #

foldMap :: Monoid m => (a -> m) -> MetaNodeType a -> m #

foldr :: (a -> b -> b) -> b -> MetaNodeType a -> b #

foldr' :: (a -> b -> b) -> b -> MetaNodeType a -> b #

foldl :: (b -> a -> b) -> b -> MetaNodeType a -> b #

foldl' :: (b -> a -> b) -> b -> MetaNodeType a -> b #

foldr1 :: (a -> a -> a) -> MetaNodeType a -> a #

foldl1 :: (a -> a -> a) -> MetaNodeType a -> a #

toList :: MetaNodeType a -> [a] #

null :: MetaNodeType a -> Bool #

length :: MetaNodeType a -> Int #

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

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

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

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

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

Traversable MetaNodeType Source # 

Methods

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

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

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

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

Eq a => Eq (MetaNodeType a) Source # 
Show a => Show (MetaNodeType a) Source # 

data Tension a Source #

Constructors

Tension

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.

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 # 

Methods

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

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

Foldable Tension Source # 

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 # 

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 # 

Methods

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

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

Show a => Show (Tension a) Source # 

Methods

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

show :: Tension a -> String #

showList :: [Tension a] -> ShowS #