diagrams-lib-1.4.2.3: Embedded domain-specific language for declarative graphics

Copyright(c) 2013-2015 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Trail

Contents

Description

This module defines trails, translationally invariant paths through space. Trails form a central part of the diagrams-lib API, so the documentation for this module merits careful study.

Related modules include:

Synopsis

Type definitions

Lines and loops

data Trail' l v n where #

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
(Metric v, OrderedField n) => Reversing (Located (Trail' l v n)) #

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)) # 
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))) #

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

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

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

(Parametric (GetSegment (Trail' c v n)), Additive v, Num n) => Parametric (Tangent (Trail' c v n)) # 
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))) #

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

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)) #

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)) # 
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))) #

RealFloat n => HasQuery (Located (Trail' l V2 n)) Crossings # 
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 #

Eq (v n) => Eq (Trail' l v n) # 
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) # 
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) # 
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) # 
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) #

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) #

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

Defined in Diagrams.Trail

Associated Types

type Unwrapped (Trail' Line v n) :: Type #

Methods

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

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

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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

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

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

(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) # 
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) #

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

Methods

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

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

(Metric v, OrderedField n, Real n) => Parametric (Trail' l v n) # 
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)) #

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

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 #

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

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 #

ToPath (Trail' l v n) # 
Instance details

Defined in Diagrams.Path

Methods

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

(HasLinearMap v, Metric v, OrderedField n) => Renderable (Trail' o v n) NullBackend # 
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 # 
Instance details

Defined in Diagrams.LinearMap

Methods

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

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

Defined in Diagrams.LinearMap

Methods

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

Rewrapped (Trail' Line v n) (Trail' Line v' n') # 
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') # 
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') # 
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) # 
Instance details

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

type Codomain (Trail' l v n) = v

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

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
  

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

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]

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

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
  

Generic trails

data Trail v n where #

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
(Metric v, OrderedField n) => Reversing (Located (Trail v n)) #

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

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

Methods

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

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

(Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) # 
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))) #

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) # 
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))) #

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

Defined in Diagrams.Path

Methods

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

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

Defined in Diagrams.TwoD.Path

Methods

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

(Metric v, Metric u, OrderedField n, r ~ Located (Trail u n)) => Deformable (Located (Trail v n)) r # 
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 #

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

Eq (v n) => Eq (Trail v n) # 
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) # 
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) # 
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) #

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) #

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

Defined in Diagrams.Trail

Associated Types

type Unwrapped (Trail v n) :: Type #

Methods

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

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

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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

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

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

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

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) #

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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 #

ToPath (Trail v n) # 
Instance details

Defined in Diagrams.Path

Methods

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

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

Defined in Diagrams.LinearMap

Methods

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

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

Defined in Diagrams.LinearMap

Methods

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

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

Defined in Diagrams.Trail

Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) # 
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')) # 
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')) # 
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) # 
Instance details

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

type N (Trail v n) = n
type Unwrapped (Trail v n) # 
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) # 
Instance details

Defined in Diagrams.Trail

type Codomain (Trail v n) = v

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

Prism onto a Line.

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

Prism onto a Loop.

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

Prism onto a Located Line.

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

Prism onto a Located Loop.

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

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

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

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 #

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.

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

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

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

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.

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

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

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

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

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

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

Constructing trails

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

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

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

A wrapped variant of emptyLine.

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

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 #

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

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

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 #

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

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

Construct a line from a list of closed segments.

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

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

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

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

Eliminating trails

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

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

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

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

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

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)

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

Test whether a line is empty.

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

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

isLine :: Trail v n -> Bool #

Determine whether a trail is a line.

isLoop :: Trail v n -> Bool #

Determine whether a trail is a loop.

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

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

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

Extract the segments comprising a line.

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

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

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

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

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

Extract the offsets of the segments of a trail.

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

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] #

Extract the offsets of the segments of a line.

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

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.)

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

Extract the offsets of the segments of a loop.

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

Extract the points of a concretely located trail, i.e. the points where one segment ends and the next begins. Note that for loops, the starting point 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 point at the start and end, e.g. with trailPoints . mapLoc cutTrail.

Note that it does not make sense to ask for the points of a Trail by itself; if you want the points of a trail with the first point at, say, the origin, you can use trailPoints . (`at` origin).

