Copyright | (c) 2013-2015 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
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:
- The
TrailLike
class (Diagrams.TrailLike) exposes a generic API for building a wide range of things out of trails. Path
s (Diagrams.Path) are collections ofLocated
(Diagrams.Located) trails.- Trails are composed of
Segment
s (see Diagrams.Segment), though most users should not need to work with segments directly.
- data Trail' l v n where
- glueLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Loop v n
- closeLine :: Trail' Line v n -> Trail' Loop v n
- cutLoop :: forall v n. (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Line v n
- data Trail v n where
- _Line :: Prism' (Trail v n) (Trail' Line v n)
- _Loop :: Prism' (Trail v n) (Trail' Loop v n)
- _LocLine :: Prism' (Located (Trail v n)) (Located (Trail' Line v n))
- _LocLoop :: Prism' (Located (Trail v n)) (Located (Trail' Loop v n))
- wrapTrail :: Trail' l v n -> Trail v n
- wrapLine :: Trail' Line v n -> Trail v n
- wrapLoop :: Trail' Loop v n -> Trail v n
- onTrail :: (Trail' Line v n -> Trail' l1 v n) -> (Trail' Loop v n -> Trail' l2 v n) -> Trail v n -> Trail v n
- onLine :: (Metric v, OrderedField n) => (Trail' Line v n -> Trail' Line v n) -> Trail v n -> Trail v n
- glueTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- closeTrail :: Trail v n -> Trail v n
- cutTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- emptyLine :: (Metric v, OrderedField n) => Trail' Line v n
- emptyTrail :: (Metric v, OrderedField n) => Trail v n
- lineFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail' Line v n
- trailFromVertices :: (Metric v, OrderedField n) => [Point v n] -> Trail v n
- lineFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail' Line v n
- trailFromOffsets :: (Metric v, OrderedField n) => [v n] -> Trail v n
- lineFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail' Line v n
- trailFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail v n
- loopFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Segment Open v n -> Trail' Loop v n
- withTrail' :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail' l v n -> r
- withTrail :: (Trail' Line v n -> r) -> (Trail' Loop v n -> r) -> Trail v n -> r
- withLine :: (Metric v, OrderedField n) => (Trail' Line v n -> r) -> Trail v n -> r
- isLineEmpty :: (Metric v, OrderedField n) => Trail' Line v n -> Bool
- isTrailEmpty :: (Metric v, OrderedField n) => Trail v n -> Bool
- isLine :: Trail v n -> Bool
- isLoop :: Trail v n -> Bool
- trailSegments :: (Metric v, OrderedField n) => Trail v n -> [Segment Closed v n]
- lineSegments :: Trail' Line v n -> [Segment Closed v n]
- loopSegments :: Trail' Loop v n -> ([Segment Closed v n], Segment Open v n)
- onLineSegments :: (Metric v, OrderedField n) => ([Segment Closed v n] -> [Segment Closed v n]) -> Trail' Line v n -> Trail' Line v n
- trailOffsets :: (Metric v, OrderedField n) => Trail v n -> [v n]
- trailOffset :: (Metric v, OrderedField n) => Trail v n -> v n
- lineOffsets :: Trail' Line v n -> [v n]
- lineOffset :: (Metric v, OrderedField n) => Trail' Line v n -> v n
- loopOffsets :: (Metric v, OrderedField n) => Trail' Loop v n -> [v n]
- trailPoints :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n]
- linePoints :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> [Point v n]
- loopPoints :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> [Point v n]
- trailVertices' :: (Metric v, OrderedField n) => n -> Located (Trail v n) -> [Point v n]
- lineVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Line v n) -> [Point v n]
- loopVertices' :: (Metric v, OrderedField n) => n -> Located (Trail' Loop v n) -> [Point v n]
- trailVertices :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n]
- lineVertices :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> [Point v n]
- loopVertices :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> [Point v n]
- trailLocSegments :: (Metric v, OrderedField n) => Located (Trail v n) -> [Located (Segment Closed v n)]
- fixTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> [FixedSegment v n]
- unfixTrail :: (Metric v, Ord n, Floating n) => [FixedSegment v n] -> Located (Trail v n)
- reverseTrail :: (Metric v, OrderedField n) => Trail v n -> Trail v n
- reverseLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Located (Trail v n)
- reverseLine :: (Metric v, OrderedField n) => Trail' Line v n -> Trail' Line v n
- reverseLocLine :: (Metric v, OrderedField n) => Located (Trail' Line v n) -> Located (Trail' Line v n)
- reverseLoop :: (Metric v, OrderedField n) => Trail' Loop v n -> Trail' Loop v n
- reverseLocLoop :: (Metric v, OrderedField n) => Located (Trail' Loop v n) -> Located (Trail' Loop v n)
- data Line
- data Loop
- newtype SegTree v n = SegTree (FingerTree (SegMeasure v n) (Segment Closed v n))
- trailMeasure :: (SegMeasure v n :>: m, Measured (SegMeasure v n) t) => a -> (m -> a) -> t -> a
- numSegs :: (Num c, Measured (SegMeasure v n) a) => a -> c
- offset :: (OrderedField n, Metric v, Measured (SegMeasure v n) t) => t -> v n
- newtype GetSegment t = GetSegment t
- getSegment :: t -> GetSegment t
- newtype GetSegmentCodomain v n = GetSegmentCodomain (Maybe (v n, Segment Closed v n, AnIso' n n))
Type definitions
Lines and loops
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
, 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
TrailLocated
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 wheremappend
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.
(Metric v, OrderedField n) => Reversing (Located (Trail' l v n)) Source # | Same as |
(Parametric (GetSegment (Trail' c v n)), EndValues (GetSegment (Trail' c v n)), Additive v, Num n) => EndValues (Tangent (Trail' c v n)) Source # | |
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) Source # | |
(Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) Source # | |
(Parametric (GetSegment (Trail' c v n)), Additive v, Num n) => Parametric (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". |
(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). |
ToPath (Located (Trail' l v n)) Source # | |
Eq (v n) => Eq (Trail' l v n) Source # | |
Ord (v n) => Ord (Trail' l v n) Source # | |
Show (v n) => Show (Trail' l v n) Source # | |
(OrderedField n, Metric v) => Semigroup (Trail' Line v n) Source # | |
(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). |
(Metric v, OrderedField n) => Enveloped (Trail' l v n) Source # | The envelope for a trail is based at the trail's start. |
(HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail' l v n) Source # | |
Wrapped (Trail' Line v n) Source # | |
(Metric v, OrderedField n) => AsEmpty (Trail' Line v n) Source # | |
(Metric v, OrderedField n) => Reversing (Trail' l v n) Source # | Same as |
(Metric v, OrderedField n, Real n) => HasArcLength (Trail' l v n) Source # | |
(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) Source # | |
(Metric v, OrderedField n, Real n) => EndValues (Trail' l v n) Source # | |
Num n => DomainBounds (Trail' l v n) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (Trail' l v n) Source # | |
(Metric v, OrderedField n) => TrailLike (Trail' Loop v n) Source # | Loops are trail-like. If given a |
(Metric v, OrderedField n) => TrailLike (Trail' Line v n) Source # | Lines are trail-like. If given a |
ToPath (Trail' l v n) Source # | |
(HasLinearMap v, Metric v, OrderedField n) => Renderable (Trail' o v n) NullBackend Source # | |
(Metric v, Metric u, OrderedField n, (~) * r (Trail' l u n)) => AffineMappable (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 # | |
Rewrapped (Trail' Line v n) (Trail' Line v' n') Source # | |
(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 # | |
(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 # | |
type V (Trail' l v n) Source # | |
type N (Trail' l v n) Source # | |
type Unwrapped (Trail' Line v n) Source # | |
type Codomain (Trail' l v n) Source # | |
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
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]
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
Generic trails
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
).
(Metric v, OrderedField n) => Reversing (Located (Trail v n)) Source # | Same as |
(Metric v, OrderedField n, Real n) => EndValues (Tangent (Trail v n)) Source # | |
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail v n)) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (Tangent (Trail v n)) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (GetSegment (Trail v n)) Source # | |
ToPath (Located (Trail v n)) Source # | |
(Metric v, Metric u, OrderedField n, (~) * r (Located (Trail u n))) => Deformable (Located (Trail v n)) r Source # | |
Eq (v n) => Eq (Trail v n) Source # | |
Ord (v n) => Ord (Trail v n) Source # | |
Show (v n) => Show (Trail v n) Source # | |
(OrderedField n, Metric v) => Semigroup (Trail v n) Source # | Two |
(Metric v, OrderedField n) => Monoid (Trail v n) Source # |
|
(Serialize (v n), OrderedField n, Metric v) => Serialize (Trail v n) Source # | |
(Metric v, OrderedField n) => Enveloped (Trail v n) Source # | |
(HasLinearMap v, Metric v, OrderedField n) => Transformable (Trail v n) Source # | |
Wrapped (Trail v n) Source # | |
(Metric v, OrderedField n) => AsEmpty (Trail v n) Source # | |
(Metric v, OrderedField n) => Reversing (Trail v n) Source # | Same as |
(Metric v, OrderedField n, Real n) => HasArcLength (Trail v n) Source # | |
(Metric v, OrderedField n, Real n) => Sectionable (Trail v n) Source # | Note that there is no |
(Metric v, OrderedField n, Real n) => EndValues (Trail v n) Source # | |
Num n => DomainBounds (Trail v n) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (Trail v n) Source # | |
(Metric v, OrderedField n) => TrailLike (Trail v n) Source # |
|
ToPath (Trail v n) Source # | |
(Metric v, Metric u, OrderedField n, (~) * r (Trail u n)) => AffineMappable (Trail v n) r Source # | |
(Metric v, Metric u, OrderedField n, OrderedField m, (~) * r (Trail u m)) => LinearMappable (Trail v n) r Source # | |
Rewrapped (Trail v n) (Trail v' n') Source # | |
Each (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')) # | |
Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) # | |
type V (Trail v n) Source # | |
type N (Trail v n) Source # | |
type Unwrapped (Trail v n) Source # | |
type Codomain (Trail v n) Source # | |
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.
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.
closeTrail :: Trail v n -> Trail v n Source #
Constructing trails
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
.
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
or a Located
(Trail'
Line
v)
.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 ===
, for
conveniently constructing a wrapTrail
. lineFromVertices
Trail
instead of a Trail' Line
.
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 ===
, for
conveniently constructing a wrapTrail
. lineFromOffsets
Trail
instead of a Trail' Line
.
lineFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail' Line v n Source #
Construct a line from a list of closed segments.
trailFromSegments :: (Metric v, OrderedField n) => [Segment Closed v n] -> Trail v n Source #
trailFromSegments ===
, for
conveniently constructing a wrapTrail
. lineFromSegments
Trail
instead of a Trail'
.
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.
Eliminating trails
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.
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.
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.
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.
lineSegments :: Trail' Line v n -> [Segment Closed v n] Source #
Extract the segments comprising a line.
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.
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.
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.
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.)
loopOffsets :: (Metric v, OrderedField n) => Trail' Loop v n -> [v n] Source #
Extract the offsets of the segments of a loop.
trailPoints :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n] Source #
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] Source #
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] Source #
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] 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)
.
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.
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.
trailVertices :: (Metric v, OrderedField n) => Located (Trail v n) -> [Point v n] Source #
Like trailVertices'
, with a default tolerance.
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) => Located (Trail' Loop v n) -> [Point v n] Source #
Same as loopVertices'
, with a default tolerance.
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.
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.
Modifying trails
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.
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
Type tag for trails with distinct endpoints.
(Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) Source # | |
(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). |
(OrderedField n, Metric v) => Semigroup (Trail' Line v n) Source # | |
(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). |
Wrapped (Trail' Line v n) Source # | |
(Metric v, OrderedField n) => AsEmpty (Trail' Line v n) Source # | |
(Metric v, OrderedField n, Real n) => Sectionable (Trail' Line v n) Source # | |
(Metric v, OrderedField n) => TrailLike (Trail' Line v n) Source # | Lines are trail-like. If given a |
Rewrapped (Trail' Line v n) (Trail' Line v' n') Source # | |
(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 # | |
(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 # | |
type Unwrapped (Trail' Line v n) Source # | |
Type tag for "loopy" trails which return to their starting point.
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop 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". |
(Metric v, OrderedField n) => TrailLike (Trail' Loop v n) Source # | Loops are trail-like. If given a |
Segment trees
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).
SegTree (FingerTree (SegMeasure v n) (Segment Closed v n)) |
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
,
Trail
s...)
offset :: (OrderedField n, Metric v, Measured (SegMeasure v n) t) => t -> v n Source #
Compute the total offset of anything measured by SegMeasure
.
Extracting segments
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 theAnIso'
value to get a real isomorphism you can use.
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail v n)) Source # | |
(Metric v, OrderedField n, Real n) => EndValues (GetSegment (Trail' Loop v n)) Source # | |
(Metric v, OrderedField n) => EndValues (GetSegment (Trail' Line v n)) Source # | |
DomainBounds t => DomainBounds (GetSegment t) Source # | |
(Metric v, OrderedField n, Real n) => Parametric (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". |
(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). |
type V (GetSegment t) Source # | |
type N (GetSegment t) Source # | |
type Codomain (GetSegment t) Source # | |
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.
newtype GetSegmentCodomain v n Source #
GetSegmentCodomain (Maybe (v n, Segment Closed v n, AnIso' n n)) |
Orphan instances
(Measured m a, Transformable a) => Transformable (FingerTree m a) Source # | |
(Measured m a, Measured n b) => Cons (FingerTree m a) (FingerTree n b) a b Source # | |
(Measured m a, Measured n b) => Snoc (FingerTree m a) (FingerTree n b) a b Source # | |