| Copyright | (c) 2013 diagrams-lib team (see LICENSE) | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | diagrams-discuss@googlegroups.com | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Diagrams.TrailLike
Description
- class (Metric (V t), OrderedField (N t)) => TrailLike t where
- fromSegments :: TrailLike t => [Segment Closed (V t) (N t)] -> t
- fromLocSegments :: TrailLike t => Located [Segment Closed (V t) (N t)] -> t
- fromOffsets :: TrailLike t => [Vn t] -> t
- fromLocOffsets :: (V t ~ v, N t ~ n, V (v n) ~ v, N (v n) ~ n, TrailLike t) => Located [v n] -> t
- fromVertices :: TrailLike t => [Point (V t) (N t)] -> t
- (~~) :: (V t ~ v, N t ~ n, TrailLike t) => Point v n -> Point v n -> t
- explodeTrail :: (V t ~ v, N t ~ n, TrailLike t) => Located (Trail v n) -> [t]
The TrailLike class
class (Metric (V t), OrderedField (N 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
   Diagrams, 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 ~~.
Minimal complete definition
Methods
Instances
| (Metric v, OrderedField n) => TrailLike [Point v n] Source # | A list of points is trail-like; this instance simply
   computes the vertices of the trail, using  | 
| TrailLike t => TrailLike (TransInv t) Source # | Translationally invariant things are trail-like as long as the underlying type is. | 
| TrailLike t => TrailLike (Located t) Source # | 
 | 
| (Metric v, OrderedField n) => TrailLike (Trail 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. | 
| (Metric v, OrderedField n) => TrailLike (Trail' Loop v n) Source # | Loops are trail-like.  If given a  | 
| (Metric v, OrderedField n) => TrailLike (Trail' Line v n) Source # | Lines are trail-like.  If given a  | 
Constructing TrailLikes
fromSegments :: TrailLike t => [Segment Closed (V t) (N 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) (N t)] -> t Source #
Construct a trail-like thing from a located list of segments.
fromOffsets :: TrailLike t => [Vn 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 t ~ v, N t ~ n, V (v n) ~ v, N (v n) ~ n, TrailLike t) => Located [v n] -> t Source #
Construct a trail-like thing of linear segments from a located list of offsets.
fromVertices :: TrailLike t => [Point (V t) (N 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(~~) :: (V t ~ v, N t ~ n, TrailLike t) => Point v n -> Point v n -> t Source #
Create a linear trail between two given points.
twiddleEx = mconcat ((~~) <$> hexagon 1 <*> hexagon 1) # centerXY # pad 1.1
explodeTrail :: (V t ~ v, N t ~ n, TrailLike t) => Located (Trail v n) -> [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