Copyright | (C) 2015 Christopher Chalmers |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Christopher Chalmers |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data HistogramPlot
- computedHistogram :: (MonadState (Axis V2) m, Foldable f) => Double -> Double -> f Double -> State (Plot HistogramPlot) () -> m ()
- data HistogramOptions
- class HasOrientation a => HasHistogramOptions a where
- histogramOptions :: Lens' a HistogramOptions
- numBins :: Lens' a Int
- binRange :: Lens' a (Maybe (Double, Double))
- normaliseSample :: Lens' a NormalisationMethod
- data NormalisationMethod
- count :: NormalisationMethod
- probability :: NormalisationMethod
- countDensity :: NormalisationMethod
- pdf :: NormalisationMethod
- cumilative :: NormalisationMethod
- cdf :: NormalisationMethod
- histogramPlot :: (MonadState (Axis V2) m, Foldable f) => f Double -> State (Plot HistogramOptions) () -> m ()
- histogramPlot' :: (MonadState (Axis V2) m, Foldable f) => f Double -> m ()
- histogramPlotOf :: MonadState (Axis V2) m => Fold s Double -> s -> State (Plot HistogramOptions) () -> m ()
- histogramPlotOf' :: MonadState (Axis V2) m => Fold s Double -> s -> m ()
- mkComputedHistogram :: Foldable f => Double -> Double -> f Double -> HistogramPlot
- mkHistogramPlot :: Foldable f => HistogramOptions -> f Double -> HistogramPlot
Histogram plot
data HistogramPlot Source #
Simple histogram type supporting uniform bins.
Instances
Enveloped HistogramPlot Source # | |
Defined in Plots.Types.Histogram getEnvelope :: HistogramPlot -> Envelope (V HistogramPlot) (N HistogramPlot) boundingBox :: HistogramPlot -> BoundingBox (V HistogramPlot) (N HistogramPlot) | |
HasOrientation HistogramPlot Source # | |
Defined in Plots.Types.Histogram | |
Plotable HistogramPlot Source # | |
Defined in Plots.Types.Histogram 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 # | |
Defined in Plots.Types.Histogram | |
type V HistogramPlot Source # | |
Defined in Plots.Types.Histogram |
Already computed histograms
:: (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
data HistogramOptions Source #
Options for binning histogram data. For now only very basic histograms building is supported.
Instances
Default HistogramOptions Source # | |
Defined in Plots.Types.Histogram def :: HistogramOptions # | |
HasOrientation HistogramOptions Source # | |
Defined in Plots.Types.Histogram | |
HasHistogramOptions HistogramOptions Source # | |
type N HistogramOptions Source # | |
Defined in Plots.Types.Histogram | |
type V HistogramOptions Source # | |
Defined in Plots.Types.Histogram |
class HasOrientation a => HasHistogramOptions a where Source #
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.
normaliseSample :: Lens' a NormalisationMethod Source #
Should the resulting histogram be normalised so the total area is 1.
Default
is False.
Instances
HasHistogramOptions HistogramOptions Source # | |
HasHistogramOptions a => HasHistogramOptions (Plot a) Source # | |
Normalisation
data NormalisationMethod Source #
The way to normalise the data from a histogram. The default method
is count
.
Instances
Default NormalisationMethod Source # | |
Defined in Plots.Types.Histogram |
probability :: NormalisationMethod Source #
The sum of the heights of the bars is equal to 1.
Example
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
pdf :: NormalisationMethod Source #
The total area of the bars is 1
. This gives a probability density
function estimate.
Example
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
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
Plotting histograms
:: (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
import Plots histogramAxis :: Axis B V2 Double histogramAxis = r2Axis &~ do histogramPlot sampleData $ do key "histogram" plotColor .= blue areaStyle . _opacity .= 0.5
histogramExample = renderAxis histogramAxis
:: (MonadState (Axis V2) m, Foldable f) | |
=> f Double | data |
-> m () | add plot to axis |
Make a HistogramPlot
without changes to the plot options.
:: 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 |
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
:: 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
.