Copyright | (c) 2011 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
This module defines paths, which are collections of concretely
located Trail
s. Many drawing systems (cairo, svg, ...) have a
similar notion of "path". Note that paths with multiple trails
are necessary for being able to draw e.g. filled objects with
holes in them.
- newtype Path v = Path [Located (Trail v)]
- pathTrails :: Path v -> [Located (Trail v)]
- pathFromTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Path v
- pathFromTrailAt :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Point v -> Path v
- pathFromLocTrail :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail v) -> Path v
- pathVertices :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> [[Point v]]
- pathOffsets :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> [v]
- pathCentroid :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> Point v
- fixPath :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> [[FixedSegment v]]
- scalePath :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Scalar v -> Path v -> Path v
- reversePath :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> Path v
- explodePath :: (VectorSpace (V t), TrailLike t) => Path (V t) -> [[t]]
- partitionPath :: (Located (Trail v) -> Bool) -> Path v -> (Path v, Path v)
Paths
A path is a (possibly empty) list of Located
Trail
s.
Hence, unlike trails, paths are not translationally invariant,
and they form a monoid under superposition (placing one path on
top of another) rather than concatenation.
Constructing paths
Since paths are TrailLike
, any function producing a TrailLike
can be used to construct a (singleton) path. The functions in this
section are provided for convenience.
pathFromTrail :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Path v Source
Convert a trail to a path beginning at the origin.
pathFromTrailAt :: (InnerSpace v, OrderedField (Scalar v)) => Trail v -> Point v -> Path v Source
Convert a trail to a path with a particular starting point.
pathFromLocTrail :: (InnerSpace v, OrderedField (Scalar v)) => Located (Trail v) -> Path v Source
Convert a located trail to a singleton path. This is equivalent
to trailLike
, but provided with a more specific name and type
for convenience.
Eliminating paths
pathVertices :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> [[Point v]] Source
Extract the vertices of a path, resulting in a separate list of
vertices for each component trail (see trailVertices
).
pathOffsets :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> [v] Source
Compute the total offset of each trail comprising a path (see trailOffset
).
pathCentroid :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> Point v Source
Compute the centroid of a path (i.e. the average location of its vertices).
fixPath :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> [[FixedSegment v]] Source
Convert a path into a list of lists of FixedSegment
s.
Modifying paths
scalePath :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Scalar v -> Path v -> Path v Source
Scale a path using its centroid (see pathCentroid
) as the base
point for the scale.
reversePath :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> Path v Source
Reverse all the component trails of a path.
Miscellaneous
explodePath :: (VectorSpace (V t), TrailLike t) => Path (V t) -> [[t]] Source
"Explode" a path by exploding every component trail (see
explodeTrail
).