Copyright | (c) Tim Docker 2006 2014 |
---|---|
License | BSD-style (see chart/COPYRIGHT) |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
Graphics.Rendering.Chart.Plot.Bars
Description
Bar Charts
Synopsis
- data PlotBars x y = PlotBars {
- _plot_bars_settings :: BarsSettings
- _plot_bars_titles :: [String]
- _plot_bars_values_with_labels :: [(x, [(y, String)])]
- data PlotBarsStyle
- data PlotBarsSpacing
- data PlotBarsAlignment
- class PlotValue a => BarsPlotValue a where
- barsIsNull :: a -> Bool
- barsReference :: [a] -> a
- barsAdd :: a -> a -> a
- data BarHorizAnchor
- data BarVertAnchor
- plotBars :: BarsPlotValue y => PlotBars x y -> Plot x y
- plotHBars :: BarsPlotValue x => PlotBars y x -> Plot x y
- plot_bars_style :: Lens' (PlotBars x y) PlotBarsStyle
- plot_bars_item_styles :: Lens' (PlotBars x y) [(FillStyle, Maybe LineStyle)]
- plot_bars_titles :: forall x y. Lens' (PlotBars x y) [String]
- plot_bars_spacing :: Lens' (PlotBars x y) PlotBarsSpacing
- plot_bars_alignment :: Lens' (PlotBars x y) PlotBarsAlignment
- plot_bars_singleton_width :: Lens' (PlotBars x y) Double
- plot_bars_label_bar_hanchor :: Lens' (PlotBars x y) BarHorizAnchor
- plot_bars_label_bar_vanchor :: Lens' (PlotBars x y) BarVertAnchor
- plot_bars_label_text_hanchor :: Lens' (PlotBars x y) HTextAnchor
- plot_bars_label_text_vanchor :: Lens' (PlotBars x y) VTextAnchor
- plot_bars_label_angle :: Lens' (PlotBars x y) Double
- plot_bars_label_style :: Lens' (PlotBars x y) FontStyle
- plot_bars_label_offset :: Lens' (PlotBars x y) Vector
- plot_bars_values :: Lens' (PlotBars x y) [(x, [y])]
- plot_bars_settings :: forall x y. Lens' (PlotBars x y) BarsSettings
- plot_bars_values_with_labels :: forall x y x y. Lens (PlotBars x y) (PlotBars x y) [(x, [(y, String)])] [(x, [(y, String)])]
- addLabels :: Show y => [(x, [y])] -> [(x, [(y, String)])]
Documentation
Constructors
PlotBars | |
Fields
|
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
Show PlotBarsStyle Source # | |
Defined in Graphics.Rendering.Chart.Plot.Bars Methods showsPrec :: Int -> PlotBarsStyle -> ShowS # show :: PlotBarsStyle -> String # showList :: [PlotBarsStyle] -> ShowS # |
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
Show PlotBarsSpacing Source # | |
Defined in Graphics.Rendering.Chart.Plot.Bars Methods showsPrec :: Int -> PlotBarsSpacing -> ShowS # show :: PlotBarsSpacing -> String # showList :: [PlotBarsSpacing] -> ShowS # |
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
Show PlotBarsAlignment Source # | |
Defined in Graphics.Rendering.Chart.Plot.Bars Methods showsPrec :: Int -> PlotBarsAlignment -> ShowS # show :: PlotBarsAlignment -> String # showList :: [PlotBarsAlignment] -> ShowS # |
class PlotValue a => BarsPlotValue a where Source #
Methods
barsIsNull :: a -> Bool Source #
barsReference :: [a] -> a Source #
The starting level for the chart, a function of some statistic (normally the lowest value or just const 0).
Instances
data BarHorizAnchor Source #
Constructors
BHA_Left | |
BHA_Centre | |
BHA_Right |
Instances
Show BarHorizAnchor Source # | |
Defined in Graphics.Rendering.Chart.Plot.Bars Methods showsPrec :: Int -> BarHorizAnchor -> ShowS # show :: BarHorizAnchor -> String # showList :: [BarHorizAnchor] -> ShowS # |
data BarVertAnchor Source #
Constructors
BVA_Bottom | |
BVA_Centre | |
BVA_Top |
Instances
Show BarVertAnchor Source # | |
Defined in Graphics.Rendering.Chart.Plot.Bars Methods showsPrec :: Int -> BarVertAnchor -> ShowS # show :: BarVertAnchor -> String # showList :: [BarVertAnchor] -> ShowS # |
plot_bars_style :: Lens' (PlotBars x y) PlotBarsStyle Source #
plot_bars_spacing :: Lens' (PlotBars x y) PlotBarsSpacing Source #
plot_bars_alignment :: Lens' (PlotBars x y) PlotBarsAlignment Source #
plot_bars_values :: Lens' (PlotBars x y) [(x, [y])] Source #
plot_bars_settings :: forall x y. Lens' (PlotBars x y) BarsSettings Source #