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 |
Plots.Types.Histogram
Description
Synopsis
- data HistogramPlot n
- computedHistogram :: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, Foldable f) => n -> n -> f n -> State (Plot (HistogramPlot n) b) () -> m ()
- data HistogramOptions n
- class HasOrientation a => HasHistogramOptions a where
- histogramOptions :: Lens' a (HistogramOptions (N a))
- numBins :: Lens' a Int
- binRange :: Lens' a (Maybe (N a, N a))
- normaliseSample :: Lens' a NormalisationMethod
- data NormalisationMethod
- count :: NormalisationMethod
- probability :: NormalisationMethod
- countDensity :: NormalisationMethod
- pdf :: NormalisationMethod
- cumilative :: NormalisationMethod
- cdf :: NormalisationMethod
- histogramPlot :: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, Foldable f, RealFrac n) => f n -> State (Plot (HistogramOptions n) b) () -> m ()
- histogramPlot' :: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, Foldable f, RealFrac n) => f n -> m ()
- histogramPlotOf :: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, RealFrac n) => Fold s n -> s -> State (Plot (HistogramOptions n) b) () -> m ()
- histogramPlotOf' :: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, RealFrac n) => Fold s n -> s -> m ()
- mkComputedHistogram :: Foldable f => n -> n -> f n -> HistogramPlot n
- mkHistogramPlot :: (Foldable f, RealFrac n) => HistogramOptions n -> f n -> HistogramPlot n
Histogram plot
data HistogramPlot n Source #
Simple histogram type supporting uniform bins.
Instances
OrderedField n => Enveloped (HistogramPlot n) Source # | |
Defined in Plots.Types.Histogram Methods getEnvelope :: HistogramPlot n -> Envelope (V (HistogramPlot n)) (N (HistogramPlot n)) # | |
HasOrientation (HistogramPlot n) Source # | |
Defined in Plots.Types.Histogram Methods orientation :: Lens' (HistogramPlot n) Orientation Source # | |
(TypeableFloat n, Renderable (Path V2 n) b) => Plotable (HistogramPlot n) b Source # | |
Defined in Plots.Types.Histogram Methods renderPlotable :: forall (v :: Type -> Type) n0. InSpace v n0 (HistogramPlot n) => AxisSpec v n0 -> PlotStyle b v n0 -> HistogramPlot n -> QDiagram b v n0 Any Source # defLegendPic :: forall (v :: Type -> Type) n0. InSpace v n0 (HistogramPlot n) => PlotStyle b v n0 -> HistogramPlot n -> QDiagram b v n0 Any Source # | |
type N (HistogramPlot n) Source # | |
Defined in Plots.Types.Histogram | |
type V (HistogramPlot n) Source # | |
Defined in Plots.Types.Histogram |
Already computed histograms
Arguments
:: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, Foldable f) | |
=> n | start of first bin |
-> n | width of each bin |
-> f n | heights of the bins |
-> State (Plot (HistogramPlot n) b) () | |
-> m () |
Plot an already computed histogram with equally sized bins.
Histogram options
data HistogramOptions n Source #
Options for binning histogram data. For now only very basic histograms building is supported.
Instances
Default (HistogramOptions n) Source # | |
Defined in Plots.Types.Histogram Methods def :: HistogramOptions n # | |
HasOrientation (HistogramOptions n) Source # | |
Defined in Plots.Types.Histogram Methods orientation :: Lens' (HistogramOptions n) Orientation Source # | |
HasHistogramOptions (HistogramOptions n) Source # | |
Defined in Plots.Types.Histogram Methods histogramOptions :: Lens' (HistogramOptions n) (HistogramOptions (N (HistogramOptions n))) Source # numBins :: Lens' (HistogramOptions n) Int Source # binRange :: Lens' (HistogramOptions n) (Maybe (N (HistogramOptions n), N (HistogramOptions n))) Source # normaliseSample :: Lens' (HistogramOptions n) NormalisationMethod Source # | |
type N (HistogramOptions n) Source # | |
Defined in Plots.Types.Histogram | |
type V (HistogramOptions n) Source # | |
Defined in Plots.Types.Histogram |
class HasOrientation a => HasHistogramOptions a where Source #
Minimal complete definition
Methods
histogramOptions :: Lens' a (HistogramOptions (N a)) 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 (N a, N a)) 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 n) Source # | |
Defined in Plots.Types.Histogram Methods histogramOptions :: Lens' (HistogramOptions n) (HistogramOptions (N (HistogramOptions n))) Source # numBins :: Lens' (HistogramOptions n) Int Source # binRange :: Lens' (HistogramOptions n) (Maybe (N (HistogramOptions n), N (HistogramOptions n))) Source # normaliseSample :: Lens' (HistogramOptions n) NormalisationMethod Source # | |
HasHistogramOptions a => HasHistogramOptions (Plot a b) 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 Methods |
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
Arguments
:: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, Foldable f, RealFrac n) | |
=> f n | data |
-> State (Plot (HistogramOptions n) b) () | 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
Arguments
:: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, Foldable f, RealFrac n) | |
=> f n | data |
-> m () | add plot to axis |
Make a HistogramPlot
without changes to the plot options.
Arguments
:: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, RealFrac n) | |
=> Fold s n | fold over the data |
-> s | data to fold |
-> State (Plot (HistogramOptions n) b) () | change to the plot |
-> m () | add plot to the |
Add a HistogramPlot
using a fold over the data.
histogramPlotOf' :: (MonadState (Axis b V2 n) m, Plotable (HistogramPlot n) b, RealFrac n) => Fold s n -> s -> m () Source #
Same as histogramPlotOf
without any changes to the plot.
Low level constructors
Arguments
:: Foldable f | |
=> n | start of first bin |
-> n | width of each bin |
-> f n | heights of the bins |
-> HistogramPlot n |
Construct a HistogramPlot
from raw histogram data.
mkHistogramPlot :: (Foldable f, RealFrac n) => HistogramOptions n -> f n -> HistogramPlot n Source #
Create a histogram by binning the data using the
HistogramOptions
.