diagrams-lib-0.4: 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, Paths, and two-dimensional Diagrams.

Methods

pathLikeSource

Arguments

:: Point (V p)

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

-> Bool

Should the path be closed?

-> [Segment (V p)]

Segments of the path.

-> p 

Instances

VectorSpace v => PathLike [Point v]

A list of points is path-like; this instance simply computes the vertices of a path-like thing.

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

Renderable (Path R2) b => PathLike (AnnDiagram b R2 Any) 

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

Construct an open path-like thing with the origin as a starting point.

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

Construct an open path-like thing of linear segments from a list of offsets. The starting point is the origin.

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.

segmentsFromVertices :: AdditiveGroup v => [Point v] -> [Segment v]Source

Construct a list of linear segments from a list of vertices. The input list must contain at least two points to generate a non-empty list of segments.

pathLikeFromTrail :: PathLike p => Trail (V p) -> pSource

Convert a trail to any path-like thing. pathLikeFromTrail is the identity on trails.

Closeable things

class PathLike p => Closeable p whereSource

Path-like things that can be "open" or "closed".

Methods

open :: p -> pSource

"Open" a path-like thing.

close :: p -> pSource

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

Instances

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 => Closeable (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 
Newtype (Path v) [(Point v, Trail v)] 

Computing with trails

trailSegments' :: AdditiveGroup v => Trail v -> [Segment v]Source

trailSegments' is like trailSegments, but explicitly includes the implicit closing segment at the end of the list for closed 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.

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

Reverse a trail's direction of travel.

fixTrail :: AdditiveGroup v => Point v -> Trail v -> [FixedSegment v]Source

Convert a starting point and a trail into a list of fixed segments.

Paths

newtype Path v Source

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

Constructors

Path 

Fields

pathTrails :: [(Point v, Trail v)]
 

Instances

Eq v => Eq (Path v) 
Ord v => Ord (Path v) 
Show v => Show (Path 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) 
(VectorSpace v, Ord v) => Closeable (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 
Newtype (Path v) [(Point v, Trail v)] 

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.

Computing with paths

pathVertices :: AdditiveGroup v => Path v -> [[Point v]]Source

Extract the vertices of a path.

pathOffsets :: AdditiveGroup v => Path v -> [v]Source

Compute the total offset of each trail comprising a path.

reversePath :: AdditiveGroup v => Path v -> Path vSource

Reverse the direction of all the component trails of a path.

fixPath :: AdditiveGroup v => Path v -> [[FixedSegment v]]Source

Convert a path into a list of lists of FixedSegments.

Miscellaneous

explodeTrail :: VectorSpace v => Point v -> Trail v -> [Path v]Source

Given a starting point, "explode" a trail by turning each segment (including the implicit closing segment, if the trail is closed) into its own separate path. Useful for (say) applying a different style to each segment.

explodePath :: VectorSpace v => Path v -> [[Path v]]Source

"Explode" a path by exploding every component trail (see explodeTrail).

(~~) :: PathLike p => Point (V p) -> Point (V p) -> pSource

Create a single-segment path between two given points.