histogram-fill-0.9.1.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 LogBinD Source # 
Instance details

Defined in Data.Histogram.Bin.LogBinD

Associated Types

type BinValue LogBinD :: * Source #

Bin BinInt Source # 
Instance details

Defined in Data.Histogram.Bin.BinInt

Associated Types

type BinValue BinInt :: * Source #

Bin BinI Source # 
Instance details

Defined in Data.Histogram.Bin.BinI

Associated Types

type BinValue BinI :: * Source #

Bin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Associated Types

type BinValue BinD :: * Source #

RealFrac f => Bin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Associated Types

type BinValue (BinF f) :: * Source #

Methods

toIndex :: BinF f -> BinValue (BinF f) -> Int Source #

fromIndex :: BinF f -> Int -> BinValue (BinF f) Source #

nBins :: BinF f -> Int Source #

inRange :: BinF f -> BinValue (BinF f) -> Bool Source #

Enum a => Bin (BinEnum a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinEnum

Associated Types

type BinValue (BinEnum a) :: * Source #

Bin b => Bin (BinPermute b) Source # 
Instance details

Defined in Data.Histogram.Bin.Extra

Associated Types

type BinValue (BinPermute b) :: * Source #

Enum2D i => Bin (BinEnum2D i) Source # 
Instance details

Defined in Data.Histogram.Bin.Extra

Associated Types

type BinValue (BinEnum2D i) :: * Source #

Bin bin => Bin (MaybeBin bin) Source # 
Instance details

Defined in Data.Histogram.Bin.MaybeBin

Associated Types

type BinValue (MaybeBin bin) :: * Source #

(Vector v a, Ord a, Fractional a) => Bin (BinVarG v a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinVar

Associated Types

type BinValue (BinVarG v a) :: * Source #

Methods

toIndex :: BinVarG v a -> BinValue (BinVarG v a) -> Int Source #

fromIndex :: BinVarG v a -> Int -> BinValue (BinVarG v a) Source #

nBins :: BinVarG v a -> Int Source #

inRange :: BinVarG v a -> BinValue (BinVarG v a) -> Bool Source #

(Bin binX, Bin binY) => Bin (Bin2D binX binY) Source # 
Instance details

Defined in Data.Histogram.Bin.Bin2D

Associated Types

type BinValue (Bin2D binX binY) :: * Source #

Methods

toIndex :: Bin2D binX binY -> BinValue (Bin2D binX binY) -> Int Source #

fromIndex :: Bin2D binX binY -> Int -> BinValue (Bin2D binX binY) Source #

nBins :: Bin2D binX binY -> Int Source #

inRange :: Bin2D binX binY -> BinValue (Bin2D binX binY) -> Bool Source #

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

Minimal complete definition

binEq

Methods

binEq :: b -> b -> Bool Source #

Approximate equality

Instances
BinEq LogBinD Source # 
Instance details

Defined in Data.Histogram.Bin.LogBinD

Methods

binEq :: LogBinD -> LogBinD -> Bool Source #

BinEq BinInt Source # 
Instance details

Defined in Data.Histogram.Bin.BinInt

Methods

binEq :: BinInt -> BinInt -> Bool Source #

BinEq BinI Source # 
Instance details

Defined in Data.Histogram.Bin.BinI

Methods

binEq :: BinI -> BinI -> Bool Source #

BinEq BinD Source #

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

Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binEq :: BinD -> BinD -> Bool Source #

RealFloat f => BinEq (BinF f) Source #

Equality is up to 2/3th of digits

Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binEq :: BinF f -> BinF f -> Bool Source #

Enum a => BinEq (BinEnum a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinEnum

Methods

binEq :: BinEnum a -> BinEnum a -> Bool Source #

BinEq bin => BinEq (MaybeBin bin) Source # 
Instance details

Defined in Data.Histogram.Bin.MaybeBin

Methods

binEq :: MaybeBin bin -> MaybeBin bin -> Bool Source #

(Vector v a, Vector v Bool, Ord a, Fractional a) => BinEq (BinVarG v a) Source #

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

Instance details

Defined in Data.Histogram.Bin.BinVar

Methods

binEq :: BinVarG v a -> BinVarG v a -> Bool Source #

(BinEq bx, BinEq by) => BinEq (Bin2D bx by) Source # 
Instance details

Defined in Data.Histogram.Bin.Bin2D

Methods

binEq :: Bin2D bx by -> Bin2D bx by -> Bool Source #

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.

Instances
IntervalBin LogBinD Source # 
Instance details

Defined in Data.Histogram.Bin.LogBinD

IntervalBin BinInt Source # 
Instance details

Defined in Data.Histogram.Bin.BinInt

IntervalBin BinI Source # 
Instance details

Defined in Data.Histogram.Bin.BinI

IntervalBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

RealFrac f => IntervalBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binInterval :: BinF f -> Int -> (BinValue (BinF f), BinValue (BinF f)) Source #

binsList :: Vector v (BinValue (BinF f), BinValue (BinF f)) => BinF f -> v (BinValue (BinF f), BinValue (BinF f)) Source #

(Enum a, Ord a) => IntervalBin (BinEnum a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinEnum

IntervalBin b => IntervalBin (BinPermute b) Source # 
Instance details

Defined in Data.Histogram.Bin.Extra

(Vector v a, Ord a, Fractional a) => IntervalBin (BinVarG v a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinVar

Methods

binInterval :: BinVarG v a -> Int -> (BinValue (BinVarG v a), BinValue (BinVarG v a)) Source #

binsList :: Vector v0 (BinValue (BinVarG v a), BinValue (BinVarG v a)) => BinVarG v a -> v0 (BinValue (BinVarG v a), BinValue (BinVarG v a)) Source #

class IntervalBin b => Bin1D b where Source #

IntervalBin which domain is single finite interval

Minimal complete definition

lowerLimit, upperLimit

Methods

lowerLimit :: b -> BinValue b Source #

Minimal accepted value of histogram

upperLimit :: b -> BinValue b Source #

Maximal accepted value of histogram

class Bin b => SliceableBin b where Source #

Binning algorithm which support slicing.

Minimal complete definition

unsafeSliceBin

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.

Instances
SliceableBin LogBinD Source # 
Instance details

Defined in Data.Histogram.Bin.LogBinD

SliceableBin BinInt Source # 
Instance details

Defined in Data.Histogram.Bin.BinInt

SliceableBin BinI Source # 
Instance details

Defined in Data.Histogram.Bin.BinI

Methods

unsafeSliceBin :: Int -> Int -> BinI -> BinI Source #

SliceableBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

unsafeSliceBin :: Int -> Int -> BinD -> BinD Source #

RealFrac f => SliceableBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

unsafeSliceBin :: Int -> Int -> BinF f -> BinF f Source #

(Enum a, Ord a) => SliceableBin (BinEnum a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinEnum

Methods

unsafeSliceBin :: Int -> Int -> BinEnum a -> BinEnum a Source #

(Vector v a, Ord a, Fractional a) => SliceableBin (BinVarG v a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinVar

Methods

unsafeSliceBin :: Int -> Int -> BinVarG v a -> BinVarG v a Source #

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.

Minimal complete definition

unsafeMergeBins

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

Instances
Data CutDirection Source # 
Instance details

Defined in Data.Histogram.Bin.Classes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CutDirection -> c CutDirection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CutDirection #

toConstr :: CutDirection -> Constr #

dataTypeOf :: CutDirection -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CutDirection) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CutDirection) #

gmapT :: (forall b. Data b => b -> b) -> CutDirection -> CutDirection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CutDirection -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CutDirection -> r #

gmapQ :: (forall d. Data d => d -> u) -> CutDirection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CutDirection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CutDirection -> m CutDirection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CutDirection -> m CutDirection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CutDirection -> m CutDirection #

Show CutDirection Source # 
Instance details

Defined in Data.Histogram.Bin.Classes

Generic CutDirection Source # 
Instance details

Defined in Data.Histogram.Bin.Classes

Associated Types

type Rep CutDirection :: * -> * #

type Rep CutDirection Source # 
Instance details

Defined in Data.Histogram.Bin.Classes

type Rep CutDirection = D1 (MetaData "CutDirection" "Data.Histogram.Bin.Classes" "histogram-fill-0.9.1.0-2szAGdwCXrF1ldwodEHqkP" False) (C1 (MetaCons "CutLower" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "CutHigher" PrefixI False) (U1 :: * -> *))

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

Minimal complete definition

binSizeN

Methods

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

Size of n'th bin.

Instances
VariableBin LogBinD Source # 
Instance details

Defined in Data.Histogram.Bin.LogBinD

VariableBin BinInt Source # 
Instance details

Defined in Data.Histogram.Bin.BinInt

VariableBin BinI Source # 
Instance details

Defined in Data.Histogram.Bin.BinI

VariableBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

RealFrac f => VariableBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binSizeN :: BinF f -> Int -> BinValue (BinF f) Source #

VariableBin b => VariableBin (BinPermute b) Source # 
Instance details

Defined in Data.Histogram.Bin.Extra

VariableBin bin => VariableBin (MaybeBin bin) Source # 
Instance details

Defined in Data.Histogram.Bin.MaybeBin

Methods

binSizeN :: MaybeBin bin -> Int -> BinValue (MaybeBin bin) Source #

(Vector v a, Ord a, Fractional a) => VariableBin (BinVarG v a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinVar

Methods

binSizeN :: BinVarG v a -> Int -> BinValue (BinVarG v a) Source #

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.

Methods

binSize :: b -> BinValue b Source #

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

Instances
UniformBin BinInt Source # 
Instance details

Defined in Data.Histogram.Bin.BinInt

UniformBin BinI Source # 
Instance details

Defined in Data.Histogram.Bin.BinI

UniformBin BinD Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

RealFrac f => UniformBin (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin.BinF

Methods

binSize :: BinF f -> BinValue (BinF f) Source #

UniformBin b => UniformBin (BinPermute b) Source # 
Instance details

Defined in Data.Histogram.Bin.Extra

Conversion

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

Class for conversion between binning algorithms.

Minimal complete definition

convertBin

Methods

convertBin :: b -> b' Source #

Convert bins

Instances
ConvertBin BinInt BinD Source # 
Instance details

Defined in Data.Histogram.Bin

ConvertBin BinI BinInt Source # 
Instance details

Defined in Data.Histogram.Bin

ConvertBin BinI BinD Source # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: BinI -> BinD Source #

RealFrac f => ConvertBin BinInt (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: BinInt -> BinF f Source #

RealFrac f => ConvertBin BinI (BinF f) Source # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: BinI -> BinF f Source #

(Bin1D b, Vector v (BinValue b), Vector v Bool, a ~ BinValue b, Fractional a) => ConvertBin b (BinVarG v a) Source # 
Instance details

Defined in Data.Histogram.Bin.BinVar

Methods

convertBin :: b -> BinVarG v a Source #

(ConvertBin bx bx', ConvertBin by by') => ConvertBin (Bin2D bx by) (Bin2D bx' by') Source # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: Bin2D bx by -> Bin2D bx' by' Source #

(ConvertBin by by', Bin bx) => ConvertBin (Bin2D bx by) (Bin2D bx by') Source # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: Bin2D bx by -> Bin2D bx by' Source #

(ConvertBin bx bx', Bin by) => ConvertBin (Bin2D bx by) (Bin2D bx' by) Source # 
Instance details

Defined in Data.Histogram.Bin

Methods

convertBin :: Bin2D bx by -> Bin2D bx' by Source #