histogram-fill-0.7.3.0: Library for histograms creation.

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

Data.Histogram.Fill

Contents

Description

Stateful and pure (still stateful under the hood) accumulators.

Synopsis

Builder type class

class HistBuilder h whereSource

Type class for stateful accumulators. In this module they are called builders. Every builder is parametrized by two types. First one is type of values which are fed to accumulator and second one is type of values which could be extracted from it.

Every instance of HBuilder should be instance of Functor too and satisfy fmap == modifyOut.

Methods

modifyOut :: (b -> b') -> h a b -> h a b'Source

Apply function to output of histogram.

modifyIn :: (a' -> a) -> h a b -> h a' bSource

Change input of builder by applying function to it.

fromContainer :: Foldable f => h a b -> h (f a) bSource

Put all values in container into builder

addCut :: (a -> Bool) -> h a b -> h a bSource

Add cut to histogram. Value would be putted into histogram only if condition is true.

Instances

HistBuilder HBuilder 
PrimMonad m => HistBuilder (HBuilderM m)

Builders modified using HistBuilder API will share same buffer.

Operators

(<<-) :: HistBuilder h => h a b -> (a' -> a) -> h a' bSource

Modify input of builder

(<<-|) :: (HistBuilder h, Foldable f) => h a b -> (a' -> f a) -> h a' bSource

Modify input of builder to use composite input

(<<?) :: HistBuilder h => h a b -> (a -> Bool) -> h a bSource

Add cut for input

(<<-$) :: HistBuilder h => h a b -> (h a b -> h a' b) -> h a' bSource

Apply function which modify builder

(-<<) :: HistBuilder h => (b -> b') -> h a b -> h a b'Source

Modify output of histogram. In fact it's same as <$> but have opposite fixity

Histogram builders

Stateful

data HBuilderM m a b Source

Stateful histogram builder. Adding value to builder could be done with feedOne and result could be extracted with freezeHBuilderM.

There are two ways to obtain stateful builder. First and recommended is to thaw HBuilder using toHBuilderIO or toHBuilderST. Second is to use mkStatefulBuilder.

Instances

PrimMonad m => HistBuilder (HBuilderM m)

Builders modified using HistBuilder API will share same buffer.

PrimMonad m => Functor (HBuilderM m a) 
(Functor (HBuilderM m a), PrimMonad m) => Applicative (HBuilderM m a) 
(PrimMonad m, Monoid b) => Monoid (HBuilderM m a b) 

feedOne :: PrimMonad m => HBuilderM m a b -> a -> m ()Source

Put one item into histogram

freezeHBuilderM :: PrimMonad m => HBuilderM m a b -> m bSource

Extract result from histogram builder. It's safe to call this function multiple times and mutate builder afterwards.

joinHBuilderM :: (Traversable f, PrimMonad m) => f (HBuilderM m a b) -> HBuilderM m a (f b)Source

Join histogram builders in container

treeHBuilderM :: (PrimMonad m, Traversable f) => f (HBuilderM m a b -> HBuilderM m a' b') -> HBuilderM m a b -> HBuilderM m a' (f b')Source

Apply functions to builder

Stateless

newtype HBuilder a b Source

Wrapper around stateful histogram builder. It is much more convenient to work with than HBuilderM.

Constructors

HBuilder (forall s. ST s (HBuilderM (ST s) a b)) 

toHBuilderST :: HBuilder a b -> ST s (HBuilderM (ST s) a b)Source

Convert builder to stateful builder in ST monad

toHBuilderIO :: HBuilder a b -> IO (HBuilderM IO a b)Source

Convert builder to builder in IO monad

joinHBuilder :: Traversable f => f (HBuilder a b) -> HBuilder a (f b)Source

Join hitogram builders in container.

treeHBuilder :: Traversable f => f (HBuilder a b -> HBuilder a' b') -> HBuilder a b -> HBuilder a' (f b')Source

Apply function to builder

Histogram constructors

Using unboxed vectors

mkSimple :: (Bin bin, Unbox val, Num val) => bin -> HBuilder (BinValue bin) (Histogram bin val)Source

Create builder. Bin content will be incremented by 1 for each item put into histogram

mkWeighted :: (Bin bin, Unbox val, Num val) => bin -> HBuilder (BinValue bin, val) (Histogram bin val)Source

Create builder. Bin content will incremented by weight supplied for each item put into histogram

mkMonoidal :: (Bin bin, Unbox val, Monoid val) => bin -> HBuilder (BinValue bin, val) (Histogram bin val)Source

Create builder. New value wil be mappended to current content of a bin for each item put into histogram

mkFoldBuilderSource

Arguments

:: (Bin bin, Unbox val) 
=> bin

Binning algorithm

-> val

Initial value

-> (val -> a -> val)

Folding function

-> HBuilder (BinValue bin, a) (Histogram bin val) 

Create most generic histogram builder.

Using generic vectors

mkSimpleG :: (Bin bin, Vector v val, Num val) => bin -> HBuilder (BinValue bin) (Histogram v bin val)Source

Create builder. Bin content will be incremented by 1 for each item put into histogram

mkWeightedG :: (Bin bin, Vector v val, Num val) => bin -> HBuilder (BinValue bin, val) (Histogram v bin val)Source

Create builder. Bin content will incremented by weight supplied for each item put into histogram

mkMonoidalG :: (Bin bin, Vector v val, Monoid val) => bin -> HBuilder (BinValue bin, val) (Histogram v bin val)Source

Create builder. New value wil be mappended to current content of a bin for each item put into histogram

mkFoldBuilderGSource

Arguments

:: (Bin bin, Vector v val) 
=> bin

Binning algorithm

-> val

Initial value

-> (val -> a -> val)

Folding function

-> HBuilder (BinValue bin, a) (Histogram v bin val) 

Create most generic histogram builder.

Pure fold

mkFolder :: b -> (a -> b -> b) -> HBuilder a bSource

Create histogram builder which just does ordinary pure fold. It is intended for use when some fold should be performed together with histogram filling

Generic constructors

mkStatefulBuilderSource

Arguments

:: PrimMonad m 
=> (a -> m ())

Add value to accumulator

-> m b

Extract result from accumulator

-> HBuilderM m a b 

Create stateful histogram builder. Output function should be safe to call multiple times and builder could be modified afterwards. So functions like unsafeFreeze from vector couldn't be used.

Fill histograms

fillBuilder :: Foldable f => HBuilder a b -> f a -> bSource

Fill histogram builder.

fillBuilderVec :: Vector v a => HBuilder a b -> v a -> bSource

Fill histogram builder.

Auxillary functions

In some cases builder constructors do not constrain output type enough. Output type is still parametric in value type of histogram. Functions below are just id function with more restrictive signature.

In example below forceInt used to fix type of histogram to 'Histogram BinI Int'. Without it compiler cannot infer type of intermediate histogram.

 show . forceInt -<< mkSimple (BinI 1 10)

Examples

All examples will make use of operators to create builders. It's possible to avoid their use but operators offer clear notation and compose nicely in pipeline. Also note that data flows from right to left as with . operator.

First example just counts ints in in [0..4] inclusive range. fillBuilder is used to put all values into accumulator.

 ghci> let h = forceInt -<< mkSimple (BinI 0 4)
 ghci> fillBuilder h [0,0,0,1,1,2,3,4,4,4]
 # Histogram
 # Underflows = 0
 # Overflows  = 0
 # BinI
 # Low  = 0
 # High = 4
 0       3
 1       2
 2       1
 3       1
 4       3

More involved example only accept even numbers. Filtering could be achieved with either addCut or <<? operator.

 forceInt -<< mkSimple (BinI 0 4) <<? even

Although for example above same result could be acheved by filtering of input it doesn't work when multiple histograms with different cuts are filled simultaneously.

Next example illustrate use of applicative interface. Here two histograms are filled at the same time. First accept only even numbers and second only odd ones. Results are put into the tuple.

 (,) <$> 
   (forceInt -<< mkSimple (BinI 0 4) <<? even)
   (forceInt -<< mkSimple (BinI 0 4) <<? odd)

Another approach is to use joinHBuilder to simultaneously fill list (or any other Travesable).

 joinHBuilder [
     forceInt -<< mkSimple (BinI 0 4) <<? even
   , forceInt -<< mkSimple (BinI 0 4) <<? odd
   ]

If one wants to collect result from many histograms he can take an advantage of Monoid instance of HBuilder. Example below concatenates string outputs of individual histograms.

 mconcat [
     show . forceInt -<< mkSimple (BinI 0 4) <<? even
   , show . forceInt -<< mkSimple (BinI 0 4) <<? odd
   ]