histogram-fill-0.6.0.0: Library for histograms creation.

Stabilityexperimental
MaintainerAlexey Khudyakov <alexey.skladnoy@gmail.com>

Data.Histogram.Generic

Contents

Description

Generic immutable histograms.

Synopsis

Data type

data Histogram v bin a Source

Immutable histogram. Histogram consists of binning algorithm, optional number of under and overflows, and data.

Instances

Typeable1 v => Typeable2 (Histogram v) 
Functor v => Functor (Histogram v bin)

If vector is a functor then histogram is functor as well

(Eq bin, Eq a, Eq (v a)) => Eq (Histogram v bin a) 
(Show a, Show (BinValue bin), Show bin, Bin bin, Vector v a) => Show (Histogram v bin a) 
(NFData a, NFData bin) => NFData (Histogram v bin a)

Vector do not supply NFData instance so let just seq it and hope it's enough. Should be enough for unboxed vectors.

histogram :: (Vector v a, Bin bin) => bin -> v a -> Histogram v bin aSource

Create histogram from binning algorithm and vector with data. Overflows are set to Nothing.

Number of bins and vector size must match.

histogramUO :: (Vector v a, Bin bin) => bin -> Maybe (a, a) -> v a -> Histogram v bin aSource

Create histogram from binning algorithm and vector with data.

Number of bins and vector size must match.

data HistIndex b Source

Point inside histogram's domain. It could be either bin index or bin value.

Constructors

Index Int

Index for a bin

Value (BinValue b)

Value

Instances

histIndex :: Bin b => b -> HistIndex b -> IntSource

Convert HistIndex to actual index

Read histograms from string

readHistogram :: (Read bin, Read a, Bin bin, Vector v a) => String -> Histogram v bin aSource

Convert String to histogram. Histogram do not have Read instance because of slowness of ReadP

readFileHistogram :: (Read bin, Read a, Bin bin, Vector v a) => FilePath -> IO (Histogram v bin a)Source

Read histogram from file.

Accessors

bins :: Histogram v bin a -> binSource

Histogram bins

histData :: Histogram v bin a -> v aSource

Histogram data as vector

underflows :: Histogram v bin a -> Maybe aSource

Number of underflows

overflows :: Histogram v bin a -> Maybe aSource

Number of overflows

outOfRange :: Histogram v bin a -> Maybe (a, a)Source

Underflows and overflows

Convert to other data types

asList :: (Vector v a, Bin bin) => Histogram v bin a -> [(BinValue bin, a)]Source

Convert histogram data to list.

asVector :: (Bin bin, Vector v a, Vector v (BinValue bin, a)) => Histogram v bin a -> v (BinValue bin, a)Source

Convert histogram data to vector

Modification

map :: (Vector v a, Vector v b) => (a -> b) -> Histogram v bin a -> Histogram v bin bSource

fmap lookalike. It's not possible to create Functor instance because of type class context.

bmap :: (Vector v a, Vector v b, Bin bin) => (BinValue bin -> a -> b) -> Histogram v bin a -> Histogram v bin bSource

Map histogram using bin value and content. Overflows and underflows are set to Nothing.

zip :: (Bin bin, BinEq bin, Vector v a, Vector v b, Vector v c) => (a -> b -> c) -> Histogram v bin a -> Histogram v bin b -> Histogram v bin cSource

Zip two histograms elementwise. Bins of histograms must be equal otherwise error will be called.

zipSafe :: (Bin bin, BinEq bin, Vector v a, Vector v b, Vector v c) => (a -> b -> c) -> Histogram v bin a -> Histogram v bin b -> Maybe (Histogram v bin c)Source

Zip two histogram elementwise. If bins are not equal return Nothing

Type conversion

convert :: (Vector v a, Vector w a) => Histogram v bin a -> Histogram w bin aSource

Convert between different vector types

convertBinning :: (ConvertBin bin bin', Vector v a) => Histogram v bin a -> Histogram v bin' aSource

Convert between binning types using ConvertBin type class.

Folding

foldl :: (Bin bin, Vector v a) => (b -> a -> b) -> b -> Histogram v bin a -> bSource

Strict fold over bin content in index order. Underflows and overflows are ignored.

bfoldl :: (Bin bin, Vector v a) => (b -> BinValue bin -> a -> b) -> b -> Histogram v bin a -> bSource

Strict fold over bin content in index order. Function is applied to bin content and bin value. Underflows and overflows are ignored.

Slicing & rebinning

sliceSource

Arguments

:: (SliceableBin bin, Vector v a) 
=> HistIndex bin

Lower inclusive bound

-> HistIndex bin

Upper inclusive bound

-> Histogram v bin a

Histogram to slice

-> Histogram v bin a 

Slice histogram. Values/indices specify inclusive variant. Under/overflows are discarded.

rebinSource

Arguments

:: (MergeableBin bin, Vector v a) 
=> CutDirection 
-> Int 
-> (a -> a -> a)

Accumulation function

-> Histogram v bin a 
-> Histogram v bin a 

Rebin histogram

rebinFoldSource

Arguments

:: (MergeableBin bin, Vector v a, Vector v b) 
=> CutDirection 
-> Int 
-> (b -> a -> b)

Accumulation function

-> b

Initial value

-> Histogram v bin a 
-> Histogram v bin b 

Rebin histogram

2D histograms

Slicing

sliceAlongXSource

Arguments

:: (Vector v a, Bin bX, Bin bY) 
=> Histogram v (Bin2D bX bY) a

2D histogram

-> HistIndex bY

Position along Y axis

-> Histogram v bX a 

Get slice of 2D histogram along X axis. This function is faster than sliceAlongY since no array reallocations is required

sliceAlongYSource

Arguments

:: (Vector v a, Bin bX, Bin bY) 
=> Histogram v (Bin2D bX bY) a

2D histogram

-> HistIndex bX

Position along X axis

-> Histogram v bY a 

Get slice of 2D histogram along X axis

listSlicesAlongX :: (Vector v a, Bin bX, Bin bY) => Histogram v (Bin2D bX bY) a -> [(BinValue bY, Histogram v bX a)]Source

Slice 2D histogram along Y axis. This function is fast because it does not require reallocations.

listSlicesAlongY :: (Vector v a, Bin bX, Bin bY) => Histogram v (Bin2D bX bY) a -> [(BinValue bX, Histogram v bY a)]Source

Slice 2D histogram along X axis.

Reducing along axis

reduceXSource

Arguments

:: (Vector v a, Vector v b, Bin bX, Bin bY) 
=> (Histogram v bX a -> b)

Function to reduce single slice along X axis

-> Histogram v (Bin2D bX bY) a

2D histogram

-> Histogram v bY b 

Reduce along X axis. Information about under/overlows is lost.

reduceYSource

Arguments

:: (Vector v a, Vector v b, Bin bX, Bin bY) 
=> (Histogram v bY a -> b)

Function to reduce histogram along Y axis

-> Histogram v (Bin2D bX bY) a

2D histogram

-> Histogram v bX b 

Reduce along Y axis. Information about under/overflows is lost.

Lift histogram transform to 2D

liftX :: (Bin bX, Bin bY, Bin bX', BinEq bX', Vector v a, Vector v b) => (Histogram v bX a -> Histogram v bX' b) -> Histogram v (Bin2D bX bY) a -> Histogram v (Bin2D bX' bY) bSource

liftY :: (Bin bX, Bin bY, Bin bY', BinEq bY', Vector v a, Vector v b, Vector v Int) => (Histogram v bY a -> Histogram v bY' b) -> Histogram v (Bin2D bX bY) a -> Histogram v (Bin2D bX bY') bSource