histogram-fill-0.2.0: Library for histograms creation.

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

Data.Histogram.Bin

Contents

Description

Binning algorithms. This is mapping from set of interest to integer indices and approximate reverse.

Synopsis

Type classes

class Bin b whereSource

Abstract binning algorithm. It provides way to map some values onto continous range of integer values starting from zero.

Following invariant is expected to hold:

 toIndex . fromIndex == id

Reverse is not nessearily true.

Associated Types

type BinValue b Source

Type of value to bin

Methods

toIndex :: b -> BinValue b -> IntSource

Convert from value to index. No bound checking performed

fromIndex :: b -> Int -> BinValue bSource

Convert from index to value.

inRange :: b -> BinValue b -> BoolSource

Check whether value in range.

nBins :: b -> IntSource

Total number of bins

Instances

Bin LogBinD 
Bin BinD 
Bin BinInt 
Bin BinI 
Indexable2D i => Bin (BinIx2D i) 
Bin (BinF f) 
Indexable i => Bin (BinIx i) 
Bin b => Bin (BinPermute b) 
(Bin binX, Bin binY) => Bin (Bin2D binX binY) 

class Bin b => Bin1D b whereSource

One dimensional binning algorithm. It means that bin values have some inherent ordering. For example all binning algorithms for real numbers could be members or this type class whereas binning algorithms for R^2 could not.

Methods

binsList :: b -> [BinValue b]Source

List of center of bins in ascending order.

binsListRange :: b -> [(BinValue b, BinValue b)]Source

List of bins in ascending order.

Instances

class Indexable a whereSource

Indexable is value which could be converted to and from Int without information loss.

Always true

 deindex . index = id

Only if Int is in range

 index . deindex = id

Methods

index :: a -> IntSource

Convert value to index

deindex :: Int -> aSource

Convert index to value

Instances

class Indexable2D a whereSource

This type class is same as Indexable but for 2D values.

Methods

index2D :: a -> (Int, Int)Source

Convert value to index

deindex2D :: (Int, Int) -> aSource

Convert index to value

Instances

(Indexable a, Indexable b) => Indexable2D (a, b) 

Bin types

Integer bins

data BinI Source

Simple binning algorithm which map continous range of bins onto indices. Each number correcsponds to different bin

Constructors

BinI !Int !Int 

binI0 :: Int -> BinISource

Construct BinI with n bins. Indexing starts from 0

Integer bins with non-1 size

data BinInt Source

Integer bins with size which differ from 1.

binIntSource

Arguments

:: Int

Lower bound

-> Int

Bin size

-> Int

Upper bound

-> BinInt 

Construct BinInt.

Indexed bins

newtype BinIx i Source

Binning for indexable values

Constructors

BinIx 

Fields

unBinIx :: BinI
 

Instances

Eq (BinIx i) 
(Read i, Indexable i) => Read (BinIx i) 
(Show i, Indexable i) => Show (BinIx i) 
Indexable i => Bin1D (BinIx i) 
Indexable i => Bin (BinIx i) 

binIx :: Indexable i => i -> i -> BinIx iSource

Construct indexed bin

Floating point bins

data BinF f Source

Floaintg point bins with equal sizes.

Instances

Eq f => Eq (BinF f) 
(Read f, RealFrac f) => Read (BinF f) 
Show f => Show (BinF f) 
Bin1D (BinF f) 
Bin (BinF f) 

binFSource

Arguments

:: RealFrac f 
=> f

Lower bound of range

-> Int

Number of bins

-> f

Upper bound of range

-> BinF f 

Create bins.

binFnSource

Arguments

:: RealFrac f 
=> f

Begin of range

-> f

Size of step

-> f

Approximation of end of range

-> BinF f 

Create bins. Note that actual upper bound can differ from specified.

binI2binF :: RealFrac f => BinI -> BinF fSource

Convert BinI to BinF

scaleBinF :: RealFrac f => f -> f -> BinF f -> BinF fSource

'scaleBinF a b' scales BinF using linear transform 'a+b*x'

Specialized for Double

data BinD Source

Floaintg point bins with equal sizes. If you work with Doubles this data type should be used instead of BinF.

binDSource

Arguments

:: Double

Lower bound of range

-> Int

Number of bins

-> Double

Upper bound of range

-> BinD 

Create bins.

binDnSource

Arguments

:: Double

Begin of range

-> Double

Size of step

-> Double

Approximation of end of range

-> BinD 

Create bins. Note that actual upper bound can differ from specified.

binI2binD :: BinI -> BinDSource

Convert BinI to BinF

scaleBinD :: Double -> Double -> BinD -> BinDSource

'scaleBinF a b' scales BinF using linear transform 'a+b*x'

Log scale point

data LogBinD Source

Logarithmic scale bins.

logBinD :: Double -> Int -> Double -> LogBinDSource

Create log-scale bins.

2D bins

data Bin2D binX binY Source

2D bins. binX is binning along X axis and binY is one along Y axis.

Constructors

Bin2D !binX !binY 

Instances

(Eq binX, Eq binY) => Eq (Bin2D binX binY) 
(Read b1, Read b2) => Read (Bin2D b1 b2) 
(Show b1, Show b2) => Show (Bin2D b1 b2) 
(Bin binX, Bin binY) => Bin (Bin2D binX binY) 

(><) :: binX -> binY -> Bin2D binX binYSource

Alias for Bin2D.

nBins2D :: (Bin bx, Bin by) => Bin2D bx by -> (Int, Int)Source

2-dimensional size of binning algorithm

toIndex2D :: (Bin binX, Bin binY) => Bin2D binX binY -> Int -> (Int, Int)Source

binX :: Bin2D bx by -> bxSource

Get binning algorithm along X axis

binY :: Bin2D bx by -> bySource

Get binning algorithm along Y axis

fmapBinX :: (Bin bx, Bin bx') => (bx -> bx') -> Bin2D bx by -> Bin2D bx' bySource

Apply function to X binning algorithm. If new binning algorithm have different number of bins will fail.

fmapBinY :: (Bin by, Bin by') => (by -> by') -> Bin2D bx by -> Bin2D bx by'Source

Apply function to Y binning algorithm. If new binning algorithm have different number of bins will fail.

2D indexed bins

data BinIx2D i Source

Binning for 2D indexable value

Instances

(Read i, Indexable2D i) => Read (BinIx2D i) 
(Show i, Indexable2D i) => Show (BinIx2D i) 
Indexable2D i => Bin (BinIx2D i) 

binIx2D :: Indexable2D i => i -> i -> BinIx2D iSource

Construct indexed bin