plots-0.1.1.1: Diagrams based plotting library.

Copyright(C) 2015 Christopher Chalmers
LicenseBSD-style (see the file LICENSE)
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Plots.Types.Histogram

Contents

Description

 
Synopsis

Histogram plot

data HistogramPlot Source #

Simple histogram type supporting uniform bins.

Instances
Enveloped HistogramPlot Source # 
Instance details

Defined in Plots.Types.Histogram

HasOrientation HistogramPlot Source # 
Instance details

Defined in Plots.Types.Histogram

Plotable HistogramPlot Source # 
Instance details

Defined in Plots.Types.Histogram

Methods

renderPlotable :: InSpace v Double HistogramPlot => AxisSpec v -> PlotStyle v -> HistogramPlot -> Diagram v Source #

defLegendPic :: InSpace v Double HistogramPlot => PlotStyle v -> HistogramPlot -> Diagram v Source #

type N HistogramPlot Source # 
Instance details

Defined in Plots.Types.Histogram

type V HistogramPlot Source # 
Instance details

Defined in Plots.Types.Histogram

type V HistogramPlot = V2

Already computed histograms

computedHistogram Source #

Arguments

:: (MonadState (Axis V2) m, Foldable f) 
=> Double

start of first bin

-> Double

width of each bin

-> f Double

heights of the bins

-> State (Plot HistogramPlot) () 
-> m () 

Plot an already computed histogram with equally sized bins.

Histogram options

class HasOrientation a => HasHistogramOptions a where Source #

Minimal complete definition

histogramOptions

Methods

histogramOptions :: Lens' a HistogramOptions Source #

Options for building the histogram from data.

numBins :: Lens' a Int Source #

The number of bins (bars) to use for the histogram. Must be positive.

Default is 10.

binRange :: Lens' a (Maybe (Double, Double)) Source #

The range of data to consider when building the histogram. Any data outside the range is ignored.

Default is Nothing.

normaliseSample :: Lens' a NormalisationMethod Source #

Should the resulting histogram be normalised so the total area is 1.

Default is False.

Normalisation

data NormalisationMethod Source #

The way to normalise the data from a histogram. The default method is count.

Instances
Default NormalisationMethod Source # 
Instance details

Defined in Plots.Types.Histogram

count :: NormalisationMethod Source #

The height of each bar is the number of observations. This is the Default method.

Example

Expand

probability :: NormalisationMethod Source #

The sum of the heights of the bars is equal to 1.

Example

Expand

countDensity :: NormalisationMethod Source #

The height of each bar is n / w where n is the number of observations and w is the total width.

Example

Expand

pdf :: NormalisationMethod Source #

The total area of the bars is 1. This gives a probability density function estimate.

Example

Expand

cumilative :: NormalisationMethod Source #

The height of each bar is the cumulative number of observations in each bin and all previous bins. The height of the last bar is the total number of observations.

Example

Expand

cdf :: NormalisationMethod Source #

Cumulative density function estimate. The height of each bar is equal to the cumulative relative number of observations in the bin and all previous bins. The height of the last bar is 1.

Example

Expand

Plotting histograms

histogramPlot Source #

Arguments

:: (MonadState (Axis V2) m, Foldable f) 
=> f Double

data

-> State (Plot HistogramOptions) ()

changes to plot options

-> m ()

add plot to axis

Add a HistogramPlot to the AxisState from a data set.

Example

Expand

import Plots
histogramAxis :: Axis B V2 Double
histogramAxis = r2Axis &~ do
  histogramPlot sampleData $ do
    key "histogram"
    plotColor .= blue
    areaStyle . _opacity .= 0.5
histogramExample = renderAxis histogramAxis

histogramPlot' Source #

Arguments

:: (MonadState (Axis V2) m, Foldable f) 
=> f Double

data

-> m ()

add plot to axis

Make a HistogramPlot without changes to the plot options.

histogramPlotOf Source #

Arguments

:: MonadState (Axis V2) m 
=> Fold s Double

fold over the data

-> s

data to fold

-> State (Plot HistogramOptions) ()

change to the plot

-> m ()

add plot to the Axis

Add a HistogramPlot using a fold over the data.

histogramPlotOf' :: MonadState (Axis V2) m => Fold s Double -> s -> m () Source #

Same as histogramPlotOf without any changes to the plot.

Low level constructors

mkComputedHistogram Source #

Arguments

:: Foldable f 
=> Double

start of first bin

-> Double

width of each bin

-> f Double

heights of the bins

-> HistogramPlot 

Construct a HistogramPlot from raw histogram data.

mkHistogramPlot :: Foldable f => HistogramOptions -> f Double -> HistogramPlot Source #

Create a histogram by binning the data using the HistogramOptions.