Copyright | (C) 2015 Christopher Chalmers |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Christopher Chalmers |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A bar plot is a plot that presents data with rectangular bars with lengths proportional to the values that they represent. The bars can be plotted vertically or horizontally.
(see multiBars
example for code to make this plot)
Synopsis
- data BarPlot n
- barPlot :: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) => f n -> State (Plot (BarPlot n) b) () -> m ()
- barPlot' :: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) => f n -> m ()
- namedBarPlot :: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) => f (String, n) -> State (Plot (BarPlot n) b) () -> m ()
- namedBarPlot' :: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) => f (String, n) -> m ()
- floatingBarPlot :: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) => f (n, n) -> State (Plot (BarPlot n) b) () -> m ()
- data BarLayout n
- class HasOrientation a => HasBarLayout a where
- multiBars :: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f, Foldable g) => f a -> (a -> g n) -> State (MultiBarState b n a) () -> m ()
- data MultiBarState b n a
- groupedBars :: Fractional n => State (MultiBarState b n a) ()
- groupedBars' :: Fractional n => n -> State (MultiBarState b n a) ()
- stackedBars :: Num n => State (MultiBarState b n a) ()
- stackedEqualBars :: Fractional n => n -> State (MultiBarState b n a) ()
- runningBars :: Num n => State (MultiBarState b n a) ()
- onBars :: (a -> State (PlotMods b V2 n) ()) -> State (MultiBarState b n a) ()
- labelBars :: HasLabels a => [String] -> State a ()
- mkBars :: (Foldable f, Num n) => BarLayout n -> f n -> BarPlot n
- mkFloatingBars :: Foldable f => BarLayout n -> f (n, n) -> BarPlot n
- mkRunningBars :: Num n => BarLayout n -> [[(n, n)]] -> [BarPlot n]
- mkStackedBars :: Num n => BarLayout n -> [[n]] -> [BarPlot n]
- mkStackedEqualBars :: Fractional n => n -> BarLayout n -> [[n]] -> [BarPlot n]
- mkGroupedBars :: Fractional n => n -> BarLayout n -> [[n]] -> [BarPlot n]
BarPlot
A bar plot for a single set of bars. Multi-bar plots are achieved
by having multiple BarPlot
s. Each bar plot corresponds to a
single legend entry. To get multiple bar entries/colours, use
multiple BarPlots
Instances
OrderedField n => Enveloped (BarPlot n) Source # | |
Defined in Plots.Types.Bar | |
HasOrientation (BarPlot n) Source # | |
Defined in Plots.Types.Bar orientation :: Lens' (BarPlot n) Orientation Source # | |
HasBarLayout (BarPlot n) Source # | |
(TypeableFloat n, Renderable (Path V2 n) b) => Plotable (BarPlot n) b Source # | |
Defined in Plots.Types.Bar | |
type N (BarPlot n) Source # | |
Defined in Plots.Types.Bar | |
type V (BarPlot n) Source # | |
Defined in Plots.Types.Bar |
:: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) | |
=> f (String, n) | bar heights with name |
-> State (Plot (BarPlot n) b) () | changes to the bars |
-> m () | changes to the |
A add BarPlot
to an Axis
while naming the bars.
Example
import Plots namedBarAxis :: Axis B V2 Double namedBarAxis = r2Axis &~ do yMin ?= 0 hide (xAxis . majorGridLines) namedBarPlot [("eggs", 12), ("bacon", 5), ("sausage", 9), ("beans", 3)] $ do vertical .= True barWidth //= 2 namedBarExample = renderAxis namedBarAxis
:: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) | |
=> f (String, n) | bar heights with name |
-> m () | add plot to the |
Simple version of namedBarPlot
without any modification to the Plot
.
Example
import Plots namedBarAxis' :: Axis B V2 Double namedBarAxis' = r2Axis &~ do xMin ?= 0 hide majorGridLines namedBarPlot' [("eggs", 12), ("bacon", 5), ("sausage", 9), ("beans", 3)]
namedBarExample' = renderAxis namedBarAxis'
:: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) | |
=> f (n, n) | bar limits |
-> State (Plot (BarPlot n) b) () | changes to the bars |
-> m () |
Same as barPlot
but with lower and upper bounds for the bars.
Bar layout
The way an individual bar plot or a group of bars plots are laid out on the axis.
Instances
Fractional n => Default (BarLayout n) Source # | |
Defined in Plots.Types.Bar | |
HasOrientation (BarLayout n) Source # | |
Defined in Plots.Types.Bar orientation :: Lens' (BarLayout n) Orientation Source # | |
HasBarLayout (BarLayout n) Source # | |
type N (BarLayout n) Source # | |
Defined in Plots.Types.Bar |
class HasOrientation a => HasBarLayout a where Source #
Class of things that have a modifiable BarLayout
.
barLayout :: Lens' a (BarLayout (N a)) Source #
Lens onto the BarLayout
barWidth :: Lens' a (N a) Source #
The width bar for single / stacked bars or the width of a group for grouped bar plot.
Default is 0.8
barSpacing :: Lens' a (N a) Source #
The spacing between each bar or group of bars.
Default is 1
barStart :: Lens' a (N a) Source #
The distance from the axis to centre of the first bar.
Default is 1
Instances
HasBarLayout (BarLayout n) Source # | |
HasBarLayout (BarPlot n) Source # | |
HasBarLayout a => HasBarLayout (Plot a b) Source # | |
HasBarLayout (MultiBarState b n a) Source # | |
Defined in Plots.Types.Bar barLayout :: Lens' (MultiBarState b n a) (BarLayout (N (MultiBarState b n a))) Source # barWidth :: Lens' (MultiBarState b n a) (N (MultiBarState b n a)) Source # barSpacing :: Lens' (MultiBarState b n a) (N (MultiBarState b n a)) Source # barStart :: Lens' (MultiBarState b n a) (N (MultiBarState b n a)) Source # |
Multi bars
Adding to axis
:: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f, Foldable g) | |
=> f a | data for multi plot |
-> (a -> g n) | extract bar heights from each data set |
-> State (MultiBarState b n a) () | state to make changes to the plot |
-> m () | changes to the |
Construct multiple bars, grouped together. See MultiBarState
for
details on how to customise how the bars are drawn.
Example
import Plots breakfastData :: [(String, V2 Double)] breakfastData = [("eggs", V2 7 5), ("bacon", V2 5 4), ("sausage", V2 2 7), ("beans", V2 2 1)]
sortedData = [ ("girls", breakfastData^..each._2._x) , ("boys", breakfastData^..each._2._y) ]
multiBarAxis :: Axis B V2 Double multiBarAxis = r2Axis &~ do yMin ?= 0 hide (xAxis . majorGridLines) hide minorTicks xLabel .= "breakfast item" multiBars sortedData snd $ do vertical .= True barWidth //= 2 labelBars (map fst breakfastData) onBars $ \(nm,_) -> key nm -- show y values without decimal point yAxis . tickLabelFunction .= atMajorTicks (show . round) -- we should really force all major ticks to like on integers too
multiBarExample = renderAxis multiBarAxis
data MultiBarState b n a Source #
The MultiBarState
is used to set the various options available
when building multiple bar plots together. The main functions used
to modify this state:
To choose the way the bars are grouped together choose one of
groupedBars
- Together in grouped (the default)stackedBars
- On on top of anotherstackedEqualBars
-stackedBars
with the same heightrunningBars
- each group of bars follows the last
- Modify the
PlotOptions
andPlotStyle
of groups of bars withonBars
. Modify the layout of the (groups of) bars with
orientation
- Horizontal or vertical barsbarWidth
- Width of each (group of) bar(s)barSpacing
- Space between each (group of) bar(s)barStart
- Start of centre of first bar
- Add labels to each (group of) bars with
labelBars
.
Instances
HasOrientation (MultiBarState b n a) Source # | |
Defined in Plots.Types.Bar orientation :: Lens' (MultiBarState b n a) Orientation Source # | |
HasBarLayout (MultiBarState b n a) Source # | |
Defined in Plots.Types.Bar barLayout :: Lens' (MultiBarState b n a) (BarLayout (N (MultiBarState b n a))) Source # barWidth :: Lens' (MultiBarState b n a) (N (MultiBarState b n a)) Source # barSpacing :: Lens' (MultiBarState b n a) (N (MultiBarState b n a)) Source # barStart :: Lens' (MultiBarState b n a) (N (MultiBarState b n a)) Source # | |
type N (MultiBarState b n a) Source # | |
Defined in Plots.Types.Bar |
Multi bar types
groupedBars :: Fractional n => State (MultiBarState b n a) () Source #
Bars that are grouped together such that each group is a single
barWidth
. The bars in a group are touching, see groupedBars' to
reduce the width of individual bars.
Example
groupedBars' :: Fractional n => n -> State (MultiBarState b n a) () Source #
Bars that are grouped together such that each group is a single
barWidth
. The parameter is the multiplier for the width of
individual bars, where
corresponds
to bars in a group touching. reduce the width of individual bars.groupedBars
1 = groupedBars
Example
stackedBars :: Num n => State (MultiBarState b n a) () Source #
Bars stacked on top of each other.
Example
stackedEqualBars :: Fractional n => n -> State (MultiBarState b n a) () Source #
Bars stacked on top of each other where every bar is the given height.
Example
runningBars :: Num n => State (MultiBarState b n a) () Source #
Normal bars
where each data set follows the last.
Example
Modify multi bars
:: (a -> State (PlotMods b V2 n) ()) | Modifier the |
-> State (MultiBarState b n a) () | Changes to each data set when executing |
Given the data for the bar, modify the properties for the bar that uses that data.
Some common functions to use on the PlotMods
:
plotColour
- change the colour of the barsareaStyle
- modify the style of the barskey
- add a legend entry for that group of bars
labelBars :: HasLabels a => [String] -> State a () Source #
Labels to use for each bar (or group of bars) along the axis.
Low level constructors
mkBars :: (Foldable f, Num n) => BarLayout n -> f n -> BarPlot n Source #
Create equidistant bars using the values.
mkFloatingBars :: Foldable f => BarLayout n -> f (n, n) -> BarPlot n Source #
Create equidistant bars with lower and upper bounds for each bar.
mkRunningBars :: Num n => BarLayout n -> [[(n, n)]] -> [BarPlot n] Source #
Create uniform bars from groups of data, placing one group after the other.
mkStackedBars :: Num n => BarLayout n -> [[n]] -> [BarPlot n] Source #
Create uniform bars from groups of data, placing one on top of the
other. The first list will be the same as mkUniformBars opts (map
(0,) ys)
, subsequent lists will be placed on top.
:: Fractional n | |
=> n | value each bar reaches |
-> BarLayout n | |
-> [[n]] | values |
-> [BarPlot n] |
Similar to mkMultiStacked
but stack has the same height.
:: Fractional n | |
=> n | width factor of individual bars (1 = touching) |
-> BarLayout n | |
-> [[n]] | |
-> [BarPlot n] |
Make bars that are grouped together. Each group of bars is treated
as a single bar when using the BarPlotsOpts
. There is an addition
parameter to adjust the width of each individual bar.