diagrams-contrib-1.4.0.1: Collection of user contributions to diagrams EDSL

Copyright(c) 2016 Bradley Hardy
LicenseBSD-style (see LICENSE)
Maintainerbradleyhardy@live.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Anchors

Contents

Description

An anchor is a point on an object which can be used for alignment by naming it, offering easier control over alignment compared to the Align module when aligning many objects.

Synopsis

Anchors

Anchored objects

data Anchored t Source #

An Anchored object which can be aligned to anchor points before concatenating with other Anchored objects. Note that when concatenating, any anchors with the same names in each of the left and right operands will be retained in the left operand, and lost in the right. To avoid this, qualify anchors in each object using '(>>/)'.

Instances

(Show (V t (N t)), Show t) => Show (Anchored t) Source # 

Methods

showsPrec :: Int -> Anchored t -> ShowS #

show :: Anchored t -> String #

showList :: [Anchored t] -> ShowS #

(Additive (V t), Num (N t), HasOrigin t, Semigroup t) => Semigroup (Anchored t) Source # 

Methods

(<>) :: Anchored t -> Anchored t -> Anchored t #

sconcat :: NonEmpty (Anchored t) -> Anchored t #

stimes :: Integral b => b -> Anchored t -> Anchored t #

(Additive (V t), Num (N t), HasOrigin t, Monoid' t) => Monoid (Anchored t) Source # 

Methods

mempty :: Anchored t #

mappend :: Anchored t -> Anchored t -> Anchored t #

mconcat :: [Anchored t] -> Anchored t #

Qualifiable t => Qualifiable (Anchored t) Source # 

Methods

(.>>) :: IsName a => a -> Anchored t -> Anchored t #

Transformable t => Transformable (Anchored t) Source # 

Methods

transform :: Transformation (V (Anchored t)) (N (Anchored t)) -> Anchored t -> Anchored t #

(HasOrigin t, Additive (V t), Num (N t)) => HasOrigin (Anchored t) Source # 

Methods

moveOriginTo :: Point (V (Anchored t)) (N (Anchored t)) -> Anchored t -> Anchored t #

type V (Anchored t) Source # 
type V (Anchored t) = V t
type N (Anchored t) Source # 
type N (Anchored t) = N t

withAnchors :: IsName anchor => [(anchor, V t (N t))] -> t -> Anchored t Source #

Attach a list of anchors to an object, making it Anchored.

noAnchors :: t -> Anchored t Source #

Turn an object into a trivial Anchored object with no anchors.

addAnchor :: IsName anchor => anchor -> V t (N t) -> Anchored t -> Anchored t Source #

Add another anchor to an already Anchored object.

deleteAnchor :: IsName anchor => anchor -> Anchored t -> Anchored t Source #

Delete an anchor from an anchored object. Does nothing if the object does not have the specified anchor.

getAnchorOffset :: (Num (N t), Additive (V t), IsName a) => a -> Anchored t -> V t (N t) Source #

Get the offset from the origin of a particular anchor, or zero if the object does not have the specified anchor.

alignAnchor :: IsName a => a -> Anchored t -> Anchored t Source #

Align an anchored object to an anchor. Subsequently concatening with '(<>)' will take this into account.

hasAnchor :: IsName a => a -> Anchored t -> Bool Source #

Does the given anchored object have the given anchor?

unanchor :: Anchored t -> t Source #

Throw away anchors and get the underlying object.

Positional anchors

data PositionalAnchor Source #

A convenient type of positional anchors.

rotateAnchors :: IsName anchor => [anchor] -> Int -> Anchored t -> Anchored t Source #

Given an Anchored object containing the given list of anchors, rotate the order of the given anchors clockwise by the given number of positions.

For example, given a diagram with positional anchors on it in these positions:

TL    T    TR

L          R

BL    B    BR

using rotatePosAnchors 1 = rotateAnchors (enumFrom AnchorL) 1 will move the anchors to these positions:

L     TL   T

BL         TR

B     BR   R

Using a parameter n is equivalent to using 1, n times and a negative number produces an anticlockwise rotation.

If any of the anchors do not exist, this function skips them.

rotatePosAnchors :: Int -> Anchored t -> Anchored t Source #

As rotateAnchors, but specialised to the list of all PositionalAnchors.

Easily concatenate many anchored objects

anchorMany :: (Num (N t), Semigroup t, Additive (V t), HasOrigin t, IsName anchor) => Anchored t -> [(anchor, anchor, Anchored t)] -> Anchored t Source #

Starting from a base anchored object, recursively concatenate more objects to the structure built up so far. Be sure to qualify anchors in the input so that names aren't overwritten.

In each (thatAnchor, thisAnchor, obj) triple, thatAnchor refers to the anchor point in the structure already constructed, and thisAnchor refers to the anchor point in the new object being added.

anchorMany_ :: (Num (N c), Semigroup c, Additive (V c), HasOrigin c, IsName anchor) => Anchored c -> [(anchor, anchor, Anchored c)] -> c Source #

As anchorMany, but call unanchor on the result. Convenient when you're not going to be doing any more alignment using anchors with the result.

Debugging

showAnchor :: (RealFloat n, Typeable n, Monoid m, Semigroup m, Renderable (Path V2 n) b, IsName a) => a -> Anchored (QDiagram b V2 n m) -> Anchored (QDiagram b V2 n m) Source #

Show a particular anchor in the Anchored object.

showAnchor_ :: (RealFloat n, Typeable n, Monoid m, Semigroup m, Renderable (Path V2 n) b, IsName a) => a -> Anchored (QDiagram b V2 n m) -> QDiagram b V2 n m Source #

Show a particular anchor in the Anchored object, then unanchor.