histogram-fill-0.8.3.0: Library for histograms creation.

CopyrightCopyright (c) 2011, Alexey Khudyakov <alexey.skladnoy@gmail.com>
LicenseBSD3
MaintainerAlexey Khudyakov <alexey.skladnoy@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell98

Data.Histogram.Bin.Classes

Contents

Description

Type classes for binning algorithms. This is mapping from set of interest to integer indices and approximate reverse.

Synopsis

Bin type class

class Bin b where Source

This type represent some abstract data binning algorithms. It maps sets/intervals of values of type 'BinValue b' to integer indices.

Following invariant is expected to hold:

toIndex . fromIndex == id

Minimal complete definition

toIndex, fromIndex, nBins

Associated Types

type BinValue b Source

Type of value to bin

Methods

toIndex :: b -> BinValue b -> Int Source

Convert from value to index. Function must not fail for any input and should produce out of range indices for invalid input.

fromIndex :: b -> Int -> BinValue b Source

Convert from index to value. Returned value should correspond to center of bin. Definition of center is left for definition of instance. Funtion may fail for invalid indices but encouraged not to do so.

nBins :: b -> Int Source

Total number of bins. Must be non-negative.

inRange :: b -> BinValue b -> Bool Source

Check whether value in range. Have default implementation. Should satisfy: inRange b x ⇔ toIndex b x ∈ [0,nBins b)

Instances

Bin BinI 
Bin BinInt 
Bin BinD 
Bin LogBinD 
Enum a => Bin (BinEnum a) 
RealFrac f => Bin (BinF f) 
Bin bin => Bin (MaybeBin bin) 
Bin b => Bin (BinPermute b) 
Enum2D i => Bin (BinEnum2D i) 
(Bin binX, Bin binY) => Bin (Bin2D binX binY) 

binsCenters :: (Bin b, Vector v (BinValue b)) => b -> v (BinValue b) Source

Return vector of bin centers

Approximate equality

class Bin b => BinEq b where Source

Approximate equality for bins. It's nessesary to define approximate equality since exact equality is ill defined for bins which work with floating point data. It's not safe to compare floating point numbers for exact equality

Methods

binEq :: b -> b -> Bool Source

Approximate equality

Instances

BinEq BinI 
BinEq BinInt 
BinEq BinD

Equality is up to 3e-11 (2/3th of digits)

BinEq LogBinD 
Enum a => BinEq (BinEnum a) 
RealFloat f => BinEq (BinF f)

Equality is up to 2/3th of digits

BinEq bin => BinEq (MaybeBin bin) 
(BinEq bx, BinEq by) => BinEq (Bin2D bx by) 

1D bins

class (Bin b, Ord (BinValue b)) => IntervalBin b where Source

For binning algorithms which work with bin values which have some natural ordering and every bin is continous interval.

Minimal complete definition

binInterval

Methods

binInterval :: b -> Int -> (BinValue b, BinValue b) Source

Interval for n'th bin

binsList :: Vector v (BinValue b, BinValue b) => b -> v (BinValue b, BinValue b) Source

List of all bins. Could be overridden for efficiency.

class IntervalBin b => Bin1D b where Source

IntervalBin which domain is single finite interval

Methods

lowerLimit :: b -> BinValue b Source

Minimal accepted value of histogram

upperLimit :: b -> BinValue b Source

Maximal accepted value of histogram

Instances

class Bin b => SliceableBin b where Source

Binning algorithm which support slicing.

Methods

unsafeSliceBin :: Int -> Int -> b -> b Source

Slice bin by indices. This function doesn't perform any checks and may produce invalid bin. Use sliceBin instead.

sliceBin Source

Arguments

:: SliceableBin b 
=> Int

Index of first bin

-> Int

Index of last bin

-> b 
-> b 

Slice bin using indices

class Bin b => MergeableBin b where Source

Bin which support rebinning.

Methods

unsafeMergeBins :: CutDirection -> Int -> b -> b Source

N consecutive bins are joined into single bin. If number of bins isn't multiple of N remaining bins with highest or lowest index are dropped. This function doesn't do any checks. Use mergeBins instead.

data CutDirection Source

How index should be dropped

Constructors

CutLower

Drop bins with smallest index

CutHigher

Drop bins with bigger index

mergeBins :: MergeableBin b => CutDirection -> Int -> b -> b Source

N consecutive bins are joined into single bin. If number of bins isn't multiple of N remaining bins with highest or lowest index are dropped. If N is larger than number of bins all bins are merged into single one.

Sizes of bin

class Bin b => VariableBin b where Source

1D binning algorithms with variable bin size

Methods

binSizeN :: b -> Int -> BinValue b Source

Size of n'th bin.

class VariableBin b => UniformBin b where Source

1D binning algorithms with constant size bins. Constant sized bins could be thought as specialization of variable-sized bins therefore a superclass constraint.

Minimal complete definition

Nothing

Methods

binSize :: b -> BinValue b Source

Size of bin. Default implementation just uses 0th bin.

Conversion

class (Bin b, Bin b') => ConvertBin b b' where Source

Class for conversion between binning algorithms.

Methods

convertBin :: b -> b' Source

Convert bins

Instances

ConvertBin BinI BinInt 
ConvertBin BinI BinD 
ConvertBin BinInt BinD 
RealFrac f => ConvertBin BinI (BinF f) 
RealFrac f => ConvertBin BinInt (BinF f) 
(ConvertBin bx bx', ConvertBin by by') => ConvertBin (Bin2D bx by) (Bin2D bx' by') 
(ConvertBin by by', Bin bx) => ConvertBin (Bin2D bx by) (Bin2D bx by') 
(ConvertBin bx bx', Bin by) => ConvertBin (Bin2D bx by) (Bin2D bx' by)