| Copyright | (C) 2016 Christopher Chalmers | 
|---|---|
| License | BSD-style (see the file LICENSE) | 
| Maintainer | Christopher Chalmers | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Plots.Types.Line
Description
A line plot is simply a Path used as a plot. This module contains
 helpers adding path plots. For line plots with markers, see
 Scatter.
Synopsis
- trailPlot :: (BaseSpace c ~ v, MonadState (Axis c) m, HasLinearMap v, Typeable v, R1 v) => Located (Trail v Double) -> State (Plot (Path v Double)) () -> m ()
- trailPlot' :: (BaseSpace c ~ v, MonadState (Axis c) m, HasLinearMap v, Typeable v, R1 v) => Located (Trail v Double) -> m ()
- pathPlot :: (BaseSpace c ~ v, MonadState (Axis c) m, HasLinearMap v, Typeable v, R1 v) => Path v Double -> State (Plot (Path v Double)) () -> m ()
- pathPlot' :: (BaseSpace c ~ v, MonadState (Axis c) m, HasLinearMap v, Typeable v, R1 v) => Path v Double -> m ()
- linePlot :: (BaseSpace c ~ v, HasLinearMap v, Foldable f, R1 v, PointLike v Double p, MonadState (Axis c) m) => f p -> State (Plot (Path v Double)) () -> m ()
- linePlot' :: (BaseSpace c ~ v, HasLinearMap v, Foldable f, R1 v, PointLike v Double p, MonadState (Axis c) 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, HasLinearMap v, Foldable f, R1 v, PointLike v Double p, MonadState (Axis c) m) | |
| => f p | points to turn into trail | 
| -> State (Plot (Path v Double)) () | changes to plot options | 
| -> m () | add plot to the  | 
Add a Path plot from a list of points.
Arguments
| :: (BaseSpace c ~ v, HasLinearMap v, Foldable f, R1 v, PointLike v Double p, MonadState (Axis c) m) | |
| => f p | points to turn into trail | 
| -> m () | add plot to the  | 
Add a Path plot from a list of points.
Construction utilities
Trails
mkTrail :: (PointLike v n p, OrderedField n, Foldable f) => f p -> Located (Trail v n) Source #
Add a smooth Path plot from a list of points using cubicSpline.
 smoothLinePlot
   :: (BaseSpace c ~ v,
       F.Foldable f,
       Typeable v,
       HasLinearMap v,
       PointLike v Double p,
       R1 v,
       Fractional (v Double), -- needs fixing in diagrams-lib
       MonadState (Axis c) m)
   => f p -- ^ points to turn into trail
   -> State (Plot (Path v Double)) () -- ^ changes to plot options
   -> m () -- ^ add plot to the Axis
 smoothLinePlot = addPlotable . cubicSpline False . toListOf (folded . unpointLike)
Add a smooth Path plot from a list of points using cubicSpline
   without changes to the plot options.
 smoothLinePlot'
   :: (BaseSpace c ~ v,
       F.Foldable f,
       PointLike v Double p,
       Typeable v,
       R1 v,
       Fractional (v Double), -- needs fixing in diagrams-lib
       MonadState (Axis c) m)
   => f p -- ^ points to turn into trail
   -> m () -- ^ add plot to the Axis
 smoothLinePlot' xs = smoothLinePlot xs (return ())
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.