diagrams-lib-1.4.4: Embedded domain-specific language for declarative graphics
Copyright(c) 2015 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams

Description

This module only contains exports defined in diagrams-lib or diagrams-core. This module can be used if you want to avoid some potential conflicts with other modules, but importing Diagrams.Prelude (which includes re-exports from other packages) is often more convenient.

Synopsis

Core library

The core definitions of transformations, diagrams, backends, and so on.

Standard library

Attributes (color, line style, etc.) and styles.

Alignment of diagrams relative to their envelopes.

Creating and using bounding boxes.

data BoundingBox v n Source #

A bounding box is an axis-aligned region determined by two points indicating its "lower" and "upper" corners. It can also represent an empty bounding box - the points are wrapped in Maybe.

Instances

Instances details
Functor v => Functor (BoundingBox v) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

fmap :: (a -> b) -> BoundingBox v a -> BoundingBox v b #

(<$) :: a -> BoundingBox v b -> BoundingBox v a #

Eq (v n) => Eq (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

(==) :: BoundingBox v n -> BoundingBox v n -> Bool #

(/=) :: BoundingBox v n -> BoundingBox v n -> Bool #

Read (v n) => Read (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Show (v n) => Show (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

showsPrec :: Int -> BoundingBox v n -> ShowS #

show :: BoundingBox v n -> String #

showList :: [BoundingBox v n] -> ShowS #

(Additive v, Ord n) => Semigroup (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

(<>) :: BoundingBox v n -> BoundingBox v n -> BoundingBox v n #

sconcat :: NonEmpty (BoundingBox v n) -> BoundingBox v n #

stimes :: Integral b => b -> BoundingBox v n -> BoundingBox v n #

(Additive v, Ord n) => Monoid (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

mempty :: BoundingBox v n #

mappend :: BoundingBox v n -> BoundingBox v n -> BoundingBox v n #

mconcat :: [BoundingBox v n] -> BoundingBox v n #

(Metric v, Traversable v, OrderedField n) => Enveloped (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

getEnvelope :: BoundingBox v n -> Envelope (V (BoundingBox v n)) (N (BoundingBox v n)) #

TypeableFloat n => Traced (BoundingBox V3 n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

getTrace :: BoundingBox V3 n -> Trace (V (BoundingBox V3 n)) (N (BoundingBox V3 n)) #

RealFloat n => Traced (BoundingBox V2 n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

getTrace :: BoundingBox V2 n -> Trace (V (BoundingBox V2 n)) (N (BoundingBox V2 n)) #

(Additive v, Num n) => HasOrigin (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

moveOriginTo :: Point (V (BoundingBox v n)) (N (BoundingBox v n)) -> BoundingBox v n -> BoundingBox v n #

AsEmpty (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

_Empty :: Prism' (BoundingBox v n) () #

(Metric v, Traversable v, OrderedField n) => Alignable (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

alignBy' :: (InSpace v0 n0 (BoundingBox v n), Fractional n0, HasOrigin (BoundingBox v n)) => (v0 n0 -> BoundingBox v n -> Point v0 n0) -> v0 n0 -> n0 -> BoundingBox v n -> BoundingBox v n Source #

defaultBoundary :: (V (BoundingBox v n) ~ v0, N (BoundingBox v n) ~ n0) => v0 n0 -> BoundingBox v n -> Point v0 n0 Source #

alignBy :: (InSpace v0 n0 (BoundingBox v n), Fractional n0, HasOrigin (BoundingBox v n)) => v0 n0 -> n0 -> BoundingBox v n -> BoundingBox v n Source #

(Additive v, Foldable v, Ord n) => HasQuery (BoundingBox v n) Any Source # 
Instance details

Defined in Diagrams.BoundingBox

Methods

getQuery :: BoundingBox v n -> Query (V (BoundingBox v n)) (N (BoundingBox v n)) Any Source #

(Additive v', Foldable v', Ord n') => Each (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') Source #

Only valid if the second point is not smaller than the first.

Instance details

Defined in Diagrams.BoundingBox

Methods

each :: Traversal (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n') #

type V (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

type V (BoundingBox v n) = v
type N (BoundingBox v n) Source # 
Instance details

Defined in Diagrams.BoundingBox

type N (BoundingBox v n) = n

emptyBox :: BoundingBox v n Source #

An empty bounding box. This is the same thing as mempty, but it doesn't require the same type constraints that the Monoid instance does.

fromCorners :: (Additive v, Foldable v, Ord n) => Point v n -> Point v n -> BoundingBox v n Source #

Create a bounding box from a point that is component-wise (<=) than the other. If this is not the case, then mempty is returned.

fromPoint :: Point v n -> BoundingBox v n Source #

Create a degenerate bounding "box" containing only a single point.

fromPoints :: (Additive v, Ord n) => [Point v n] -> BoundingBox v n Source #

Create the smallest bounding box containing all the given points.

boundingBox :: (InSpace v n a, HasBasis v, Enveloped a) => a -> BoundingBox v n Source #

Create a bounding box for any enveloped object (such as a diagram or path).

isEmptyBox :: BoundingBox v n -> Bool Source #

Queries whether the BoundingBox is empty.

getCorners :: BoundingBox v n -> Maybe (Point v n, Point v n) Source #

Gets the lower and upper corners that define the bounding box.

getAllCorners :: (Additive v, Traversable v) => BoundingBox v n -> [Point v n] Source #

Computes all of the corners of the bounding box.

boxExtents :: (Additive v, Num n) => BoundingBox v n -> v n Source #

Get the size of the bounding box - the vector from the (component-wise) lesser point to the greater point.

boxCenter :: (Additive v, Fractional n) => BoundingBox v n -> Maybe (Point v n) Source #

Get the center point in a bounding box.

mCenterPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Maybe (Point v n) Source #

Get the center of a the bounding box of an enveloped object, return Nothing for object with empty envelope.

centerPoint :: (InSpace v n a, HasBasis v, Enveloped a) => a -> Point v n Source #

Get the center of a the bounding box of an enveloped object, return the origin for object with empty envelope.

boxTransform :: (Additive v, Fractional n) => BoundingBox v n -> BoundingBox v n -> Maybe (Transformation v n) Source #

Create a transformation mapping points from one bounding box to the other. Returns Nothing if either of the boxes are empty.

boxFit :: (InSpace v n a, HasBasis v, Enveloped a, Transformable a, Monoid a) => BoundingBox v n -> a -> a Source #

Transforms an enveloped thing to fit within a BoundingBox. If the bounding box is empty, then the result is also mempty.

contains' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> Point v n -> Bool Source #

Check whether a point is strictly contained in a bounding box.

inside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool Source #

Test whether the first bounding box is strictly contained inside the second.

outside' :: (Additive v, Foldable v, Ord n) => BoundingBox v n -> BoundingBox v n -> Bool Source #

Test whether the first bounding box lies strictly outside the second (they do not intersect at all).

boxGrid :: (Traversable v, Additive v, Num n, Enum n) => n -> BoundingBox v n -> [Point v n] Source #

boxGrid f box returns a grid of regularly spaced points inside the box, such that there are (1/f) points along each dimension. For example, for a 3D box with corners at (0,0,0) and (2,2,2), boxGrid 0.1 would yield a grid of approximately 1000 points (it might actually be 11^3 instead of 10^3) spaced 0.2 units apart.

Combining multiple diagrams into one.

Giving concrete locations to translation-invariant things.

Linear and cubic bezier segments.

Trails.

data Trail v n where Source #

Trail is a wrapper around Trail', hiding whether the underlying Trail' is a line or loop (though which it is can be recovered; see e.g. withTrail).

Constructors

Trail :: Trail' l v n -> Trail v n 

Instances

Instances details
(Metric v, OrderedField n) => Reversing (Located (Trail v n)) Source #

Same as reverseLocTrail.

Instance details

Defined in Diagrams.Trail

Methods

reversing :: Located (Trail v n) -> Located (Trail v n) #

(Metric v, OrderedField n, Real n) => EndValues (Tangent (Trail v n)) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: Tangent (Trail v n) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) Source #

atEnd :: Tangent (Trail v n) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) Source #

(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail v n)) Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: Tangent (Trail v n) -> N (Tangent (Trail v n)) -> Codomain (Tangent (Trail v n)) (N (Tangent (Trail v n))) Source #

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: GetSegment (Trail v n) -> N (GetSegment (Trail v n)) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) Source #

ToPath (Located (Trail v n)) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located (Trail v n) -> Path (V (Located (Trail v n))) (N (Located (Trail v n))) Source #

RealFloat n => HasQuery (Located (Trail V2 n)) Crossings Source # 
Instance details

Defined in Diagrams.TwoD.Path

(Metric v, Metric u, OrderedField n, r ~ Located (Trail u n)) => Deformable (Located (Trail v n)) r Source # 
Instance details

Defined in Diagrams.Deform

Methods

deform' :: N (Located (Trail v n)) -> Deformation (V (Located (Trail v n))) (V r) (N (Located (Trail v n))) -> Located (Trail v n) -> r Source #

deform :: Deformation (V (Located (Trail v n))) (V r) (N (Located (Trail v n))) -> Located (Trail v n) -> r Source #

Eq (v n) => Eq (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

(==) :: Trail v n -> Trail v n -> Bool #

(/=) :: Trail v n -> Trail v n -> Bool #

Ord (v n) => Ord (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

compare :: Trail v n -> Trail v n -> Ordering #

(<) :: Trail v n -> Trail v n -> Bool #

(<=) :: Trail v n -> Trail v n -> Bool #

(>) :: Trail v n -> Trail v n -> Bool #

(>=) :: Trail v n -> Trail v n -> Bool #

max :: Trail v n -> Trail v n -> Trail v n #

min :: Trail v n -> Trail v n -> Trail v n #

Show (v n) => Show (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

showsPrec :: Int -> Trail v n -> ShowS #

show :: Trail v n -> String #

showList :: [Trail v n] -> ShowS #

(OrderedField n, Metric v) => Semigroup (Trail v n) Source #

Two Trails are combined by first ensuring they are both lines (using cutTrail on loops) and then concatenating them. The result, in general, is a line. However, there is a special case for the empty line, which acts as the identity (so combining the empty line with a loop results in a loop).

Instance details

Defined in Diagrams.Trail

Methods

(<>) :: Trail v n -> Trail v n -> Trail v n #

sconcat :: NonEmpty (Trail v n) -> Trail v n #

stimes :: Integral b => b -> Trail v n -> Trail v n #

(Metric v, OrderedField n) => Monoid (Trail v n) Source #

Trails are combined as described in the Semigroup instance; the empty line is the identity element, with special cases so that combining the empty line with a loop results in the unchanged loop (in all other cases loops will be cut). Note that this does, in fact, satisfy the monoid laws, though it is a bit strange. Mostly it is provided for convenience, so one can work directly with Trails instead of working with Trail' Lines and then wrapping.

Instance details

Defined in Diagrams.Trail

Methods

mempty :: Trail v n #

mappend :: Trail v n -> Trail v n -> Trail v n #

mconcat :: [Trail v n] -> Trail v n #

(Serialize (v n), OrderedField n, Metric v) => Serialize (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

put :: Putter (Trail v n) #

get :: Get (Trail v n) #

(Metric v, OrderedField n) => Enveloped (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

getEnvelope :: Trail v n -> Envelope (V (Trail v n)) (N (Trail v n)) #

RealFloat n => Traced (Trail V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getTrace :: Trail V2 n -> Trace (V (Trail V2 n)) (N (Trail V2 n)) #

(HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

transform :: Transformation (V (Trail v n)) (N (Trail v n)) -> Trail v n -> Trail v n #

Wrapped (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Associated Types

type Unwrapped (Trail v n) #

Methods

_Wrapped' :: Iso' (Trail v n) (Unwrapped (Trail v n)) #

(Metric v, OrderedField n) => AsEmpty (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Empty :: Prism' (Trail v n) () #

(Metric v, OrderedField n) => Reversing (Trail v n) Source #

Same as reverseTrail.

Instance details

Defined in Diagrams.Trail

Methods

reversing :: Trail v n -> Trail v n #

(Metric v, OrderedField n, Real n) => HasArcLength (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

arcLengthBounded :: N (Trail v n) -> Trail v n -> Interval (N (Trail v n)) Source #

arcLength :: N (Trail v n) -> Trail v n -> N (Trail v n) Source #

stdArcLength :: Trail v n -> N (Trail v n) Source #

arcLengthToParam :: N (Trail v n) -> Trail v n -> N (Trail v n) -> N (Trail v n) Source #

stdArcLengthToParam :: Trail v n -> N (Trail v n) -> N (Trail v n) Source #

(Metric v, OrderedField n, Real n) => Sectionable (Trail v n) Source #

Note that there is no Sectionable instance for Trail' Loop, because it does not make sense (splitting a loop at a parameter results in a single line, not two loops). However, it's convenient to have a Sectionable instance for Trail; if the Trail contains a loop the loop will first be cut and then splitAtParam called on the resulting line. This is semantically a bit silly, so please don't rely on it. (*E.g.* if this is really the behavior you want, consider first calling cutLoop yourself.)

Instance details

Defined in Diagrams.Trail

Methods

splitAtParam :: Trail v n -> N (Trail v n) -> (Trail v n, Trail v n) Source #

section :: Trail v n -> N (Trail v n) -> N (Trail v n) -> Trail v n Source #

reverseDomain :: Trail v n -> Trail v n Source #

(Metric v, OrderedField n, Real n) => EndValues (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: Trail v n -> Codomain (Trail v n) (N (Trail v n)) Source #

atEnd :: Trail v n -> Codomain (Trail v n) (N (Trail v n)) Source #

Num n => DomainBounds (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

domainLower :: Trail v n -> N (Trail v n) Source #

domainUpper :: Trail v n -> N (Trail v n) Source #

(Metric v, OrderedField n, Real n) => Parametric (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: Trail v n -> N (Trail v n) -> Codomain (Trail v n) (N (Trail v n)) Source #

(Metric v, OrderedField n) => TrailLike (Trail v n) Source #

Trails are trail-like; the location is simply ignored.

Instance details

Defined in Diagrams.TrailLike

Methods

trailLike :: Located (Trail (V (Trail v n)) (N (Trail v n))) -> Trail v n Source #

ToPath (Trail v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Trail v n -> Path (V (Trail v n)) (N (Trail v n)) Source #

(Metric v, Metric u, OrderedField n, r ~ Trail u n) => AffineMappable (Trail v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

amap :: AffineMap (V (Trail v n)) (V r) (N r) -> Trail v n -> r Source #

(Metric v, Metric u, OrderedField n, OrderedField m, r ~ Trail u m) => LinearMappable (Trail v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

vmap :: (Vn (Trail v n) -> Vn r) -> Trail v n -> r Source #

Rewrapped (Trail v n) (Trail v' n') Source # 
Instance details

Defined in Diagrams.Trail

Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

each :: Traversal (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) #

Cons (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

_Cons :: Prism (Path v n) (Path v' n') (Located (Trail v n), Path v n) (Located (Trail v' n'), Path v' n') #

Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

_Snoc :: Prism (Path v n) (Path v' n') (Path v n, Located (Trail v n)) (Path v' n', Located (Trail v' n')) #

type V (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

type V (Trail v n) = v
type N (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

type N (Trail v n) = n
type Unwrapped (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

type Unwrapped (Trail v n) = Either (Trail' Line v n) (Trail' Loop v n)
type Codomain (Trail v n) Source # 
Instance details

Defined in Diagrams.Trail

type Codomain (Trail v n) = v

newtype GetSegmentCodomain v n Source #

Constructors

GetSegmentCodomain (Maybe (v n, Segment Closed v n, AnIso' n n)) 

newtype GetSegment t Source #

A newtype wrapper around trails which exists solely for its Parametric, DomainBounds and EndValues instances. The idea is that if tr is a trail, you can write, e.g.

  getSegment tr atParam 0.6
  

or

  atStart (getSegment tr)
  

to get the segment at parameter 0.6 or the first segment in the trail, respectively.

The codomain for GetSegment, i.e. the result you get from calling atParam, atStart, or atEnd, is GetSegmentCodomain, which is a newtype wrapper around Maybe (v, Segment Closed v, AnIso' n n). Nothing results if the trail is empty; otherwise, you get:

  • the offset from the start of the trail to the beginning of the segment,
  • the segment itself, and
  • a reparameterization isomorphism: in the forward direction, it translates from parameters on the whole trail to a parameters on the segment. Note that for technical reasons you have to call cloneIso on the AnIso' value to get a real isomorphism you can use.

Constructors

GetSegment t 

Instances

Instances details
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail v n)) Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) Source # 
Instance details

Defined in Diagrams.Trail

DomainBounds t => DomainBounds (GetSegment t) Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: GetSegment (Trail v n) -> N (GetSegment (Trail v n)) -> Codomain (GetSegment (Trail v n)) (N (GetSegment (Trail v n))) Source #

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) Source #

The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1".

Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) Source #

Parameters less than 0 yield the first segment; parameters greater than 1 yield the last. A parameter exactly at the junction of two segments yields the second segment (i.e. the one with higher parameter values).

Instance details

Defined in Diagrams.Trail

type V (GetSegment t) Source # 
Instance details

Defined in Diagrams.Trail

type V (GetSegment t) = V t
type N (GetSegment t) Source # 
Instance details

Defined in Diagrams.Trail

type N (GetSegment t) = N t
type Codomain (GetSegment t) Source # 
Instance details

Defined in Diagrams.Trail

data Trail' l v n where Source #

Intuitively, a trail is a single, continuous path through space. However, a trail has no fixed starting point; it merely specifies how to move through space, not where. For example, "take three steps forward, then turn right twenty degrees and take two more steps" is an intuitive analog of a trail; these instructions specify a path through space from any given starting location. To be precise, trails are translation-invariant; applying a translation to a trail has no effect.

A Located Trail, on the other hand, is a trail paired with some concrete starting location ("start at the big tree on the corner, then take three steps forward, ..."). See the Diagrams.Located module for help working with Located values.

Formally, the semantics of a trail is a continuous (though not necessarily differentiable) function from the real interval [0,1] to vectors in some vector space. (In contrast, a Located trail is a continuous function from [0,1] to points in some affine space.)

There are two types of trails:

  • A "line" (think of the "train", "subway", or "bus" variety, rather than the "straight" variety...) is a trail with two distinct endpoints. Actually, a line can have the same start and end points, but it is still drawn as if it had distinct endpoints: the two endpoints will have the appropriate end caps, and the trail will not be filled. Lines have a Monoid instance where mappend corresponds to concatenation, i.e. chaining one line after the other.
  • A "loop" is required to end in the same place it starts (that is, t(0) = t(1)). Loops are filled and are drawn as one continuous loop, with the appropriate join at the start/endpoint rather than end caps. Loops do not have a Monoid instance.

To convert between lines and loops, see glueLine, closeLine, and cutLoop.

To construct trails, see emptyTrail, trailFromSegments, trailFromVertices, trailFromOffsets, and friends. You can also get any type of trail from any function which returns a TrailLike (e.g. functions in Diagrams.TwoD.Shapes, and many others; see Diagrams.TrailLike).

To extract information from trails, see withLine, isLoop, trailSegments, trailOffsets, trailVertices, and friends.

Constructors

Line :: SegTree v n -> Trail' Line v n 
Loop :: SegTree v n -> Segment Open v n -> Trail' Loop v n 

Instances

Instances details
(Metric v, OrderedField n) => Reversing (Located (Trail' l v n)) Source #

Same as reverseLocLine or reverseLocLoop.

Instance details

Defined in Diagrams.Trail

Methods

reversing :: Located (Trail' l v n) -> Located (Trail' l v n) #

(Parametric (GetSegment (Trail' c v n)), EndValues (GetSegment (Trail' c v n)), Additive v, Num n) => EndValues (Tangent (Trail' c v n)) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: Tangent (Trail' c v n) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) Source #

atEnd :: Tangent (Trail' c v n) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) Source #

(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) Source # 
Instance details

Defined in Diagrams.Trail

(Parametric (GetSegment (Trail' c v n)), Additive v, Num n) => Parametric (Tangent (Trail' c v n)) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: Tangent (Trail' c v n) -> N (Tangent (Trail' c v n)) -> Codomain (Tangent (Trail' c v n)) (N (Tangent (Trail' c v n))) Source #

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) Source #

The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1".

Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) Source #

Parameters less than 0 yield the first segment; parameters greater than 1 yield the last. A parameter exactly at the junction of two segments yields the second segment (i.e. the one with higher parameter values).

Instance details

Defined in Diagrams.Trail

ToPath (Located (Trail' l v n)) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located (Trail' l v n) -> Path (V (Located (Trail' l v n))) (N (Located (Trail' l v n))) Source #

RealFloat n => HasQuery (Located (Trail' l V2 n)) Crossings Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getQuery :: Located (Trail' l V2 n) -> Query (V (Located (Trail' l V2 n))) (N (Located (Trail' l V2 n))) Crossings Source #

Eq (v n) => Eq (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

(==) :: Trail' l v n -> Trail' l v n -> Bool #

(/=) :: Trail' l v n -> Trail' l v n -> Bool #

Ord (v n) => Ord (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

compare :: Trail' l v n -> Trail' l v n -> Ordering #

(<) :: Trail' l v n -> Trail' l v n -> Bool #

(<=) :: Trail' l v n -> Trail' l v n -> Bool #

(>) :: Trail' l v n -> Trail' l v n -> Bool #

(>=) :: Trail' l v n -> Trail' l v n -> Bool #

max :: Trail' l v n -> Trail' l v n -> Trail' l v n #

min :: Trail' l v n -> Trail' l v n -> Trail' l v n #

Show (v n) => Show (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

showsPrec :: Int -> Trail' l v n -> ShowS #

show :: Trail' l v n -> String #

showList :: [Trail' l v n] -> ShowS #

(OrderedField n, Metric v) => Semigroup (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

(<>) :: Trail' Line v n -> Trail' Line v n -> Trail' Line v n #

sconcat :: NonEmpty (Trail' Line v n) -> Trail' Line v n #

stimes :: Integral b => b -> Trail' Line v n -> Trail' Line v n #

(Metric v, OrderedField n) => Monoid (Trail' Line v n) Source #

The empty trail is constantly the zero vector. Trails are composed via concatenation. Note that only lines have a monoid instance (and not loops).

Instance details

Defined in Diagrams.Trail

Methods

mempty :: Trail' Line v n #

mappend :: Trail' Line v n -> Trail' Line v n -> Trail' Line v n #

mconcat :: [Trail' Line v n] -> Trail' Line v n #

(Metric v, OrderedField n) => Enveloped (Trail' l v n) Source #

The envelope for a trail is based at the trail's start.

Instance details

Defined in Diagrams.Trail

Methods

getEnvelope :: Trail' l v n -> Envelope (V (Trail' l v n)) (N (Trail' l v n)) #

(HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

transform :: Transformation (V (Trail' l v n)) (N (Trail' l v n)) -> Trail' l v n -> Trail' l v n #

Wrapped (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

Associated Types

type Unwrapped (Trail' Line v n) #

Methods

_Wrapped' :: Iso' (Trail' Line v n) (Unwrapped (Trail' Line v n)) #

(Metric v, OrderedField n) => AsEmpty (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Empty :: Prism' (Trail' Line v n) () #

(Metric v, OrderedField n) => Reversing (Trail' l v n) Source #

Same as reverseLine or reverseLoop.

Instance details

Defined in Diagrams.Trail

Methods

reversing :: Trail' l v n -> Trail' l v n #

(Metric v, OrderedField n, Real n) => HasArcLength (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

arcLengthBounded :: N (Trail' l v n) -> Trail' l v n -> Interval (N (Trail' l v n)) Source #

arcLength :: N (Trail' l v n) -> Trail' l v n -> N (Trail' l v n) Source #

stdArcLength :: Trail' l v n -> N (Trail' l v n) Source #

arcLengthToParam :: N (Trail' l v n) -> Trail' l v n -> N (Trail' l v n) -> N (Trail' l v n) Source #

stdArcLengthToParam :: Trail' l v n -> N (Trail' l v n) -> N (Trail' l v n) Source #

(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

splitAtParam :: Trail' Line v n -> N (Trail' Line v n) -> (Trail' Line v n, Trail' Line v n) Source #

section :: Trail' Line v n -> N (Trail' Line v n) -> N (Trail' Line v n) -> Trail' Line v n Source #

reverseDomain :: Trail' Line v n -> Trail' Line v n Source #

(Metric v, OrderedField n, Real n) => EndValues (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: Trail' l v n -> Codomain (Trail' l v n) (N (Trail' l v n)) Source #

atEnd :: Trail' l v n -> Codomain (Trail' l v n) (N (Trail' l v n)) Source #

Num n => DomainBounds (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

domainLower :: Trail' l v n -> N (Trail' l v n) Source #

domainUpper :: Trail' l v n -> N (Trail' l v n) Source #

(Metric v, OrderedField n, Real n) => Parametric (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: Trail' l v n -> N (Trail' l v n) -> Codomain (Trail' l v n) (N (Trail' l v n)) Source #

(Metric v, OrderedField n) => TrailLike (Trail' Loop v n) Source #

Loops are trail-like. If given a Trail containing a line, the line will be turned into a loop using glueLine. The location is ignored.

Instance details

Defined in Diagrams.TrailLike

Methods

trailLike :: Located (Trail (V (Trail' Loop v n)) (N (Trail' Loop v n))) -> Trail' Loop v n Source #

(Metric v, OrderedField n) => TrailLike (Trail' Line v n) Source #

Lines are trail-like. If given a Trail which contains a loop, the loop will be cut with cutLoop. The location is ignored.

Instance details

Defined in Diagrams.TrailLike

Methods

trailLike :: Located (Trail (V (Trail' Line v n)) (N (Trail' Line v n))) -> Trail' Line v n Source #

ToPath (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Trail' l v n -> Path (V (Trail' l v n)) (N (Trail' l v n)) Source #

(HasLinearMap v, Metric v, OrderedField n) => Renderable (Trail' o v n) NullBackend Source # 
Instance details

Defined in Diagrams.Trail

Methods

render :: NullBackend -> Trail' o v n -> Render NullBackend (V (Trail' o v n)) (N (Trail' o v n)) #

(Metric v, Metric u, OrderedField n, r ~ Trail' l u n) => AffineMappable (Trail' l v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

amap :: AffineMap (V (Trail' l v n)) (V r) (N r) -> Trail' l v n -> r Source #

(Metric v, Metric u, OrderedField n, OrderedField m, r ~ Trail' l u m) => LinearMappable (Trail' l v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

vmap :: (Vn (Trail' l v n) -> Vn r) -> Trail' l v n -> r Source #

Rewrapped (Trail' Line v n) (Trail' Line v' n') Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n, Metric u, OrderedField n') => Cons (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Cons :: Prism (Trail' Line v n) (Trail' Line u n') (Segment Closed v n, Trail' Line v n) (Segment Closed u n', Trail' Line u n') #

(Metric v, OrderedField n, Metric u, OrderedField n') => Snoc (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Snoc :: Prism (Trail' Line v n) (Trail' Line u n') (Trail' Line v n, Segment Closed v n) (Trail' Line u n', Segment Closed u n') #

type V (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

type V (Trail' l v n) = v
type N (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

type N (Trail' l v n) = n
type Unwrapped (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

type Unwrapped (Trail' Line v n) = SegTree v n
type Codomain (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Trail

type Codomain (Trail' l v n) = v

data Loop Source #

Type tag for "loopy" trails which return to their starting point.

Instances

Instances details
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail' Loop v n)) Source #

The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1".

Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n) => TrailLike (Trail' Loop v n) Source #

Loops are trail-like. If given a Trail containing a line, the line will be turned into a loop using glueLine. The location is ignored.

Instance details

Defined in Diagrams.TrailLike

Methods

trailLike :: Located (Trail (V (Trail' Loop v n)) (N (Trail' Loop v n))) -> Trail' Loop v n Source #

data Line Source #

Type tag for trails with distinct endpoints.

Instances

Instances details
(Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n) => Parametric (GetSegment (Trail' Line v n)) Source #

Parameters less than 0 yield the first segment; parameters greater than 1 yield the last. A parameter exactly at the junction of two segments yields the second segment (i.e. the one with higher parameter values).

Instance details

Defined in Diagrams.Trail

(OrderedField n, Metric v) => Semigroup (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

(<>) :: Trail' Line v n -> Trail' Line v n -> Trail' Line v n #

sconcat :: NonEmpty (Trail' Line v n) -> Trail' Line v n #

stimes :: Integral b => b -> Trail' Line v n -> Trail' Line v n #

(Metric v, OrderedField n) => Monoid (Trail' Line v n) Source #

The empty trail is constantly the zero vector. Trails are composed via concatenation. Note that only lines have a monoid instance (and not loops).

Instance details

Defined in Diagrams.Trail

Methods

mempty :: Trail' Line v n #

mappend :: Trail' Line v n -> Trail' Line v n -> Trail' Line v n #

mconcat :: [Trail' Line v n] -> Trail' Line v n #

Wrapped (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

Associated Types

type Unwrapped (Trail' Line v n) #

Methods

_Wrapped' :: Iso' (Trail' Line v n) (Unwrapped (Trail' Line v n)) #

(Metric v, OrderedField n) => AsEmpty (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Empty :: Prism' (Trail' Line v n) () #

(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

splitAtParam :: Trail' Line v n -> N (Trail' Line v n) -> (Trail' Line v n, Trail' Line v n) Source #

section :: Trail' Line v n -> N (Trail' Line v n) -> N (Trail' Line v n) -> Trail' Line v n Source #

reverseDomain :: Trail' Line v n -> Trail' Line v n Source #

(Metric v, OrderedField n) => TrailLike (Trail' Line v n) Source #

Lines are trail-like. If given a Trail which contains a loop, the loop will be cut with cutLoop. The location is ignored.

Instance details

Defined in Diagrams.TrailLike

Methods

trailLike :: Located (Trail (V (Trail' Line v n)) (N (Trail' Line v n))) -> Trail' Line v n Source #

Rewrapped (Trail' Line v n) (Trail' Line v' n') Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n, Metric u, OrderedField n') => Cons (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Cons :: Prism (Trail' Line v n) (Trail' Line u n') (Segment Closed v n, Trail' Line v n) (Segment Closed u n', Trail' Line u n') #

(Metric v, OrderedField n, Metric u, OrderedField n') => Snoc (Trail' Line v n) (Trail' Line u n') (Segment Closed v n) (Segment Closed u n') Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Snoc :: Prism (Trail' Line v n) (Trail' Line u n') (Trail' Line v n, Segment Closed v n) (Trail' Line u n', Segment Closed u n') #

type Unwrapped (Trail' Line v n) Source # 
Instance details

Defined in Diagrams.Trail

type Unwrapped (Trail' Line v n) = SegTree v n

newtype SegTree v n Source #

A SegTree represents a sequence of closed segments, stored in a fingertree so we can easily recover various monoidal measures of the segments (number of segments, arc length, envelope...) and also easily slice and dice them according to the measures (e.g., split off the smallest number of segments from the beginning which have a combined arc length of at least 5).

Constructors

SegTree (FingerTree (SegMeasure v n) (Segment Closed v n)) 

Instances

Instances details
Eq (v n) => Eq (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

(==) :: SegTree v n -> SegTree v n -> Bool #

(/=) :: SegTree v n -> SegTree v n -> Bool #

Ord (v n) => Ord (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

compare :: SegTree v n -> SegTree v n -> Ordering #

(<) :: SegTree v n -> SegTree v n -> Bool #

(<=) :: SegTree v n -> SegTree v n -> Bool #

(>) :: SegTree v n -> SegTree v n -> Bool #

(>=) :: SegTree v n -> SegTree v n -> Bool #

max :: SegTree v n -> SegTree v n -> SegTree v n #

min :: SegTree v n -> SegTree v n -> SegTree v n #

Show (v n) => Show (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

showsPrec :: Int -> SegTree v n -> ShowS #

show :: SegTree v n -> String #

showList :: [SegTree v n] -> ShowS #

(Ord n, Floating n, Metric v) => Semigroup (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

(<>) :: SegTree v n -> SegTree v n -> SegTree v n #

sconcat :: NonEmpty (SegTree v n) -> SegTree v n #

stimes :: Integral b => b -> SegTree v n -> SegTree v n #

(Ord n, Floating n, Metric v) => Monoid (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

mempty :: SegTree v n #

mappend :: SegTree v n -> SegTree v n -> SegTree v n #

mconcat :: [SegTree v n] -> SegTree v n #

(OrderedField n, Metric v, Serialize (v n)) => Serialize (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

put :: Putter (SegTree v n) #

get :: Get (SegTree v n) #

(Floating n, Ord n, Metric v) => Transformable (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

transform :: Transformation (V (SegTree v n)) (N (SegTree v n)) -> SegTree v n -> SegTree v n #

Wrapped (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Associated Types

type Unwrapped (SegTree v n) #

Methods

_Wrapped' :: Iso' (SegTree v n) (Unwrapped (SegTree v n)) #

(Metric v, OrderedField n, Real n) => HasArcLength (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

arcLengthBounded :: N (SegTree v n) -> SegTree v n -> Interval (N (SegTree v n)) Source #

arcLength :: N (SegTree v n) -> SegTree v n -> N (SegTree v n) Source #

stdArcLength :: SegTree v n -> N (SegTree v n) Source #

arcLengthToParam :: N (SegTree v n) -> SegTree v n -> N (SegTree v n) -> N (SegTree v n) Source #

stdArcLengthToParam :: SegTree v n -> N (SegTree v n) -> N (SegTree v n) Source #

(Metric v, OrderedField n, Real n) => Sectionable (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

splitAtParam :: SegTree v n -> N (SegTree v n) -> (SegTree v n, SegTree v n) Source #

section :: SegTree v n -> N (SegTree v n) -> N (SegTree v n) -> SegTree v n Source #

reverseDomain :: SegTree v n -> SegTree v n Source #

(Metric v, OrderedField n, Real n) => EndValues (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atStart :: SegTree v n -> Codomain (SegTree v n) (N (SegTree v n)) Source #

atEnd :: SegTree v n -> Codomain (SegTree v n) (N (SegTree v n)) Source #

Num n => DomainBounds (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

domainLower :: SegTree v n -> N (SegTree v n) Source #

domainUpper :: SegTree v n -> N (SegTree v n) Source #

(Metric v, OrderedField n, Real n) => Parametric (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

atParam :: SegTree v n -> N (SegTree v n) -> Codomain (SegTree v n) (N (SegTree v n)) Source #

(Metric v, Metric u, OrderedField n, r ~ SegTree u n) => AffineMappable (SegTree v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

amap :: AffineMap (V (SegTree v n)) (V r) (N r) -> SegTree v n -> r Source #

(Metric v, Metric u, OrderedField n, OrderedField m, r ~ SegTree u m) => LinearMappable (SegTree v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

vmap :: (Vn (SegTree v n) -> Vn r) -> SegTree v n -> r Source #

(Ord n, Metric v, Floating n) => Measured (SegMeasure v n) (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

Methods

measure :: SegTree v n -> SegMeasure v n #

Rewrapped (SegTree v n) (SegTree v' n') Source # 
Instance details

Defined in Diagrams.Trail

(Metric v, OrderedField n, Metric u, OrderedField n') => Cons (SegTree v n) (SegTree u n') (Segment Closed v n) (Segment Closed u n') Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Cons :: Prism (SegTree v n) (SegTree u n') (Segment Closed v n, SegTree v n) (Segment Closed u n', SegTree u n') #

(Metric v, OrderedField n, Metric u, OrderedField n') => Snoc (SegTree v n) (SegTree u n') (Segment Closed v n) (Segment Closed u n') Source # 
Instance details

Defined in Diagrams.Trail

Methods

_Snoc :: Prism (SegTree v n) (SegTree u n') (SegTree v n, Segment Closed v n) (SegTree u n', Segment Closed u n') #

type V (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

type V (SegTree v n) = v
type N (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

type N (SegTree v n) = n
type Unwrapped (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

type Codomain (SegTree v n) Source # 
Instance details

Defined in Diagrams.Trail

type Codomain (SegTree v n) = v

trailMeasure :: (SegMeasure v n :>: m, Measured (SegMeasure v n) t) => a -> (m -> a) -> t -> a Source #

Given a default result (to be used in the case of an empty trail), and a function to map a single measure to a result, extract the given measure for a trail and use it to compute a result. Put another way, lift a function on a single measure (along with a default value) to a function on an entire trail.

numSegs :: (Num c, Measured (SegMeasure v n) a) => a -> c Source #

Compute the number of segments of anything measured by SegMeasure (e.g. SegMeasure itself, Segment, SegTree, Trails...)

offset :: (OrderedField n, Metric v, Measured (SegMeasure v n) t) => t -> v n Source #

Compute the total offset of anything measured by SegMeasure.

withTrail' :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail' l v n -> r Source #

A generic eliminator for Trail', taking functions specifying what to do in the case of a line or a loop.

getSegment :: t -> GetSegment t Source #

Create a GetSegment wrapper around a trail, after which you can call atParam, atStart, or atEnd to extract a segment.

_Line :: Prism' (Trail v n) (Trail' Line v n) Source #

Prism onto a Line.

_Loop :: Prism' (Trail v n) (Trail' Loop v n) Source #

Prism onto a Loop.

_LocLine :: Prism' (Located (Trail v n)) (Located (Trail' Line v n)) Source #

Prism onto a Located Line.

_LocLoop :: Prism' (Located (Trail v n)) (Located (Trail' Loop v n)) Source #

Prism onto a Located Loop.

withTrail :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail v n -> r Source #

A generic eliminator for Trail, taking functions specifying what to do in the case of a line or a loop.

onTrail :: (Trail' Line v n -> Trail' l1 v n) -> (Trail' Loop v n -> Trail' l2 v n) -> Trail v n -> Trail v n Source #

Modify a Trail, specifying two separate transformations for the cases of a line or a loop.

withLine :: (Metric v, OrderedField n) => (Trail' Line v n -> r) -> Trail v n -> r Source #

An eliminator for Trail based on eliminating lines: if the trail is a line, the given function is applied; if it is a loop, it is first converted to a line with cutLoop. That is,

withLine f === withTrail f (f . cutLoop)

onLine :: (Metric v, OrderedField n) => (Trail' Line v n -> Trail' Line v n) -> Trail v n -> Trail v n Source #

Modify a Trail by specifying a transformation on lines. If the trail is a line, the transformation will be applied directly. If it is a loop, it will first be cut using cutLoop, the transformation applied, and then glued back into a loop with glueLine. That is,

  onLine f === onTrail f (glueLine . f . cutLoop)
  

Note that there is no corresponding onLoop function, because there is no nice way in general to convert a line into a loop, operate on it, and then convert back.

wrapTrail :: Trail' l v n -> Trail v n Source #

Convert a Trail' into a Trail, hiding the type-level distinction between lines and loops.

wrapLine :: Trail' Line v n -> Trail v n Source #

Convert a line into a Trail. This is the same as wrapTrail, but with a more specific type, which can occasionally be convenient for fixing the type of a polymorphic expression.

wrapLoop :: Trail' Loop v n -> Trail v n Source #

Convert a loop into a Trail. This is the same as wrapTrail, but with a more specific type, which can occasionally be convenient for fixing the type of a polymorphic expression.

emptyLine :: (Metric v, OrderedField n) => Trail' Line v n Source #

The empty line, which is the identity for concatenation of lines.

emptyTrail :: (Metric v, OrderedField n) => Trail v n Source #

A wrapped variant of emptyLine.

lineFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail' Line v n Source #

Construct a line from a list of closed segments.

loopFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Segment Open v n -> Trail' Loop v n Source #

Construct a loop from a list of closed segments and an open segment that completes the loop.

trailFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail v n Source #

trailFromSegments === wrapTrail . lineFromSegments, for conveniently constructing a Trail instead of a Trail'.

lineFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail' Line v n Source #

Construct a line containing only linear segments from a list of vectors, where each vector represents the offset from one vertex to the next. See also fromOffsets.

import Diagrams.Coordinates
lineFromOffsetsEx = strokeLine $ lineFromOffsets [ 2 ^& 1, 2 ^& (-1), 2 ^& 0.5 ]

trailFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail v n Source #

trailFromOffsets === wrapTrail . lineFromOffsets, for conveniently constructing a Trail instead of a Trail' Line.

lineFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail' Line v n Source #

Construct a line containing only linear segments from a list of vertices. Note that only the relative offsets between the vertices matters; the information about their absolute position will be discarded. That is, for all vectors v,

lineFromVertices === lineFromVertices . translate v

If you want to retain the position information, you should instead use the more general fromVertices function to construct, say, a Located (Trail' Line v) or a Located (Trail v).

import Diagrams.Coordinates
lineFromVerticesEx = pad 1.1 . centerXY . strokeLine
  $ lineFromVertices [origin, 0 ^& 1, 1 ^& 2, 5 ^& 1]

trailFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail v n Source #

trailFromVertices === wrapTrail . lineFromVertices, for conveniently constructing a Trail instead of a Trail' Line.

glueLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Loop v n Source #

Make a line into a loop by "gluing" the endpoint to the starting point. In particular, the offset of the final segment is modified so that it ends at the starting point of the entire trail. Typically, you would first construct a line which you know happens to end where it starts, and then call glueLine to turn it into a loop.

glueLineEx = pad 1.1 . hsep 1
  $ [almostClosed # strokeLine, almostClosed # glueLine # strokeLoop]

almostClosed :: Trail' Line V2 Double
almostClosed = fromOffsets $ map r2 [(2, -1), (-3, -0.5), (-2, 1), (1, 0.5)]

glueLine is left inverse to cutLoop, that is,

  glueLine . cutLoop === id
  

glueTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n Source #

glueTrail is a variant of glueLine which works on Trails. It performs glueLine on lines and is the identity on loops.

closeLine :: Trail' Line v n -> Trail' Loop v n Source #

Make a line into a loop by adding a new linear segment from the line's end to its start.

closeLine does not have any particularly nice theoretical properties, but can be useful e.g. when you want to make a closed polygon out of a list of points where the initial point is not repeated at the end. To use glueLine, one would first have to duplicate the initial vertex, like

glueLine . lineFromVertices $ ps ++ [head ps]

Using closeLine, however, one can simply

closeLine . lineFromVertices $ ps

closeLineEx = pad 1.1 . centerXY . hcat' (with & sep .~ 1)
  $ [almostClosed # strokeLine, almostClosed # closeLine # strokeLoop]

closeTrail :: Trail v n -> Trail v n Source #

closeTrail is a variant of closeLine for Trail, which performs closeLine on lines and is the identity on loops.

cutLoop :: forall v n. (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Line v n Source #

Turn a loop into a line by "cutting" it at the common start/end point, resulting in a line which just happens to start and end at the same place.

cutLoop is right inverse to glueLine, that is,

  glueLine . cutLoop === id
  

cutTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n Source #

cutTrail is a variant of cutLoop for Trail; it is the is the identity on lines and performs cutLoop on loops.

isLineEmpty :: (Metric v, OrderedField n) => Trail' Line v n -> Bool Source #

Test whether a line is empty.

isTrailEmpty :: (Metric v, OrderedField n) => Trail v n -> Bool Source #

Test whether a trail is empty. Note that loops are never empty.

isLine :: Trail v n -> Bool Source #

Determine whether a trail is a line.

isLoop :: Trail v n -> Bool Source #

Determine whether a trail is a loop.

lineSegments :: Trail' Line v n -> [Segment Closed v n] Source #

Extract the segments comprising a line.

onLineSegments :: (Metric v, OrderedField n) => ([Segment Closed v n] -> [Segment Closed v n]) -> Trail' Line v n -> Trail' Line v n Source #

Modify a line by applying a function to its list of segments.

loopSegments :: Trail' Loop v n -> ([Segment Closed v n], Segment Open v n) Source #

Extract the segments comprising a loop: a list of closed segments, and one final open segment.

trailSegments :: (Metric v, OrderedField n) => Trail v n -> [Segment Closed v n] Source #

Extract the segments of a trail. If the trail is a loop it will first have cutLoop applied.

trailOffsets :: (Metric v, OrderedField n) => Trail v n -> [v n] Source #

Extract the offsets of the segments of a trail.

trailOffset :: (Metric v, OrderedField n) => Trail v n -> v n Source #

Compute the offset from the start of a trail to the end. Satisfies

  trailOffset === sumV . trailOffsets
  

but is more efficient.

trailOffsetEx = (strokeLine almostClosed <> showOffset) # centerXY # pad 1.1
  where showOffset = fromOffsets [trailOffset (wrapLine almostClosed)]
                   # strokeP # lc red

lineOffsets :: Trail' Line v n -> [v n] Source #

Extract the offsets of the segments of a line.

loopOffsets :: (Metric v, OrderedField n) => Trail' Loop v n -> [v n] Source #

Extract the offsets of the segments of a loop.

lineOffset :: (Metric v, OrderedField n) => Trail' Line v n -> v n Source #

Compute the offset from the start of a line to the end. (Note, there is no corresponding loopOffset function because by definition it would be constantly zero.)

trailVertices' :: (Metric v, OrderedField n) => n -> Located (Trail v n) -> [Point v n] Source #

Extract the vertices of a concretely located trail. Here a vertex is defined as a non-differentiable point on the trail, i.e. a sharp corner. (Vertices are thus a subset of the places where segments join; if you want all joins between segments, see trailPoints.) The tolerance determines how close the tangents of two segments must be at their endpoints to consider the transition point to be differentiable.

Note that for loops, the starting vertex will not be repeated at the end. If you want this behavior, you can use cutTrail to make the loop into a line first, which happens to repeat the same vertex at the start and end, e.g. with trailVertices . mapLoc cutTrail.

It does not make sense to ask for the vertices of a Trail by itself; if you want the vertices of a trail with the first vertex at, say, the origin, you can use trailVertices . (`at` origin).

trailVertices :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n] Source #

Like trailVertices', with a default tolerance.

lineVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Line v n) -> [Point v n] Source #

Extract the vertices of a concretely located line. See trailVertices for more information.

lineVertices :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> [Point v n] Source #

Like lineVertices', with a default tolerance.

loopVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Loop v n) -> [Point v n] Source #

Extract the vertices of a concretely located loop. Note that the initial vertex is not repeated at the end. See trailVertices for more information.

loopVertices :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> [Point v n] Source #

Same as loopVertices', with a default tolerance.

fixTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> [FixedSegment v n] Source #

Convert a concretely located trail into a list of fixed segments. unfixTrail is almost its left inverse.

unfixTrail :: (Metric v, Ord n, Floating n) => [FixedSegment v n] -> Located (Trail v n) Source #

Convert a list of fixed segments into a located trail. Note that this may lose information: it throws away the locations of all but the first FixedSegment. This does not matter precisely when each FixedSegment begins where the previous one ends.

This is almost left inverse to fixTrail, that is, unfixTrail . fixTrail == id, except for the fact that unfixTrail will never yield a Loop. In the case of a loop, we instead have glueTrail . unfixTrail . fixTrail == id. On the other hand, it is not the case that fixTrail . unfixTrail == id since unfixTrail may lose information.

trailLocSegments :: (Metric v, OrderedField n) => Located (Trail v n) -> [Located (Segment Closed v n)] Source #

Convert a concretely located trail into a list of located segments.

reverseTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n Source #

Reverse a trail. Semantically, if a trail given by a function t from [0,1] to vectors, then the reverse of t is given by t'(s) = t(1-s). reverseTrail is an involution, that is,

  reverseTrail . reverseTrail === id
  

reverseLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Located (Trail v n) Source #

Reverse a concretely located trail. The endpoint of the original trail becomes the starting point of the reversed trail, so the original and reversed trails comprise exactly the same set of points. reverseLocTrail is an involution, i.e.

  reverseLocTrail . reverseLocTrail === id
  

reverseLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Line v n Source #

Reverse a line. See reverseTrail.

reverseLocLine :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> Located (Trail' Line v n) Source #

Reverse a concretely located line. See reverseLocTrail.

reverseLoop :: (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Loop v n Source #

Reverse a loop. See reverseTrail.

reverseLocLoop :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> Located (Trail' Loop v n) Source #

Reverse a concretely located loop. See reverseLocTrail. Note that this is guaranteed to preserve the location.

Parametrization of segments and trails.

Adjusting the length of parameterized objects.

Computing tangent and normal vectors of segments and trails.

Trail-like things.

Paths.

class ToPath t where Source #

Type class for things that can be converted to a Path.

Note that this class is very different from TrailLike. TrailLike is usually the result of a library function to give you a convenient, polymorphic result (Path, Diagram etc.).

Methods

toPath :: (Metric (V t), OrderedField (N t)) => t -> Path (V t) (N t) Source #

toPath takes something that can be converted to Path and returns the Path.

Instances

Instances details
ToPath a => ToPath [a] Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: [a] -> Path (V [a]) (N [a]) Source #

ToPath (Located [Segment Closed v n]) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located [Segment Closed v n] -> Path (V (Located [Segment Closed v n])) (N (Located [Segment Closed v n])) Source #

ToPath (Located (Segment Closed v n)) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located (Segment Closed v n) -> Path (V (Located (Segment Closed v n))) (N (Located (Segment Closed v n))) Source #

ToPath (Located (Trail v n)) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located (Trail v n) -> Path (V (Located (Trail v n))) (N (Located (Trail v n))) Source #

ToPath (Located (Trail' l v n)) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located (Trail' l v n) -> Path (V (Located (Trail' l v n))) (N (Located (Trail' l v n))) Source #

ToPath (FixedSegment v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: FixedSegment v n -> Path (V (FixedSegment v n)) (N (FixedSegment v n)) Source #

ToPath (Trail v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Trail v n -> Path (V (Trail v n)) (N (Trail v n)) Source #

ToPath (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Path v n -> Path (V (Path v n)) (N (Path v n)) Source #

ToPath (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Trail' l v n -> Path (V (Trail' l v n)) (N (Trail' l v n)) Source #

newtype Path v n Source #

A path is a (possibly empty) list of Located Trails. Hence, unlike trails, paths are not translationally invariant, and they form a monoid under superposition (placing one path on top of another) rather than concatenation.

Constructors

Path [Located (Trail v n)] 

Instances

Instances details
Eq (v n) => Eq (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

(==) :: Path v n -> Path v n -> Bool #

(/=) :: Path v n -> Path v n -> Bool #

Ord (v n) => Ord (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

compare :: Path v n -> Path v n -> Ordering #

(<) :: Path v n -> Path v n -> Bool #

(<=) :: Path v n -> Path v n -> Bool #

(>) :: Path v n -> Path v n -> Bool #

(>=) :: Path v n -> Path v n -> Bool #

max :: Path v n -> Path v n -> Path v n #

min :: Path v n -> Path v n -> Path v n #

Show (v n) => Show (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

showsPrec :: Int -> Path v n -> ShowS #

show :: Path v n -> String #

showList :: [Path v n] -> ShowS #

Generic (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Associated Types

type Rep (Path v n) :: Type -> Type #

Methods

from :: Path v n -> Rep (Path v n) x #

to :: Rep (Path v n) x -> Path v n #

Semigroup (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

(<>) :: Path v n -> Path v n -> Path v n #

sconcat :: NonEmpty (Path v n) -> Path v n #

stimes :: Integral b => b -> Path v n -> Path v n #

Monoid (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

mempty :: Path v n #

mappend :: Path v n -> Path v n -> Path v n #

mconcat :: [Path v n] -> Path v n #

(OrderedField n, Metric v, Serialize (v n), Serialize (V (v n) (N (v n)))) => Serialize (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

put :: Putter (Path v n) #

get :: Get (Path v n) #

(Metric v, OrderedField n) => Juxtaposable (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

juxtapose :: Vn (Path v n) -> Path v n -> Path v n -> Path v n #

(Metric v, OrderedField n) => Enveloped (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

getEnvelope :: Path v n -> Envelope (V (Path v n)) (N (Path v n)) #

RealFloat n => Traced (Path V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getTrace :: Path V2 n -> Trace (V (Path V2 n)) (N (Path V2 n)) #

(HasLinearMap v, Metric v, OrderedField n) => Transformable (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

transform :: Transformation (V (Path v n)) (N (Path v n)) -> Path v n -> Path v n #

(Additive v, Num n) => HasOrigin (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

moveOriginTo :: Point (V (Path v n)) (N (Path v n)) -> Path v n -> Path v n #

Wrapped (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Associated Types

type Unwrapped (Path v n) #

Methods

_Wrapped' :: Iso' (Path v n) (Unwrapped (Path v n)) #

AsEmpty (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

_Empty :: Prism' (Path v n) () #

(Metric v, OrderedField n) => Reversing (Path v n) Source #

Same as reversePath.

Instance details

Defined in Diagrams.Path

Methods

reversing :: Path v n -> Path v n #

(Metric v, OrderedField n) => Alignable (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

alignBy' :: (InSpace v0 n0 (Path v n), Fractional n0, HasOrigin (Path v n)) => (v0 n0 -> Path v n -> Point v0 n0) -> v0 n0 -> n0 -> Path v n -> Path v n Source #

defaultBoundary :: (V (Path v n) ~ v0, N (Path v n) ~ n0) => v0 n0 -> Path v n -> Point v0 n0 Source #

alignBy :: (InSpace v0 n0 (Path v n), Fractional n0, HasOrigin (Path v n)) => v0 n0 -> n0 -> Path v n -> Path v n Source #

(Metric v, OrderedField n) => TrailLike (Path v n) Source #

Paths are trail-like; a trail can be used to construct a singleton path.

Instance details

Defined in Diagrams.Path

Methods

trailLike :: Located (Trail (V (Path v n)) (N (Path v n))) -> Path v n Source #

ToPath (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Path v n -> Path (V (Path v n)) (N (Path v n)) Source #

(HasLinearMap v, Metric v, OrderedField n) => Renderable (Path v n) NullBackend Source # 
Instance details

Defined in Diagrams.Path

Methods

render :: NullBackend -> Path v n -> Render NullBackend (V (Path v n)) (N (Path v n)) #

RealFloat n => HasQuery (Path V2 n) Crossings Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getQuery :: Path V2 n -> Query (V (Path V2 n)) (N (Path V2 n)) Crossings Source #

(Metric v, Metric u, OrderedField n, r ~ Path u n) => AffineMappable (Path v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

amap :: AffineMap (V (Path v n)) (V r) (N r) -> Path v n -> r Source #

(Metric v, Metric u, OrderedField n, OrderedField m, r ~ Path u m) => LinearMappable (Path v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

vmap :: (Vn (Path v n) -> Vn r) -> Path v n -> r Source #

(Metric v, Metric u, OrderedField n, r ~ Path u n) => Deformable (Path v n) r Source # 
Instance details

Defined in Diagrams.Deform

Methods

deform' :: N (Path v n) -> Deformation (V (Path v n)) (V r) (N (Path v n)) -> Path v n -> r Source #

deform :: Deformation (V (Path v n)) (V r) (N (Path v n)) -> Path v n -> r Source #

Rewrapped (Path v n) (Path v' n') Source # 
Instance details

Defined in Diagrams.Path

Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

each :: Traversal (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) #

Cons (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

_Cons :: Prism (Path v n) (Path v' n') (Located (Trail v n), Path v n) (Located (Trail v' n'), Path v' n') #

Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

_Snoc :: Prism (Path v n) (Path v' n') (Path v n, Located (Trail v n)) (Path v' n', Located (Trail v' n')) #

type Rep (Path v n) Source # 
Instance details

Defined in Diagrams.Path

type Rep (Path v n) = D1 ('MetaData "Path" "Diagrams.Path" "diagrams-lib-1.4.4-LFME2FJCG1UId7DRx5kBjb" 'True) (C1 ('MetaCons "Path" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Located (Trail v n)])))
type V (Path v n) Source # 
Instance details

Defined in Diagrams.Path

type V (Path v n) = v
type N (Path v n) Source # 
Instance details

Defined in Diagrams.Path

type N (Path v n) = n
type Unwrapped (Path v n) Source # 
Instance details

Defined in Diagrams.Path

type Unwrapped (Path v n) = [Located (Trail v n)]

pathTrails :: Path v n -> [Located (Trail v n)] Source #

Extract the located trails making up a Path.

pathFromTrail :: (Metric v, OrderedField n) => Trail v n -> Path v n Source #

Convert a trail to a path beginning at the origin.

pathFromTrailAt :: (Metric v, OrderedField n) => Trail v n -> Point v n -> Path v n Source #

Convert a trail to a path with a particular starting point.

pathFromLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Path v n Source #

Convert a located trail to a singleton path. This is equivalent to trailLike, but provided with a more specific name and type for convenience.

pathVertices' :: (Metric v, OrderedField n) => n -> Path v n -> [[Point v n]] Source #

Extract the vertices of a path, resulting in a separate list of vertices for each component trail. Here a vertex is defined as a non-differentiable point on the trail, i.e. a sharp corner. (Vertices are thus a subset of the places where segments join; if you want all joins between segments, see pathPoints.) The tolerance determines how close the tangents of two segments must be at their endpoints to consider the transition point to be differentiable. See trailVertices for more information.

pathVertices :: (Metric v, OrderedField n) => Path v n -> [[Point v n]] Source #

Like pathVertices', with a default tolerance.

pathOffsets :: (Metric v, OrderedField n) => Path v n -> [v n] Source #

Compute the total offset of each trail comprising a path (see trailOffset).

pathCentroid :: (Metric v, OrderedField n) => Path v n -> Point v n Source #

Compute the centroid of a path (i.e. the average location of its vertices; see pathVertices).

pathLocSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Segment Closed v n)]] Source #

Convert a path into a list of lists of located segments.

fixPath :: (Metric v, OrderedField n) => Path v n -> [[FixedSegment v n]] Source #

Convert a path into a list of lists of FixedSegments.

explodePath :: (V t ~ v, N t ~ n, TrailLike t) => Path v n -> [[t]] Source #

"Explode" a path by exploding every component trail (see explodeTrail).

partitionPath :: (Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n) Source #

Partition a path into two paths based on a predicate on trails: the first containing all the trails for which the predicate returns True, and the second containing the remaining trails.

scalePath :: (HasLinearMap v, Metric v, OrderedField n) => n -> Path v n -> Path v n Source #

Scale a path using its centroid (see pathCentroid) as the base point for the scale.

reversePath :: (Metric v, OrderedField n) => Path v n -> Path v n Source #

Reverse all the component trails of a path.

Cubic splines.

Some additional transformation-related functions, like conjugation of transformations.

Projective transformations and other deformations lacking an inverse.

Giving names to subdiagrams and later retrieving subdiagrams by name.

Envelopes, aka functional bounding regions.

Traces, aka embedded raytracers, for finding points on the boundary of a diagram.

A query is a function that maps points in a vector space to values in some monoid; they can be used to annotate the points of a diagram with some values.

Utilities for working with points.

Utilities for working with size.

Angles

Convenience infix operators for working with coordinates.

Directions, distinguished from angles or vectors

data Direction v n Source #

A vector is described by a Direction and a magnitude. So we can think of a Direction as a vector that has forgotten its magnitude. Directions can be used with fromDirection and the lenses provided by its instances.

Instances

Instances details
Functor v => Functor (Direction v) Source # 
Instance details

Defined in Diagrams.Direction

Methods

fmap :: (a -> b) -> Direction v a -> Direction v b #

(<$) :: a -> Direction v b -> Direction v a #

HasPhi v => HasPhi (Direction v) Source # 
Instance details

Defined in Diagrams.Direction

Methods

_phi :: RealFloat n => Lens' (Direction v n) (Angle n) Source #

HasTheta v => HasTheta (Direction v) Source # 
Instance details

Defined in Diagrams.Direction

Methods

_theta :: RealFloat n => Lens' (Direction v n) (Angle n) Source #

Eq (v n) => Eq (Direction v n) Source # 
Instance details

Defined in Diagrams.Direction

Methods

(==) :: Direction v n -> Direction v n -> Bool #

(/=) :: Direction v n -> Direction v n -> Bool #

Ord (v n) => Ord (Direction v n) Source # 
Instance details

Defined in Diagrams.Direction

Methods

compare :: Direction v n -> Direction v n -> Ordering #

(<) :: Direction v n -> Direction v n -> Bool #

(<=) :: Direction v n -> Direction v n -> Bool #

(>) :: Direction v n -> Direction v n -> Bool #

(>=) :: Direction v n -> Direction v n -> Bool #

max :: Direction v n -> Direction v n -> Direction v n #

min :: Direction v n -> Direction v n -> Direction v n #

Read (v n) => Read (Direction v n) Source # 
Instance details

Defined in Diagrams.Direction

Show (v n) => Show (Direction v n) Source # 
Instance details

Defined in Diagrams.Direction

Methods

showsPrec :: Int -> Direction v n -> ShowS #

show :: Direction v n -> String #

showList :: [Direction v n] -> ShowS #

(V (v n) ~ v, N (v n) ~ n, Transformable (v n)) => Transformable (Direction v n) Source # 
Instance details

Defined in Diagrams.Direction

Methods

transform :: Transformation (V (Direction v n)) (N (Direction v n)) -> Direction v n -> Direction v n #

type V (Direction v n) Source # 
Instance details

Defined in Diagrams.Direction

type V (Direction v n) = v
type N (Direction v n) Source # 
Instance details

Defined in Diagrams.Direction

type N (Direction v n) = n

_Dir :: Iso' (Direction v n) (v n) Source #

_Dir is provided to allow efficient implementations of functions in particular vector-spaces, but should be used with care as it exposes too much information.

direction :: v n -> Direction v n Source #

direction v is the direction in which v points. Returns an unspecified value when given the zero vector as input.

fromDirection :: (Metric v, Floating n) => Direction v n -> v n Source #

fromDirection d is the unit vector in the direction d.

fromDir :: (Metric v, Floating n) => Direction v n -> v n Source #

Synonym for fromDirection.

angleBetweenDirs :: (Metric v, Floating n, Ord n) => Direction v n -> Direction v n -> Angle n Source #

compute the positive angle between the two directions in their common plane

dirBetween :: (Additive v, Num n) => Point v n -> Point v n -> Direction v n Source #

dirBetween p q returns the direction from p to q.

A wide range of things (shapes, transformations, combinators) specific to creating two-dimensional diagrams.

Extra things for three-dimensional diagrams.

Tools for making animations.

Various utility definitions.