diagrams-lib-1.4.5.1: 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

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 n 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 n)] 

Instances

Instances details
Eq (v n) => Eq (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

(==) :: Path v n -> Path v n -> Bool #

(/=) :: Path v n -> Path v n -> Bool #

Ord (v n) => Ord (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

compare :: Path v n -> Path v n -> Ordering #

(<) :: Path v n -> Path v n -> Bool #

(<=) :: Path v n -> Path v n -> Bool #

(>) :: Path v n -> Path v n -> Bool #

(>=) :: Path v n -> Path v n -> Bool #

max :: Path v n -> Path v n -> Path v n #

min :: Path v n -> Path v n -> Path v n #

Show (v n) => Show (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

showsPrec :: Int -> Path v n -> ShowS #

show :: Path v n -> String #

showList :: [Path v n] -> ShowS #

Generic (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Associated Types

type Rep (Path v n) :: Type -> Type #

Methods

from :: Path v n -> Rep (Path v n) x #

to :: Rep (Path v n) x -> Path v n #

Semigroup (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

(<>) :: Path v n -> Path v n -> Path v n #

sconcat :: NonEmpty (Path v n) -> Path v n #

stimes :: Integral b => b -> Path v n -> Path v n #

Monoid (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

mempty :: Path v n #

mappend :: Path v n -> Path v n -> Path v n #

mconcat :: [Path v n] -> Path v n #

(OrderedField n, Metric v, Serialize (v n), Serialize (V (v n) (N (v n)))) => Serialize (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

put :: Putter (Path v n) #

get :: Get (Path v n) #

(Metric v, OrderedField n) => Juxtaposable (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

juxtapose :: Vn (Path v n) -> Path v n -> Path v n -> Path v n #

(Metric v, OrderedField n) => Enveloped (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

getEnvelope :: Path v n -> Envelope (V (Path v n)) (N (Path v n)) #

RealFloat n => Traced (Path V2 n) Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getTrace :: Path V2 n -> Trace (V (Path V2 n)) (N (Path V2 n)) #

(HasLinearMap v, Metric v, OrderedField n) => Transformable (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

transform :: Transformation (V (Path v n)) (N (Path v n)) -> Path v n -> Path v n #

(Additive v, Num n) => HasOrigin (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

moveOriginTo :: Point (V (Path v n)) (N (Path v n)) -> Path v n -> Path v n #

Wrapped (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Associated Types

type Unwrapped (Path v n) #

Methods

_Wrapped' :: Iso' (Path v n) (Unwrapped (Path v n)) #

AsEmpty (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

_Empty :: Prism' (Path v n) () #

(Metric v, OrderedField n) => Reversing (Path v n) Source #

Same as reversePath.

Instance details

Defined in Diagrams.Path

Methods

reversing :: Path v n -> Path v n #

(Metric v, OrderedField n) => Alignable (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

alignBy' :: (InSpace v0 n0 (Path v n), Fractional n0, HasOrigin (Path v n)) => (v0 n0 -> Path v n -> Point v0 n0) -> v0 n0 -> n0 -> Path v n -> Path v n Source #

defaultBoundary :: (V (Path v n) ~ v0, N (Path v n) ~ n0) => v0 n0 -> Path v n -> Point v0 n0 Source #

alignBy :: (InSpace v0 n0 (Path v n), Fractional n0, HasOrigin (Path v n)) => v0 n0 -> n0 -> Path v n -> Path v n Source #

(Metric v, OrderedField n) => TrailLike (Path v n) Source #

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

Instance details

Defined in Diagrams.Path

Methods

trailLike :: Located (Trail (V (Path v n)) (N (Path v n))) -> Path v n Source #

ToPath (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Path v n -> Path (V (Path v n)) (N (Path v n)) Source #

(HasLinearMap v, Metric v, OrderedField n) => Renderable (Path v n) NullBackend Source # 
Instance details

Defined in Diagrams.Path

Methods

render :: NullBackend -> Path v n -> Render NullBackend (V (Path v n)) (N (Path v n)) #

RealFloat n => HasQuery (Path V2 n) Crossings Source # 
Instance details

Defined in Diagrams.TwoD.Path

Methods

getQuery :: Path V2 n -> Query (V (Path V2 n)) (N (Path V2 n)) Crossings Source #

(Metric v, Metric u, OrderedField n, r ~ Path u n) => AffineMappable (Path v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

amap :: AffineMap (V (Path v n)) (V r) (N r) -> Path v n -> r Source #

(Metric v, Metric u, OrderedField n, OrderedField m, r ~ Path u m) => LinearMappable (Path v n) r Source # 
Instance details

Defined in Diagrams.LinearMap

Methods

vmap :: (Vn (Path v n) -> Vn r) -> Path v n -> r Source #

(Metric v, Metric u, OrderedField n, r ~ Path u n) => Deformable (Path v n) r Source # 
Instance details

Defined in Diagrams.Deform

Methods

deform' :: N (Path v n) -> Deformation (V (Path v n)) (V r) (N (Path v n)) -> Path v n -> r Source #

deform :: Deformation (V (Path v n)) (V r) (N (Path v n)) -> Path v n -> r Source #

Rewrapped (Path v n) (Path v' n') Source # 
Instance details

Defined in Diagrams.Path

Each (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

each :: Traversal (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) #

Cons (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

_Cons :: Prism (Path v n) (Path v' n') (Located (Trail v n), Path v n) (Located (Trail v' n'), Path v' n') #

Snoc (Path v n) (Path v' n') (Located (Trail v n)) (Located (Trail v' n')) Source # 
Instance details

Defined in Diagrams.Path

Methods

_Snoc :: Prism (Path v n) (Path v' n') (Path v n, Located (Trail v n)) (Path v' n', Located (Trail v' n')) #

type Rep (Path v n) Source # 
Instance details

Defined in Diagrams.Path

type Rep (Path v n) = D1 ('MetaData "Path" "Diagrams.Path" "diagrams-lib-1.4.5.1-BxQ0fcrmYomKiAQfFq3Jde" 'True) (C1 ('MetaCons "Path" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Located (Trail v n)])))
type V (Path v n) Source # 
Instance details

Defined in Diagrams.Path

type V (Path v n) = v
type N (Path v n) Source # 
Instance details

Defined in Diagrams.Path

type N (Path v n) = n
type Unwrapped (Path v n) Source # 
Instance details

Defined in Diagrams.Path

type Unwrapped (Path v n) = [Located (Trail v n)]

pathTrails :: Path v n -> [Located (Trail v n)] 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.

class ToPath t where Source #

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

Methods

toPath :: (Metric (V t), OrderedField (N t)) => t -> Path (V t) (N t) Source #

toPath takes something that can be converted to Path and returns the Path.

Instances

Instances details
ToPath a => ToPath [a] Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: [a] -> Path (V [a]) (N [a]) Source #

ToPath (Located [Segment Closed v n]) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located [Segment Closed v n] -> Path (V (Located [Segment Closed v n])) (N (Located [Segment Closed v n])) Source #

ToPath (Located (Segment Closed v n)) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located (Segment Closed v n) -> Path (V (Located (Segment Closed v n))) (N (Located (Segment Closed v n))) Source #

ToPath (Located (Trail v n)) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located (Trail v n) -> Path (V (Located (Trail v n))) (N (Located (Trail v n))) Source #

ToPath (Located (Trail' l v n)) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Located (Trail' l v n) -> Path (V (Located (Trail' l v n))) (N (Located (Trail' l v n))) Source #

ToPath (FixedSegment v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: FixedSegment v n -> Path (V (FixedSegment v n)) (N (FixedSegment v n)) Source #

ToPath (Trail v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Trail v n -> Path (V (Trail v n)) (N (Trail v n)) Source #

ToPath (Path v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Path v n -> Path (V (Path v n)) (N (Path v n)) Source #

ToPath (Trail' l v n) Source # 
Instance details

Defined in Diagrams.Path

Methods

toPath :: Trail' l v n -> Path (V (Trail' l v n)) (N (Trail' l v n)) Source #

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, TrailLike t) => Path v n -> [[t]] Source #

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

partitionPath :: (Located (Trail v n) -> Bool) -> Path v n -> (Path v n, Path v n) 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.