| Copyright | (C) 2016 Christopher Chalmers | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Christopher Chalmers | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Plots.Types.Line
Description
Synopsis
- trailPlot :: (BaseSpace c ~ v, Plotable (Path v n) b, MonadState (Axis b c n) m) => Trail v n -> State (Plot (Path v n) b) () -> m ()
- trailPlot' :: (BaseSpace c ~ v, Plotable (Path v n) b, MonadState (Axis b c n) m) => Trail v n -> m ()
- pathPlot :: (BaseSpace c ~ v, Plotable (Path v n) b, MonadState (Axis b c n) m) => Path v n -> State (Plot (Path v n) b) () -> m ()
- pathPlot' :: (BaseSpace c ~ v, Plotable (Path v n) b, MonadState (Axis b c n) m) => Path v n -> m ()
- linePlot :: (BaseSpace c ~ v, Metric v, Foldable f, PointLike v n p, Plotable (Path v n) b, MonadState (Axis b c n) m) => f p -> State (Plot (Path v n) b) () -> m ()
- linePlot' :: (BaseSpace c ~ v, Metric v, Foldable f, PointLike v n p, Plotable (Path v n) b, MonadState (Axis b c n) m) => f p -> m ()
- smoothLinePlot :: (BaseSpace c ~ v, Foldable f, Metric v, PointLike v n p, Plotable (Path v n) b, Fractional (v n), MonadState (Axis b c n) m) => f p -> State (Plot (Path v n) b) () -> m ()
- smoothLinePlot' :: (BaseSpace c ~ v, Foldable f, PointLike v n p, Plotable (Path v n) b, Fractional (v n), MonadState (Axis b c n) m) => f p -> m ()
- mkTrail :: (PointLike v n p, OrderedField n, Foldable f) => f p -> Located (Trail v n)
- mkTrailOf :: (PointLike v n p, OrderedField n) => Fold s p -> s -> Located (Trail v n)
- mkPath :: (PointLike v n p, OrderedField n, Foldable f, Foldable g) => g (f p) -> Path v n
- mkPathOf :: (PointLike v n p, OrderedField n) => Fold s t -> Fold t p -> s -> Path v n
Documentation
Line plots from points
Arguments
| :: (BaseSpace c ~ v, Metric v, Foldable f, PointLike v n p, Plotable (Path v n) b, MonadState (Axis b c n) m) | |
| => f p | points to turn into trail | 
| -> State (Plot (Path v n) b) () | changes to plot options | 
| -> m () | add plot to the  | 
Add a Path plot from a list of points.
Arguments
| :: (BaseSpace c ~ v, Metric v, Foldable f, PointLike v n p, Plotable (Path v n) b, MonadState (Axis b c n) m) | |
| => f p | points to turn into trail | 
| -> m () | add plot to the  | 
Add a Path plot from a list of points.
Arguments
| :: (BaseSpace c ~ v, Foldable f, Metric v, PointLike v n p, Plotable (Path v n) b, Fractional (v n), MonadState (Axis b c n) m) | |
| => f p | points to turn into trail | 
| -> State (Plot (Path v n) b) () | changes to plot options | 
| -> m () | add plot to the  | 
Add a smooth Path plot from a list of points using cubicSpline.
Arguments
| :: (BaseSpace c ~ v, Foldable f, PointLike v n p, Plotable (Path v n) b, Fractional (v n), MonadState (Axis b c n) m) | |
| => f p | points to turn into trail | 
| -> m () | add plot to the  | 
Add a smooth Path plot from a list of points using cubicSpline
   without changes to the plot options.
Construction utilities
Trails
mkTrail :: (PointLike v n p, OrderedField n, Foldable f) => f p -> Located (Trail v n) Source #
Construct a localed trail from a list of foldable of points.
mkTrailOf :: (PointLike v n p, OrderedField n) => Fold s p -> s -> Located (Trail v n) Source #
Construct a localed trail from a fold over points.