Copyright | (c) 2013 diagrams-lib team (see LICENSE) |
---|---|
License | BSD-style (see LICENSE) |
Maintainer | diagrams-discuss@googlegroups.com |
Safe Haskell | None |
Language | Haskell2010 |
- class (InnerSpace (V t), OrderedField (Scalar (V t))) => TrailLike t where
- fromSegments :: TrailLike t => [Segment Closed (V t)] -> t
- fromLocSegments :: TrailLike t => Located [Segment Closed (V t)] -> t
- fromOffsets :: TrailLike t => [V t] -> t
- fromLocOffsets :: (V (V t) ~ V t, TrailLike t) => Located [V t] -> t
- fromVertices :: TrailLike t => [Point (V t)] -> t
- (~~) :: TrailLike t => Point (V t) -> Point (V t) -> t
- explodeTrail :: (VectorSpace (V t), TrailLike t) => Located (Trail (V t)) -> [t]
The TrailLike class
class (InnerSpace (V t), OrderedField (Scalar (V t))) => TrailLike t where Source
A type class for trail-like things, i.e. things which can be
constructed from a concretely located Trail
. Instances include
lines, loops, trails, paths, lists of vertices, two-dimensional
Diagram
s, and Located
variants of all the above.
Usually, type variables with TrailLike
constraints are used as
the output types of functions, like
foo :: (TrailLike t) => ... -> t
Functions with such a type can be used to construct trails, paths, diagrams, lists of points, and so on, depending on the context.
To write a function with a signature like the above, you can of
course call trailLike
directly; more typically, one would use
one of the provided functions like fromOffsets
, fromVertices
,
fromSegments
, or ~~
.
(InnerSpace v, OrderedField (Scalar v)) => TrailLike [Point v] | A list of points is trail-like; this instance simply
computes the vertices of the trail, using |
TrailLike t => TrailLike (Active t) | |
TrailLike t => TrailLike (TransInv t) | Translationally invariant things are trail-like as long as the underlying type is. |
TrailLike t => TrailLike (Located t) |
|
(InnerSpace v, OrderedField (Scalar v)) => TrailLike (Trail 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)) => TrailLike (Trail' Loop v) | Loops are trail-like. If given a |
(InnerSpace v, OrderedField (Scalar v)) => TrailLike (Trail' Line v) | Lines are trail-like. If given a |
Renderable (Path R2) b => TrailLike (QDiagram b R2 Any) |
Constructing TrailLikes
fromSegments :: TrailLike t => [Segment Closed (V t)] -> t Source
Construct a trail-like thing from a list of segments, with the origin as the location.
fromSegmentsEx = fromSegments [ straight (r2 (1,1)) , bézier3 (r2 (1,1)) unitX unit_Y , straight unit_X ] # centerXY # pad 1.1
fromLocSegments :: TrailLike t => Located [Segment Closed (V t)] -> t Source
Construct a trail-like thing from a located list of segments.
fromOffsets :: TrailLike t => [V t] -> t Source
Construct a trail-like thing of linear segments from a list of offsets, with the origin as the location.
fromOffsetsEx = fromOffsets [ unitX , unitX # rotateBy (1/6) , unitX # rotateBy (-1/6) , unitX ] # centerXY # pad 1.1
fromLocOffsets :: (V (V t) ~ V t, TrailLike t) => Located [V t] -> t Source
Construct a trail-like thing of linear segments from a located list of offsets.
fromVertices :: TrailLike t => [Point (V t)] -> t Source
Construct a trail-like thing connecting the given vertices with linear segments, with the first vertex as the location. If no vertices are given, the empty trail is used with the origin as the location.
import Data.List (transpose) fromVerticesEx = ( [ pentagon 1 , pentagon 1.3 # rotateBy (1/15) , pentagon 1.5 # rotateBy (2/15) ] # transpose # concat ) # fromVertices # closeTrail # strokeTrail # centerXY # pad 1.1
(~~) :: TrailLike t => Point (V t) -> Point (V t) -> t Source
Create a linear trail between two given points.
twiddleEx = mconcat ((~~) <$> hexagon 1 <*> hexagon 1) # centerXY # pad 1.1
explodeTrail :: (VectorSpace (V t), TrailLike t) => Located (Trail (V t)) -> [t] Source
Given a concretely located trail, "explode" it by turning each segment into its own separate trail. Useful for (say) applying a different style to each segment.
explodeTrailEx = pentagon 1 # explodeTrail -- generate a list of diagrams # zipWith lc [orange, green, yellow, red, blue] # mconcat # centerXY # pad 1.1