| Copyright | (c) 2011 diagrams-lib team (see LICENSE) | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | diagrams-discuss@googlegroups.com | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Diagrams.Path
Description
This module defines paths, which are collections of concretely
 located Trails.  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 n = Path [Located (Trail v n)]
 - pathTrails :: Path v n -> [Located (Trail v n)]
 - class ToPath t where
 - pathFromTrail :: (Metric v, OrderedField n) => Trail v n -> Path v n
 - pathFromTrailAt :: (Metric v, OrderedField n) => Trail v n -> Point v n -> Path v n
 - pathFromLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Path v n
 - pathPoints :: (Metric v, OrderedField n) => Path v n -> [[Point v n]]
 - pathVertices' :: (Metric v, OrderedField n) => n -> Path v n -> [[Point v n]]
 - pathVertices :: (Metric v, OrderedField n) => Path v n -> [[Point v n]]
 - pathOffsets :: (Metric v, OrderedField n) => Path v n -> [v n]
 - pathCentroid :: (Metric v, OrderedField n) => Path v n -> Point v n
 - pathLocSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Segment Closed v n)]]
 - fixPath :: (Metric v, OrderedField n) => Path v n -> [[FixedSegment v n]]
 - scalePath :: (HasLinearMap v, Metric v, OrderedField n) => n -> Path v n -> Path v n
 - reversePath :: (Metric v, OrderedField n) => Path v n -> Path v n
 - explodePath :: (V t ~ v, N t ~ n, Additive v, TrailLike t) => Path v n -> [[t]]
 - partitionPath :: (Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n)
 
Paths
A path is a (possibly empty) list of Located Trails.
   Hence, unlike trails, paths are not translationally invariant,
   and they form a monoid under superposition (placing one path on
   top of another) rather than concatenation.
Instances
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.
Type class for things that can be converted to a Path.
Note that this class is very different from TrailLike. TrailLike is
   usually the result of a library function to give you a convenient,
   polymorphic result (Path, Diagram etc.).
pathFromTrail :: (Metric v, OrderedField n) => Trail v n -> Path v n Source
Convert a trail to a path beginning at the origin.
pathFromTrailAt :: (Metric v, OrderedField n) => Trail v n -> Point v n -> Path v n Source
Convert a trail to a path with a particular starting point.
pathFromLocTrail :: (Metric v, OrderedField n) => Located (Trail v n) -> Path v n Source
Convert a located trail to a singleton path.  This is equivalent
   to trailLike, but provided with a more specific name and type
   for convenience.
Eliminating paths
pathPoints :: (Metric v, OrderedField n) => Path v n -> [[Point v n]] Source
Extract the points of a path, resulting in a separate list of
   points for each component trail.  Here a point is any place
   where two segments join; see also pathVertices and trailPoints.
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 and paths.  For an
   unproblematic version which only yields vertices at which there
   is a sharp corner, excluding points differentiable points, see
   pathVertices.
This function is not re-exported from Diagrams.Prelude; to use it, import Diagrams.Path.
pathVertices' :: (Metric v, OrderedField n) => n -> Path v n -> [[Point v n]] Source
Extract the vertices of a path, resulting in a separate list of
   vertices for each component trail.  Here a vertex is defined as
   a non-differentiable point on the trail, i.e. a sharp corner.
   (Vertices are thus a subset of the places where segments join; if
   you want all joins between segments, see pathPoints.)  The
   tolerance determines how close the tangents of two segments must be
   at their endpoints to consider the transition point to be
   differentiable.  See trailVertices for more information.
pathVertices :: (Metric v, OrderedField n) => Path v n -> [[Point v n]] Source
Like pathVertices', with a default tolerance.
pathOffsets :: (Metric v, OrderedField n) => Path v n -> [v n] Source
Compute the total offset of each trail comprising a path (see trailOffset).
pathCentroid :: (Metric v, OrderedField n) => Path v n -> Point v n Source
Compute the centroid of a path (i.e. the average location of
   its vertices; see pathVertices).
pathLocSegments :: (Metric v, OrderedField n) => Path v n -> [[Located (Segment Closed v n)]] Source
Convert a path into a list of lists of located segments.
fixPath :: (Metric v, OrderedField n) => Path v n -> [[FixedSegment v n]] Source
Convert a path into a list of lists of FixedSegments.
Modifying paths
scalePath :: (HasLinearMap v, Metric v, OrderedField n) => n -> Path v n -> Path v n Source
Scale a path using its centroid (see pathCentroid) as the base
   point for the scale.
reversePath :: (Metric v, OrderedField n) => Path v n -> Path v n Source
Reverse all the component trails of a path.
Miscellaneous
explodePath :: (V t ~ v, N t ~ n, Additive v, TrailLike t) => Path v n -> [[t]] Source
"Explode" a path by exploding every component trail (see
   explodeTrail).