plots-0.1.1.3: Diagrams based plotting library
Copyright(C) 2015 Christopher Chalmers
LicenseBSD-style (see the file LICENSE)
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Plots.Types.Bar

Description

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

BarPlot

data BarPlot n Source #

A bar plot for a single set of bars. Multi-bar plots are achieved by having multiple BarPlots. Each bar plot corresponds to a single legend entry. To get multiple bar entries/colours, use multiple BarPlots

Instances

Instances details
OrderedField n => Enveloped (BarPlot n) Source # 
Instance details

Defined in Plots.Types.Bar

Methods

getEnvelope :: BarPlot n -> Envelope (V (BarPlot n)) (N (BarPlot n)) #

HasOrientation (BarPlot n) Source # 
Instance details

Defined in Plots.Types.Bar

HasBarLayout (BarPlot n) Source # 
Instance details

Defined in Plots.Types.Bar

(TypeableFloat n, Renderable (Path V2 n) b) => Plotable (BarPlot n) b Source # 
Instance details

Defined in Plots.Types.Bar

Methods

renderPlotable :: forall (v :: Type -> Type) n0. InSpace v n0 (BarPlot n) => AxisSpec v n0 -> PlotStyle b v n0 -> BarPlot n -> QDiagram b v n0 Any Source #

defLegendPic :: forall (v :: Type -> Type) n0. InSpace v n0 (BarPlot n) => PlotStyle b v n0 -> BarPlot n -> QDiagram b v n0 Any Source #

type N (BarPlot n) Source # 
Instance details

Defined in Plots.Types.Bar

type N (BarPlot n) = n
type V (BarPlot n) Source # 
Instance details

Defined in Plots.Types.Bar

type V (BarPlot n) = V2

barPlot Source #

Arguments

:: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) 
=> f n

bar heights

-> State (Plot (BarPlot n) b) ()

changes to the bars

-> m ()

changes to the Axis

A add BarPlot to an Axis.

Example

Expand

import Plots
barAxis :: Axis B V2 Double
barAxis = r2Axis &~ do
  yMin ?= 0
  hide majorGridLines
  barPlot [13.5, 3.0, 6.9, 7.2, 4.6] $ do
    vertical .= True
    barWidth //= 2
barExample = renderAxis barAxis

barPlot' Source #

Arguments

:: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) 
=> f n

bar heights

-> m ()

changes to the Axis

Simple version of barPlot without any modification to the Plot.

Example

Expand

import Plots
barAxis' :: Axis B V2 Double
barAxis' = r2Axis &~ do
  xMin ?= 0
  hide (yAxis . majorGridLines)
  barPlot' [13.5, 3.0, 6.9, 7.2, 4.6]
barExample' = renderAxis barAxis'

namedBarPlot Source #

Arguments

:: (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 Axis

A add BarPlot to an Axis while naming the bars.

Example

Expand

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

namedBarPlot' Source #

Arguments

:: (MonadState (Axis b V2 n) m, Plotable (BarPlot n) b, Foldable f) 
=> f (String, n)

bar heights with name

-> m ()

add plot to the Axis

Simple version of namedBarPlot without any modification to the Plot.

Example

Expand

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'

floatingBarPlot Source #

Arguments

:: (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

data BarLayout n Source #

The way an individual bar plot or a group of bars plots are laid out on the axis.

Instances

Instances details
Fractional n => Default (BarLayout n) Source # 
Instance details

Defined in Plots.Types.Bar

Methods

def :: BarLayout n #

HasOrientation (BarLayout n) Source # 
Instance details

Defined in Plots.Types.Bar

HasBarLayout (BarLayout n) Source # 
Instance details

Defined in Plots.Types.Bar

type N (BarLayout n) Source # 
Instance details

Defined in Plots.Types.Bar

type N (BarLayout n) = n

class HasOrientation a => HasBarLayout a where Source #

Class of things that have a modifiable BarLayout.

Minimal complete definition

barLayout

Methods

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

Instances details
HasBarLayout (BarLayout n) Source # 
Instance details

Defined in Plots.Types.Bar

HasBarLayout (BarPlot n) Source # 
Instance details

Defined in Plots.Types.Bar

HasBarLayout a => HasBarLayout (Plot a b) Source # 
Instance details

Defined in Plots.Types.Bar

Methods

barLayout :: Lens' (Plot a b) (BarLayout (N (Plot a b))) Source #

barWidth :: Lens' (Plot a b) (N (Plot a b)) Source #

barSpacing :: Lens' (Plot a b) (N (Plot a b)) Source #

barStart :: Lens' (Plot a b) (N (Plot a b)) Source #

HasBarLayout (MultiBarState b n a) Source # 
Instance details

Defined in Plots.Types.Bar

Multi bars

Adding to axis

multiBars Source #

Arguments

:: (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 Axis

Construct multiple bars, grouped together. See MultiBarState for details on how to customise how the bars are drawn.

Example

Expand

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:

Instances

Instances details
HasOrientation (MultiBarState b n a) Source # 
Instance details

Defined in Plots.Types.Bar

HasBarLayout (MultiBarState b n a) Source # 
Instance details

Defined in Plots.Types.Bar

type N (MultiBarState b n a) Source # 
Instance details

Defined in Plots.Types.Bar

type N (MultiBarState b n a) = n

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

Expand

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 groupedBars 1 = groupedBars corresponds to bars in a group touching. reduce the width of individual bars.

Example

Expand

stackedBars :: Num n => State (MultiBarState b n a) () Source #

Bars stacked on top of each other.

Example

Expand

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

Expand

runningBars :: Num n => State (MultiBarState b n a) () Source #

Normal bars where each data set follows the last.

Example

Expand

Modify multi bars

onBars Source #

Arguments

:: (a -> State (PlotMods b V2 n) ())

Modifier the PlotOptions and PlotStyle for the bars associated with the data from a.

-> State (MultiBarState b n a) ()

Changes to each data set when executing multiBars.

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 bars
  • areaStyle - modify the style of the bars
  • key - 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.

mkStackedEqualBars Source #

Arguments

:: Fractional n 
=> n

value each bar reaches

-> BarLayout n 
-> [[n]]

values

-> [BarPlot n] 

Similar to mkMultiStacked but stack has the same height.

mkGroupedBars Source #

Arguments

:: 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.