histogram-fill-0.9.0.0: Library for histograms creation.

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

Data.Histogram.Fill

Contents

Description

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

Synopsis

Builder type class

class HistBuilder h where Source #

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.

Minimal complete definition

modifyOut, modifyIn, fromContainer, addCut

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' b Source #

Change input of builder by applying function to it.

fromContainer Source #

Arguments

:: (forall m. Monad m => (a -> m ()) -> f a -> m ())

mapM_ function for container

-> h a b 
-> h (f a) b 

Put all values in container into builder

addCut :: (a -> Bool) -> h a b -> h a b Source #

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

Instances

HistBuilder HBuilder Source # 

Methods

modifyOut :: (b -> b') -> HBuilder a b -> HBuilder a b' Source #

modifyIn :: (a' -> a) -> HBuilder a b -> HBuilder a' b Source #

fromContainer :: (forall (m :: * -> *). Monad m => (a -> m ()) -> f a -> m ()) -> HBuilder a b -> HBuilder (f a) b Source #

addCut :: (a -> Bool) -> HBuilder a b -> HBuilder a b Source #

Monad m => HistBuilder (HBuilderM m) Source #

Builders modified using HistBuilder API will share the same buffer.

Methods

modifyOut :: (b -> b') -> HBuilderM m a b -> HBuilderM m a b' Source #

modifyIn :: (a' -> a) -> HBuilderM m a b -> HBuilderM m a' b Source #

fromContainer :: (forall (a :: * -> *). Monad a => (a -> a ()) -> f a -> a ()) -> HBuilderM m a b -> HBuilderM m (f a) b Source #

addCut :: (a -> Bool) -> HBuilderM m a b -> HBuilderM m a b Source #

Operators

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

Modify input of builder

(<<-|) :: (HistBuilder h, Foldable f) => h a b -> (a' -> f a) -> h a' b infixl 5 Source #

Modify input of builder to use composite input

(<<?) :: HistBuilder h => h a b -> (a -> Bool) -> h a b infixl 5 Source #

Add cut for input

(<<-$) :: h a b -> (h a b -> h a' b) -> h a' b infixl 5 Source #

Apply function which modify builder

(-<<) :: HistBuilder h => (b -> b') -> h a b -> h a b' infixr 4 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 a value to builder could be done with feedOne and the result could be extracted with freezeHBuilderM.

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

Constructors

HBuilderM 

Fields

Instances

Monad m => HistBuilder (HBuilderM m) Source #

Builders modified using HistBuilder API will share the same buffer.

Methods

modifyOut :: (b -> b') -> HBuilderM m a b -> HBuilderM m a b' Source #

modifyIn :: (a' -> a) -> HBuilderM m a b -> HBuilderM m a' b Source #

fromContainer :: (forall (a :: * -> *). Monad a => (a -> a ()) -> f a -> a ()) -> HBuilderM m a b -> HBuilderM m (f a) b Source #

addCut :: (a -> Bool) -> HBuilderM m a b -> HBuilderM m a b Source #

Monad m => Functor (HBuilderM m a) Source # 

Methods

fmap :: (a -> b) -> HBuilderM m a a -> HBuilderM m a b #

(<$) :: a -> HBuilderM m a b -> HBuilderM m a a #

Monad m => Applicative (HBuilderM m a) Source # 

Methods

pure :: a -> HBuilderM m a a #

(<*>) :: HBuilderM m a (a -> b) -> HBuilderM m a a -> HBuilderM m a b #

liftA2 :: (a -> b -> c) -> HBuilderM m a a -> HBuilderM m a b -> HBuilderM m a c #

(*>) :: HBuilderM m a a -> HBuilderM m a b -> HBuilderM m a b #

(<*) :: HBuilderM m a a -> HBuilderM m a b -> HBuilderM m a a #

(Monad m, Semigroup b) => Semigroup (HBuilderM m a b) Source # 

Methods

(<>) :: HBuilderM m a b -> HBuilderM m a b -> HBuilderM m a b #

sconcat :: NonEmpty (HBuilderM m a b) -> HBuilderM m a b #

stimes :: Integral b => b -> HBuilderM m a b -> HBuilderM m a b #

(Monad m, Monoid b) => Monoid (HBuilderM m a b) Source # 

Methods

mempty :: HBuilderM m a b #

mappend :: HBuilderM m a b -> HBuilderM m a b -> HBuilderM m a b #

mconcat :: [HBuilderM m a b] -> HBuilderM m a b #

feedOne :: HBuilderM m a b -> a -> m () Source #

Put one item into the histogram

freezeHBuilderM :: HBuilderM m a b -> m b Source #

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

Stateless

newtype HBuilder a b Source #

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

Constructors

HBuilder (forall m. PrimMonad m => m (HBuilderM m a b)) 

Instances

HistBuilder HBuilder Source # 

Methods

modifyOut :: (b -> b') -> HBuilder a b -> HBuilder a b' Source #

modifyIn :: (a' -> a) -> HBuilder a b -> HBuilder a' b Source #

fromContainer :: (forall (m :: * -> *). Monad m => (a -> m ()) -> f a -> m ()) -> HBuilder a b -> HBuilder (f a) b Source #

addCut :: (a -> Bool) -> HBuilder a b -> HBuilder a b Source #

Functor (HBuilder a) Source # 

Methods

fmap :: (a -> b) -> HBuilder a a -> HBuilder a b #

(<$) :: a -> HBuilder a b -> HBuilder a a #

Applicative (HBuilder a) Source # 

Methods

pure :: a -> HBuilder a a #

(<*>) :: HBuilder a (a -> b) -> HBuilder a a -> HBuilder a b #

liftA2 :: (a -> b -> c) -> HBuilder a a -> HBuilder a b -> HBuilder a c #

(*>) :: HBuilder a a -> HBuilder a b -> HBuilder a b #

(<*) :: HBuilder a a -> HBuilder a b -> HBuilder a a #

Semigroup b => Semigroup (HBuilder a b) Source # 

Methods

(<>) :: HBuilder a b -> HBuilder a b -> HBuilder a b #

sconcat :: NonEmpty (HBuilder a b) -> HBuilder a b #

stimes :: Integral b => b -> HBuilder a b -> HBuilder a b #

Monoid b => Monoid (HBuilder a b) Source # 

Methods

mempty :: HBuilder a b #

mappend :: HBuilder a b -> HBuilder a b -> HBuilder a b #

mconcat :: [HBuilder a b] -> HBuilder a b #

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

Convert the builder to stateful builder in the ST monad

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

Convert the builder to builder in the IO monad

toHBuilderM :: PrimMonad m => HBuilder a b -> m (HBuilderM m a b) Source #

Convert the builder to a stateful builder in a primitive monad

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 the histogram

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

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

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

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

mkFoldBuilder Source #

Arguments

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

Binning algorithm

-> val

Initial value

-> (val -> a -> val)

Folding function

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

Create a 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 the 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 the weight supplied for each item put into the histogram

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

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

mkFoldBuilderG Source #

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 b Source #

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

mkStatefulBuilder Source #

Arguments

:: (a -> m ())

Add value to accumulator

-> m b

Extract result from accumulator

-> HBuilderM m a b 

Create stateful histogram builder. The output function should be safe to call multiple times and the 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 -> b Source #

Fill histogram builder.

fillBuilderVec :: Vector v a => HBuilder a b -> v a -> b Source #

Fill histogram builder.

Auxillary functions

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

In example below forceInt used to fix type of the histogram to 'Histogram BinI Int'. Without it, the compiler cannot infer type of the 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 a pipeline. Also note that data flows from right to left as with the . operator.

First example just counts ints in the [0..4] inclusive range. fillBuilder is used to put all values into an 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 that only accepts even numbers. Filtering could be achieved with either addCut or the <<? operator.

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

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

Next example illustrates the use of an applicative interface. Here two histograms are filled at the same time. First accept only even numbers and second only the 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 sequenceA to simultaneously fill a list (or any other Traversable).

Data.Traversable.sequenceA [
    forceInt -<< mkSimple (BinI 0 4) <<? even
  , forceInt -<< mkSimple (BinI 0 4) <<? odd
  ]

If one wants to collect results from many histograms he can take an advantage of the 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
  ]

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

Deprecated: Use Data.Traversable.sequenceA instead

Join histogram builders in a container.

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

Deprecated: Use Data.Traversable.sequenceA instead

Join histogram builders in a container

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

Deprecated: Use Data.Traversable.traverse. treeHBuilderM fs h = F.traverse ($ h) fs

Apply functions to the builder

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

Deprecated: Use Data.Traversable.traverse. treeHBuilderM fs h = F.traverse ($ h) fs

Apply function to a builder