This function allows you "observe" the fact that trails are implemented as lists of segments, which may be problematic if we want to think of trails as parametric vector functions. This also means that the behavior of this function may not be stable under future changes to the implementation of trails. For an unproblematic version which only yields vertices at which there is a sharp corner, excluding points where the trail is differentiable, see trailVertices.

This function is not re-exported from Diagrams.Prelude; to use it, import Diagrams.Trail.

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

Extract the segment join points of a concretely located line. See trailPoints for more information.

This function allows you "observe" the fact that lines are implemented as lists of segments, which may be problematic if we want to think of lines as parametric vector functions. This also means that the behavior of this function may not be stable under future changes to the implementation of trails. For an unproblematic version which only yields vertices at which there is a sharp corner, excluding points where the trail is differentiable, see lineVertices.

This function is not re-exported from Diagrams.Prelude; to use it, import Diagrams.Trail.

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

Extract the segment join points of a concretely located loop. Note that the initial vertex is not repeated at the end. See trailPoints for more information.

This function allows you "observe" the fact that lines are implemented as lists of segments, which may be problematic if we want to think of lines as parametric vector functions. This also means that the behavior of this function may not be stable under future changes to the implementation of trails. For an unproblematic version which only yields vertices at which there is a sharp corner, excluding points where the trail is differentiable, see lineVertices.

This function is not re-exported from Diagrams.Prelude; to use it, import Diagrams.Trail.

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

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).

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

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

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

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

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

Like trailVertices', with a default tolerance.

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

Like lineVertices', with a default tolerance.

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

Same as loopVertices', with a default tolerance.

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

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

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

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) #

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.

Modifying trails

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

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) #

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 #

Reverse a line. See reverseTrail.

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

Reverse a concretely located line. See reverseLocTrail.

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

Reverse a loop. See reverseTrail.

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

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

Internals

Most users of diagrams should not need to use anything in this section directly, but they are exported on the principle that we can't forsee what uses people might have for them.

Type tags

data Line #

Type tag for trails with distinct endpoints.

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

Defined in Diagrams.Trail

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

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) # 
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) #

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

Defined in Diagrams.Trail

Associated Types

type Unwrapped (Trail' Line v n) :: Type #

Methods

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

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

Defined in Diagrams.Trail

Methods

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

(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) # 
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) #

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

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

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

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 #

Rewrapped (Trail' Line v n) (Trail' Line v' n') # 
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') # 
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') # 
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) # 
Instance details

Defined in Diagrams.Trail

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

data Loop #

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

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

Defined in Diagrams.Trail

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

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) #

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 #

Segment trees

newtype SegTree v n #

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
Eq (v n) => Eq (SegTree v n) # 
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) # 
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) # 
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) # 
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 #

(Floating n, Ord n, Metric v) => Monoid (SegTree v n) # 
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) # 
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) # 
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) # 
Instance details

Defined in Diagrams.Trail

Associated Types

type Unwrapped (SegTree v n) :: Type #

Methods

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

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

Defined in Diagrams.Trail

Methods

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

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

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

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

Methods

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

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

Defined in Diagrams.LinearMap

Methods

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

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

Defined in Diagrams.LinearMap

Methods

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

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

Defined in Diagrams.Trail

Methods

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

Rewrapped (SegTree v n) (SegTree v' n') # 
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') # 
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') # 
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) # 
Instance details

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

type Codomain (SegTree v n) # 
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 #

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 #

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 #

Compute the total offset of anything measured by SegMeasure.

Extracting segments

newtype GetSegment t #

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
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail v n)) # 
Instance details

Defined in Diagrams.Trail

Methods

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

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

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

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) # 
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))) #

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

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)) #

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

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

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

Defined in Diagrams.Trail

getSegment :: t -> GetSegment t #

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

newtype GetSegmentCodomain v n #

Constructors

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

Orphan instances

(Measured m a, Transformable a) => Transformable (FingerTree m a) # 
Instance details

Methods

transform :: Transformation (V (FingerTree m a)) (N (FingerTree m a)) -> FingerTree m a -> FingerTree m a #

(Measured m a, Measured n b) => Cons (FingerTree m a) (FingerTree n b) a b # 
Instance details

Methods

_Cons :: Prism (FingerTree m a) (FingerTree n b) (a, FingerTree m a) (b, FingerTree n b) #

(Measured m a, Measured n b) => Snoc (FingerTree m a) (FingerTree n b) a b # 
Instance details

Methods

_Snoc :: Prism (FingerTree m a) (FingerTree n b) (FingerTree m a, a) (FingerTree n b, b) #