| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Graphics.Rendering.Chart.State
Synopsis
- plot :: ToPlot p => EC (Layout x y) (p x y) -> EC (Layout x y) ()
 - plotLeft :: ToPlot p => EC (LayoutLR x y1 y2) (p x y1) -> EC (LayoutLR x y1 y2) ()
 - plotRight :: ToPlot p => EC (LayoutLR x y1 y2) (p x y2) -> EC (LayoutLR x y1 y2) ()
 - takeColor :: EC l (AlphaColour Double)
 - takeShape :: EC l PointShape
 - data CState
 - colors :: Lens' CState [AlphaColour Double]
 - shapes :: Lens' CState [PointShape]
 - type EC l a = StateT l (State CState) a
 - execEC :: Default l => EC l a -> l
 - liftEC :: Default l1 => EC l1 a -> EC l2 l1
 - liftCState :: State CState a -> EC l a
 
Documentation
plot :: ToPlot p => EC (Layout x y) (p x y) -> EC (Layout x y) () Source #
Add a plot to the Layout being constructed.
plotLeft :: ToPlot p => EC (LayoutLR x y1 y2) (p x y1) -> EC (LayoutLR x y1 y2) () Source #
Add a plot against the left axis to the LayoutLR being constructed.
plotRight :: ToPlot p => EC (LayoutLR x y1 y2) (p x y2) -> EC (LayoutLR x y1 y2) () Source #
Add a plot against the right axis tof the LayoutLR being constructed.
takeShape :: EC l PointShape Source #
Pop and return the next shape from the state
The state held when monadically constructing a graphical element
Instances
| Default CState Source # | |
Defined in Graphics.Rendering.Chart.State  | |
| (Default a, ToRenderable a) => ToRenderable (EC a b) Source # | |
Defined in Graphics.Rendering.Chart.State Methods toRenderable :: EC a b -> Renderable () Source #  | |
type EC l a = StateT l (State CState) a Source #
We use nested State monads to give nice syntax. The outer state is the graphical element being constructed (typically a layout). The inner state contains any additional state reqired. This approach means that lenses and the state monad lens operators can be used directly on the value being constructed.
execEC :: Default l => EC l a -> l Source #
Run the monadic EC computation, and return the graphical
 element (ie the outer monad' state)