| Safe Haskell | None | 
|---|
Graphics.Rendering.Chart.Plot.Bars
Description
Bar Charts
- data PlotBars x y = PlotBars {}
 - defaultPlotBars :: BarsPlotValue y => PlotBars x y
 - data PlotBarsStyle
 - data PlotBarsSpacing
 - data  PlotBarsAlignment 
- = BarsLeft
 - | BarsCentered
 - | BarsRight
 
 - class PlotValue a => BarsPlotValue a  where
- barsReference :: a
 - barsAdd :: a -> a -> a
 
 - plotBars :: BarsPlotValue y => PlotBars x y -> Plot x y
 - plot_bars_style :: forall x y. Lens' (PlotBars x y) PlotBarsStyle
 - plot_bars_item_styles :: forall x y. Lens' (PlotBars x y) [(FillStyle, Maybe LineStyle)]
 - plot_bars_titles :: forall x y. Lens' (PlotBars x y) [String]
 - plot_bars_spacing :: forall x y. Lens' (PlotBars x y) PlotBarsSpacing
 - plot_bars_alignment :: forall x y. Lens' (PlotBars x y) PlotBarsAlignment
 - plot_bars_reference :: forall x y. Lens' (PlotBars x y) y
 - plot_bars_singleton_width :: forall x y. Lens' (PlotBars x y) Double
 - plot_bars_values :: forall x y x. Lens (PlotBars x y) (PlotBars x y) [(x, [y])] [(x, [y])]
 
Documentation
Value describing how to plot a set of bars. Note that the input data is typed [(x,[y])], ie for each x value we plot several y values. Typically the size of each [y] list would be the same.
Constructors
| PlotBars | |
Fields 
  | |
Instances
| BarsPlotValue y => Default (PlotBars x y) | 
defaultPlotBars :: BarsPlotValue y => PlotBars x ySource
Deprecated: Use the according Data.Default instance!
data PlotBarsStyle Source
Constructors
| BarsStacked | Bars for a fixed x are stacked vertically on top of each other.  | 
| BarsClustered | Bars for a fixed x are put horizontally beside each other.  | 
Instances
data PlotBarsSpacing Source
Constructors
| BarsFixWidth Double | All bars have the same width in pixels.  | 
| BarsFixGap Double Double | (BarsFixGap g mw) means make the gaps between the bars equal to g, but with a minimum bar width of mw  | 
Instances
data PlotBarsAlignment Source
How bars for a given (x,[y]) are aligned with respect to screen coordinate corresponding to x (deviceX).
Constructors
| BarsLeft | The left edge of bars is at deviceX  | 
| BarsCentered | Bars are centered around deviceX  | 
| BarsRight | The right edge of bars is at deviceX  | 
Instances
class PlotValue a => BarsPlotValue a whereSource
Instances
plotBars :: BarsPlotValue y => PlotBars x y -> Plot x ySource
plot_bars_style :: forall x y. Lens' (PlotBars x y) PlotBarsStyleSource
plot_bars_titles :: forall x y. Lens' (PlotBars x y) [String]Source
plot_bars_spacing :: forall x y. Lens' (PlotBars x y) PlotBarsSpacingSource
plot_bars_alignment :: forall x y. Lens' (PlotBars x y) PlotBarsAlignmentSource
plot_bars_reference :: forall x y. Lens' (PlotBars x y) ySource
plot_bars_singleton_width :: forall x y. Lens' (PlotBars x y) DoubleSource
plot_bars_values :: forall x y x. Lens (PlotBars x y) (PlotBars x y) [(x, [y])] [(x, [y])]Source