Stability | experimental |
---|---|
Maintainer | Alexey Khudyakov <alexey.skladnoy@gmail.com> |
Safe Haskell | Safe-Infered |
Stateful and pure (still stateful under the hood) accumulators.
- class HistBuilder h where
- (<<-) :: HistBuilder h => h a b -> (a' -> a) -> h a' b
- (<<-|) :: (HistBuilder h, Foldable f) => h a b -> (a' -> f a) -> h a' b
- (<<?) :: HistBuilder h => h a b -> (a -> Bool) -> h a b
- (<<-$) :: HistBuilder h => h a b -> (h a b -> h a' b) -> h a' b
- (-<<) :: HistBuilder h => (b -> b') -> h a b -> h a b'
- data HBuilderM m a b
- feedOne :: PrimMonad m => HBuilderM m a b -> a -> m ()
- freezeHBuilderM :: PrimMonad m => HBuilderM m a b -> m b
- joinHBuilderM :: (Traversable f, PrimMonad m) => f (HBuilderM m a b) -> HBuilderM m a (f b)
- treeHBuilderM :: (PrimMonad m, Traversable f) => f (HBuilderM m a b -> HBuilderM m a' b') -> HBuilderM m a b -> HBuilderM m a' (f b')
- data HBuilder a b
- toHBuilderST :: HBuilder a b -> forall s. ST s (HBuilderM (ST s) a b)
- toHBuilderIO :: HBuilder a b -> IO (HBuilderM IO a b)
- joinHBuilder :: Traversable f => f (HBuilder a b) -> HBuilder a (f b)
- treeHBuilder :: Traversable f => f (HBuilder a b -> HBuilder a' b') -> HBuilder a b -> HBuilder a' (f b')
- module Data.Histogram.Bin
- mkSimple :: (Bin bin, Unbox val, Num val) => bin -> HBuilder (BinValue bin) (Histogram bin val)
- mkWeighted :: (Bin bin, Unbox val, Num val) => bin -> HBuilder (BinValue bin, val) (Histogram bin val)
- mkMonoidal :: (Bin bin, Unbox val, Monoid val) => bin -> HBuilder (BinValue bin, val) (Histogram bin val)
- mkFoldBuilder :: (Bin bin, Unbox val) => bin -> val -> (val -> a -> val) -> HBuilder (BinValue bin, a) (Histogram bin val)
- mkSimpleG :: (Bin bin, Vector v val, Num val) => bin -> HBuilder (BinValue bin) (Histogram v bin val)
- mkWeightedG :: (Bin bin, Vector v val, Num val) => bin -> HBuilder (BinValue bin, val) (Histogram v bin val)
- mkMonoidalG :: (Bin bin, Vector v val, Monoid val) => bin -> HBuilder (BinValue bin, val) (Histogram v bin val)
- mkFoldBuilderG :: (Bin bin, Vector v val) => bin -> val -> (val -> a -> val) -> HBuilder (BinValue bin, a) (Histogram v bin val)
- mkFolder :: b -> (a -> b -> b) -> HBuilder a b
- fillBuilder :: Foldable f => HBuilder a b -> f a -> b
- fillBuilderVec :: Vector v a => HBuilder a b -> v a -> b
- forceInt :: Histogram v bin Int -> Histogram v bin Int
- forceDouble :: Histogram v bin Double -> Histogram v bin Double
- forceFloat :: Histogram v bin Float -> Histogram v bin Float
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
.
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.
HistBuilder HBuilder | |
PrimMonad m => HistBuilder (HBuilderM m) |
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
Stateful histogram builder. There is no direct way to construct
such builder. Only way to do it is to create HBuilder
and use
toHBuilderST
or toHBuilderIO
.
It's useful when result should be extracted many times from the same accumulator.
freezeHBuilderM :: PrimMonad m => HBuilderM m a b -> m bSource
Create stateful histogram from instructions. Histograms could be filled either in the ST monad or with createHistograms
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
Stateless histogram builder
HistBuilder HBuilder | |
Functor (HBuilder a) | |
Applicative (HBuilder a) | |
Monoid b => Monoid (HBuilder a b) |
toHBuilderST :: HBuilder a b -> forall s. ST s (HBuilderM (ST s) a b)Source
Convert builder to stateful builder in ST 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
module Data.Histogram.Bin
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
:: (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
:: (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
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 ]