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

Maintainerdiagrams-discuss@googlegroups.com

Diagrams.Path

Contents

Description

Generic functionality for constructing and manipulating trails (sequences of linear or cubic Bezier segments) and paths (collections of concretely located trails).

Synopsis

Constructing path-like things

class (Monoid p, VectorSpace (V p)) => PathLike p whereSource

Type class for path-like things, which must be monoids. Instances include Trails and Paths.

Methods

setStart :: Point (V p) -> p -> pSource

Set the starting point of the path-like thing. Some path-like things (e.g. Trails) may ignore this operation.

fromSegments :: [Segment (V p)] -> pSource

Construct a path-like thing from a list of Segments.

close :: p -> pSource

"Close" a path-like thing, by implicitly connecting the endpoint(s) back to the starting point(s).

open :: p -> pSource

"Open" a path-like thing.

Instances

(Ord v, VectorSpace v) => PathLike (Path v)

Paths are (of course) path-like. fromSegments creates a path with start point at the origin.

VectorSpace v => PathLike (Trail v)

Trails are PathLike things. Note that since trails are translationally invariant, setStart has no effect. fromSegments creates an open trail.

fromOffsets :: PathLike p => [V p] -> pSource

Construct a path-like thing of linear segments from a list of offsets.

fromVertices :: PathLike p => [Point (V p)] -> pSource

Construct a path-like thing of linear segments from a list of vertices, with the first vertex as the starting point.

Trails

data Trail v Source

A trail is a sequence of segments placed end-to-end. Trails are thus translationally invariant, and form a monoid under concatenation. Trails can also be open (the default) or closed (the final point in a closed trail is implicitly connected back to the starting point).

Constructors

Trail 

Fields

trailSegments :: [Segment v]
 
isClosed :: Bool
 

Instances

Functor Trail 
Eq v => Eq (Trail v) 
Ord v => Ord (Trail v) 
Show v => Show (Trail v) 
Monoid (Trail v)

The empty trail has no segments. Trails are composed via concatenation. t1 `mappend` t2 is closed iff either t1 or t2 are.

(InnerSpace v, OrderedField (Scalar v)) => Boundable (Trail v)

The bounding function for a trail is based at the trail's start.

HasLinearMap v => Transformable (Trail v) 
VectorSpace v => PathLike (Trail v)

Trails are PathLike things. Note that since trails are translationally invariant, setStart has no effect. fromSegments creates an open trail.

(Show v, HasLinearMap v) => Renderable (Trail v) ShowBackend 

Destructing trails

trailOffsets :: Trail v -> [v]Source

Extract the offsets of the segments of a trail.

trailOffset :: AdditiveGroup v => Trail v -> vSource

Compute the offset from the start of a trail to the end.

trailVertices :: AdditiveGroup v => Point v -> Trail v -> [Point v]Source

Extract the vertices of a trail, given a concrete location at which to place the first vertex.

Paths

newtype Path v Source

A path is a (possibly empty) collection of trails, with each trail paired with an absolute starting point. Hence, paths are not translationally invariant, and form a monoid under union/superposition.

Constructors

Path 

Fields

pathTrails :: Set (Trail v, Point v)
 

Instances

Eq v => Eq (Path v) 
Ord v => Ord (Path v) 
Show v => Show (Path v) 
Ord v => Monoid (Path v) 
(InnerSpace v, OrderedField (Scalar v)) => Boundable (Path v) 
(HasLinearMap v, Ord v) => Transformable (Path v) 
(Ord v, VectorSpace v) => HasOrigin (Path v) 
(Ord v, VectorSpace v) => PathLike (Path v)

Paths are (of course) path-like. fromSegments creates a path with start point at the origin.

(Ord v, Show v, HasLinearMap v) => Renderable (Path v) ShowBackend 

Constructing paths from trails

pathFromTrail :: AdditiveGroup v => Trail v -> Path vSource

Convert a trail to a path beginning at the origin.

pathFromTrailAt :: Trail v -> Point v -> Path vSource

Convert a trail to a path with a particular starting point.

Destructing paths

pathVertices :: (AdditiveGroup v, Ord v) => Path v -> Set [Point v]Source

Extract the vertices of a path.