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

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

Diagrams.Path

Contents

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.

Synopsis

Paths

newtype Path v Source

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.

Constructors

Path [Located (Trail v)] 

Instances

Eq v => Eq (Path v) 
Ord v => Ord (Path v) 
Show v => Show (Path v) 
Semigroup (Path v) 
Monoid (Path v) 
(InnerSpace v, OrderedField (Scalar v)) => Juxtaposable (Path v) 
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Path v) 
Traced (Path R2) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Transformable (Path v) 
VectorSpace v => HasOrigin (Path v) 
Wrapped (Path v) 
(InnerSpace v, OrderedField (Scalar v)) => TrailLike (Path v)

Paths are trail-like; a trail can be used to construct a singleton path.

(InnerSpace v, OrderedField (Scalar v)) => Alignable (Path v) 
(VectorSpace v, InnerSpace v, (~) * s (Scalar v), Ord s, Fractional s, Floating s, Show s, Show v) => Deformable (Path v) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Renderable (Path v) NullBackend 
Rewrapped (Path v) (Path v') 
Typeable (* -> *) Path 
type V (Path v) = v 
type Unwrapped (Path v) = [Located (Trail v)] 

pathTrails :: Path v -> [Located (Trail v)] Source

Extract the located trails making up a Path.

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

pathLocSegments :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> [[Located (Segment Closed v)]] Source

Convert a path into a list of lists of located segments.

fixPath :: (InnerSpace v, OrderedField (Scalar v)) => Path v -> [[FixedSegment v]] Source

Convert a path into a list of lists of FixedSegments.

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

partitionPath :: (Located (Trail v) -> Bool) -> Path v -> (Path v, Path v) Source

Partition a path into two paths based on a predicate on trails: the first containing all the trails for which the predicate returns True, and the second containing the remaining trails.