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

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Path

Contents

Description

This module defines trails (translationally invariant sequences of linear or cubic Bézier segments) and paths (collections of concretely located trails). Trails and paths can be used for drawing shapes, laying out other diagrams, clipping, and other things.

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.

PathLike p => PathLike (Active p) 
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 (QDiagram 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) 
Semigroup (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)) => Enveloped (Trail v)

The envelope 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.

HasLinearMap v => Renderable (Trail v) NullBackend 
(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.

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

If the trail is closed, this adds in the closing segment. Otherwise, the trail is returned unmodified.

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) 
Semigroup (Path v) 
Monoid (Path v) 
(InnerSpace v, OrderedField (Scalar v)) => Juxtaposable (Path v) 
(InnerSpace v, OrderedField (Scalar v)) => Enveloped (Path v) 
HasLinearMap v => Transformable (Path v) 
VectorSpace v => HasOrigin (Path v) 
(InnerSpace v, OrderedField (Scalar v)) => Alignable (Path v) 
VectorSpace v => Closeable (Path v) 
VectorSpace v => PathLike (Path v)

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

HasLinearMap v => Renderable (Path v) NullBackend 
(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.

pathCentroid :: (VectorSpace v, Fractional (Scalar v)) => Path v -> Point vSource

Compute the centroid of a path (i.e. the average of its vertices).

expandPath :: (HasLinearMap v, VectorSpace v, Fractional (Scalar v), Eq (Scalar v)) => Scalar v -> Path v -> Path vSource

Scale a path using its centroid (see pathCentroid) as the base point for the scale.

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 p), PathLike p) => Point (V p) -> Trail (V p) -> [p]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 p), PathLike p) => Path (V p) -> [[p]]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.