Copyright | (c) 2013 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 where
- glueLine :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> Trail' Loop v
- closeLine :: Trail' Line v -> Trail' Loop v
- cutLoop :: forall v. (InnerSpace v, OrderedField (Scalar v)) => Trail' Loop v -> Trail' Line v
- data Trail v where
- wrapTrail :: Trail' l v -> Trail v
- wrapLine :: Trail' Line v -> Trail v
- wrapLoop :: Trail' Loop v -> Trail v
- onTrail :: (Trail' Line v -> Trail' l1 v) -> (Trail' Loop v -> Trail' l2 v) -> Trail v -> Trail v
- onLine :: (InnerSpace v, OrderedField (Scalar v)) => (Trail' Line v -> Trail' Line v) -> Trail v -> Trail v
- glueTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Trail v
- closeTrail :: Trail v -> Trail v
- cutTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Trail v
- emptyLine :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v
- emptyTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v
- lineFromVertices :: (InnerSpace v, OrderedField (Scalar v)) => [Point v] -> Trail' Line v
- trailFromVertices :: (InnerSpace v, OrderedField (Scalar v)) => [Point v] -> Trail v
- lineFromOffsets :: (InnerSpace v, OrderedField (Scalar v)) => [v] -> Trail' Line v
- trailFromOffsets :: (InnerSpace v, OrderedField (Scalar v)) => [v] -> Trail v
- lineFromSegments :: (InnerSpace v, OrderedField (Scalar v)) => [Segment Closed v] -> Trail' Line v
- trailFromSegments :: (InnerSpace v, OrderedField (Scalar v)) => [Segment Closed v] -> Trail v
- withTrail' :: (Trail' Line v -> r) -> (Trail' Loop v -> r) -> Trail' l v -> r
- withTrail :: (Trail' Line v -> r) -> (Trail' Loop v -> r) -> Trail v -> r
- withLine :: (InnerSpace v, OrderedField (Scalar v)) => (Trail' Line v -> r) -> Trail v -> r
- isLineEmpty :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> Bool
- isTrailEmpty :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Bool
- isLine :: Trail v -> Bool
- isLoop :: Trail v -> Bool
- trailSegments :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> [Segment Closed v]
- lineSegments :: Trail' Line v -> [Segment Closed v]
- loopSegments :: Trail' Loop v -> ([Segment Closed v], Segment Open v)
- onLineSegments :: (InnerSpace v, OrderedField (Scalar v)) => ([Segment Closed v] -> [Segment Closed v]) -> Trail' Line v -> Trail' Line v
- trailOffsets :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> [v]
- trailOffset :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> v
- lineOffsets :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> [v]
- lineOffset :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> v
- loopOffsets :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Loop v -> [v]
- trailVertices :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail v) -> [Point v]
- lineVertices :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail' Line v) -> [Point v]
- loopVertices :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail' Loop v) -> [Point v]
- fixTrail :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail v) -> [FixedSegment v]
- reverseTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Trail v
- reverseLocTrail :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail v) -> Located (Trail v)
- reverseLine :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> Trail' Line v
- reverseLocLine :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail' Line v) -> Located (Trail' Line v)
- reverseLoop :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Loop v -> Trail' Loop v
- reverseLocLoop :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail' Loop v) -> Located (Trail' Loop v)
- data Line
- data Loop
- newtype SegTree v = SegTree (FingerTree (SegMeasure v) (Segment Closed v))
- trailMeasure :: (InnerSpace v, OrderedField (Scalar v), SegMeasure v :>: m, Measured (SegMeasure v) t) => a -> (m -> a) -> t -> a
- numSegs :: (Floating (Scalar v), Num c, Ord (Scalar v), InnerSpace v, Measured (SegMeasure v) a) => a -> c
- offset :: (Floating (Scalar v), Ord (Scalar v), InnerSpace v, Measured (SegMeasure v) t) => t -> v
- newtype GetSegment t = GetSegment t
- getSegment :: t -> GetSegment t
Type definitions
Lines and loops
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.
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => EndValues (GetSegment (Trail' Loop v)) | |
(InnerSpace v, OrderedField (Scalar v)) => EndValues (GetSegment (Trail' Line v)) | |
(Parametric (GetSegment (Trail' c v)), EndValues (GetSegment (Trail' c v)), VectorSpace v, Num (Scalar v)) => EndValues (Tangent (Trail' c v)) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (GetSegment (Trail' Loop v)) | The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1". |
(InnerSpace v, OrderedField (Scalar v)) => Parametric (GetSegment (Trail' Line v)) | 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). |
(Parametric (GetSegment (Trail' c v)), VectorSpace v, Num (Scalar v)) => Parametric (Tangent (Trail' c v)) | |
Eq v => Eq (Trail' l v) | |
Ord v => Ord (Trail' l v) | |
Show v => Show (Trail' l v) | |
(OrderedField (Scalar v), InnerSpace v) => Semigroup (Trail' Line v) | |
(OrderedField (Scalar v), InnerSpace v) => Monoid (Trail' Line v) | The empty trail is constantly the zero vector. Trails are composed via concatenation. Note that only lines have a monoid instance (and not loops). |
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Trail' l v) | The envelope for a trail is based at the trail's start. |
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Transformable (Trail' l v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => HasArcLength (Trail' l v) | |
(InnerSpace v, RealFrac (Scalar v), Floating (Scalar v)) => Sectionable (Trail' Line v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => EndValues (Trail' l v) | |
Num (Scalar v) => DomainBounds (Trail' l v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (Trail' l v) | |
(InnerSpace v, OrderedField (Scalar v)) => TrailLike (Trail' Loop v) | Loops are trail-like. If given a |
(InnerSpace v, OrderedField (Scalar v)) => TrailLike (Trail' Line v) | Lines are trail-like. If given a |
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Renderable (Trail' o v) NullBackend | |
type Codomain (Tangent (Trail' c v)) = Codomain (Trail' c v) | |
type V (Trail' l v) = v | |
type Codomain (Trail' l v) = v |
glueLine :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> Trail' Loop v 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 . hcat' (with & sep .~ 1) $ [almostClosed # strokeLine, almostClosed # glueLine # strokeLoop] almostClosed :: Trail' Line R2 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 -> Trail' Loop v 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. (InnerSpace v, OrderedField (Scalar v)) => Trail' Loop v -> Trail' Line v 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
).
Eq v => Eq (Trail v) | |
Ord v => Ord (Trail v) | |
Show v => Show (Trail v) | |
(OrderedField (Scalar v), InnerSpace v) => Semigroup (Trail v) | Two |
(OrderedField (Scalar v), InnerSpace v) => Monoid (Trail v) |
|
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Trail v) | |
Traced (Trail R2) | |
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Transformable (Trail v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => HasArcLength (Trail v) | |
(InnerSpace v, RealFrac (Scalar v), Floating (Scalar v)) => Sectionable (Trail v) | Note that there is no |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => EndValues (Trail v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => EndValues (GetSegment (Trail v)) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => EndValues (Tangent (Trail v)) | |
Num (Scalar v) => DomainBounds (Trail v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (Trail v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (GetSegment (Trail v)) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (Tangent (Trail v)) | |
(InnerSpace v, OrderedField (Scalar v)) => TrailLike (Trail v) |
|
(VectorSpace v, InnerSpace v, (~) * s (Scalar v), Ord s, Fractional s, Floating s, Show s, Show v) => Deformable (Located (Trail v)) | |
(Show v, OrderedField (Scalar v), InnerSpace v, HasLinearMap v) => Renderable (Trail v) ShowBackend | |
type V (Trail v) = v | |
type Codomain (Trail v) = v | |
type Codomain (Tangent (Trail v)) = Codomain (Trail v) |
onTrail :: (Trail' Line v -> Trail' l1 v) -> (Trail' Loop v -> Trail' l2 v) -> Trail v -> Trail v Source
Modify a Trail
, specifying two separate transformations for the
cases of a line or a loop.
onLine :: (InnerSpace v, OrderedField (Scalar v)) => (Trail' Line v -> Trail' Line v) -> Trail v -> Trail v 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.
glueTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Trail v Source
closeTrail :: Trail v -> Trail v Source
cutTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Trail v Source
Constructing trails
emptyLine :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v Source
The empty line, which is the identity for concatenation of lines.
emptyTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v Source
A wrapped variant of emptyLine
.
lineFromVertices :: (InnerSpace v, OrderedField (Scalar v)) => [Point v] -> Trail' Line v 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 :: (InnerSpace v, OrderedField (Scalar v)) => [Point v] -> Trail v Source
trailFromVertices ===
, for
conveniently constructing a wrapTrail
. lineFromVertices
Trail
instead of a Trail' Line
.
lineFromOffsets :: (InnerSpace v, OrderedField (Scalar v)) => [v] -> Trail' Line v 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 :: (InnerSpace v, OrderedField (Scalar v)) => [v] -> Trail v Source
trailFromOffsets ===
, for
conveniently constructing a wrapTrail
. lineFromOffsets
Trail
instead of a Trail' Line
.
lineFromSegments :: (InnerSpace v, OrderedField (Scalar v)) => [Segment Closed v] -> Trail' Line v Source
Construct a line from a list of closed segments.
trailFromSegments :: (InnerSpace v, OrderedField (Scalar v)) => [Segment Closed v] -> Trail v Source
trailFromSegments ===
, for
conveniently constructing a wrapTrail
. lineFromSegments
Trail
instead of a Trail'
.
Eliminating trails
withTrail' :: (Trail' Line v -> r) -> (Trail' Loop v -> r) -> Trail' l v -> 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 -> r) -> (Trail' Loop v -> r) -> Trail v -> r Source
A generic eliminator for Trail
, taking functions specifying
what to do in the case of a line or a loop.
withLine :: (InnerSpace v, OrderedField (Scalar v)) => (Trail' Line v -> r) -> Trail v -> r Source
isLineEmpty :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> Bool Source
Test whether a line is empty.
isTrailEmpty :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Bool Source
Test whether a trail is empty. Note that loops are never empty.
trailSegments :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> [Segment Closed v] Source
Extract the segments of a trail. If the trail is a loop it will
first have cutLoop
applied.
loopSegments :: Trail' Loop v -> ([Segment Closed v], Segment Open v) Source
Extract the segments comprising a loop: a list of closed segments, and one final open segment.
onLineSegments :: (InnerSpace v, OrderedField (Scalar v)) => ([Segment Closed v] -> [Segment Closed v]) -> Trail' Line v -> Trail' Line v Source
Modify a line by applying a function to its list of segments.
trailOffsets :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> [v] Source
Extract the offsets of the segments of a trail.
trailOffset :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> v 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)] # stroke # lc red # lw 0.05
lineOffsets :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> [v] Source
Extract the offsets of the segments of a line.
lineOffset :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> v 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 :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Loop v -> [v] Source
Extract the offsets of the segments of a loop.
trailVertices :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail v) -> [Point v] Source
Extract the vertices of a concretely located trail. 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
.
Note that 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 :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail' Line v) -> [Point v] Source
Extract the vertices of a concretely located line. See
trailVertices
for more information.
loopVertices :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail' Loop v) -> [Point v] 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.
fixTrail :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail v) -> [FixedSegment v] Source
Convert a concretely located trail into a list of fixed segments.
Modifying trails
reverseTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Trail v 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 :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail v) -> Located (Trail v) 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 :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Line v -> Trail' Line v Source
Reverse a line. See reverseTrail
.
reverseLocLine :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail' Line v) -> Located (Trail' Line v) Source
Reverse a concretely located line. See reverseLocTrail
.
reverseLoop :: (InnerSpace v, OrderedField (Scalar v)) => Trail' Loop v -> Trail' Loop v Source
Reverse a loop. See reverseTrail
.
reverseLocLoop :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail' Loop v) -> Located (Trail' Loop v) 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.
(InnerSpace v, OrderedField (Scalar v)) => EndValues (GetSegment (Trail' Line v)) | |
(InnerSpace v, OrderedField (Scalar v)) => Parametric (GetSegment (Trail' Line v)) | 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 (Scalar v), InnerSpace v) => Semigroup (Trail' Line v) | |
(OrderedField (Scalar v), InnerSpace v) => Monoid (Trail' Line v) | The empty trail is constantly the zero vector. Trails are composed via concatenation. Note that only lines have a monoid instance (and not loops). |
(InnerSpace v, RealFrac (Scalar v), Floating (Scalar v)) => Sectionable (Trail' Line v) | |
(InnerSpace v, OrderedField (Scalar v)) => TrailLike (Trail' Line v) | Lines are trail-like. If given a |
Type tag for "loopy" trails which return to their starting point.
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => EndValues (GetSegment (Trail' Loop v)) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (GetSegment (Trail' Loop v)) | The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1". |
(InnerSpace v, OrderedField (Scalar v)) => TrailLike (Trail' Loop v) | 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) (Segment Closed v)) |
Eq v => Eq (SegTree v) | |
Ord v => Ord (SegTree v) | |
Show v => Show (SegTree v) | |
(OrderedField (Scalar v), InnerSpace v) => Monoid (SegTree v) | |
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Transformable (SegTree v) | |
Wrapped (SegTree v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => HasArcLength (SegTree v) | |
(InnerSpace v, RealFrac (Scalar v), Floating (Scalar v)) => Sectionable (SegTree v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v), Num (Scalar v)) => EndValues (SegTree v) | |
Num (Scalar v) => DomainBounds (SegTree v) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (SegTree v) | |
(OrderedField (Scalar v), InnerSpace v) => Measured (SegMeasure v) (SegTree v) | |
Rewrapped (SegTree v) (SegTree v') | |
type V (SegTree v) = v | |
type Unwrapped (SegTree v) = FingerTree (SegMeasure v) (Segment Closed v) | |
type Codomain (SegTree v) = v |
trailMeasure :: (InnerSpace v, OrderedField (Scalar v), SegMeasure v :>: m, Measured (SegMeasure v) 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 :: (Floating (Scalar v), Num c, Ord (Scalar v), InnerSpace v, Measured (SegMeasure v) a) => a -> c Source
Compute the number of segments of anything measured by
SegMeasure
(e.g. SegMeasure
itself, Segment
, SegTree
,
Trail
s...)
offset :: (Floating (Scalar v), Ord (Scalar v), InnerSpace v, Measured (SegMeasure v) t) => t -> v 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 Maybe (v, Segment
Closed v, AnIso' (Scalar v) (Scalar v))
. 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.
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => EndValues (GetSegment (Trail v)) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => EndValues (GetSegment (Trail' Loop v)) | |
(InnerSpace v, OrderedField (Scalar v)) => EndValues (GetSegment (Trail' Line v)) | |
DomainBounds t => DomainBounds (GetSegment t) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (GetSegment (Trail v)) | |
(InnerSpace v, OrderedField (Scalar v), RealFrac (Scalar v)) => Parametric (GetSegment (Trail' Loop v)) | The parameterization for loops wraps around, i.e. parameters are first reduced "mod 1". |
(InnerSpace v, OrderedField (Scalar v)) => Parametric (GetSegment (Trail' Line v)) | 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) = V t | |
type Codomain (GetSegment t) = Maybe (V t, Segment Closed (V t), AnIso' (Scalar (V t)) (Scalar (V t))) |
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.