monoid-statistics-1.0.0: Monoids for calculation of statistics of sample

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

Data.Monoid.Statistics.Class

Contents

Description

 

Synopsis

Type class and helpers

class Monoid m => StatMonoid m a where Source #

This type class is used to express parallelizable constant space algorithms for calculation of statistics. By definitions statistic is some measure of sample which doesn't depend on order of elements (for example: mean, sum, number of elements, variance, etc).

For many statistics it's possible to possible to construct constant space algorithm which is expressed as fold. Additionally it's usually possible to write function which combine state of fold accumulator to get statistic for union of two samples.

Thus for such algorithm we have value which corresponds to empty sample, merge function which which corresponds to merging of two samples, and single step of fold. Last one allows to evaluate statistic given data sample and first two form a monoid and allow parallelization: split data into parts, build estimate for each by folding and then merge them using mappend.

Instance must satisfy following laws. If floating point arithmetics is used then equality should be understood as approximate.

1. addValue (addValue y mempty) x  == addValue mempty x <> addValue mempty y
2. x <> y == y <> x

Minimal complete definition

addValue | singletonMonoid

Methods

addValue :: m -> a -> m Source #

Add one element to monoid accumulator. It's step of fold.

singletonMonoid :: a -> m Source #

State of accumulator corresponding to 1-element sample.

Instances

Real a => StatMonoid KBNSum a Source # 
Real a => StatMonoid KahanSum a Source # 
StatMonoid BinomAcc Bool Source # 
(~) * a Double => StatMonoid MaxD a Source # 

Methods

addValue :: MaxD -> a -> MaxD Source #

singletonMonoid :: a -> MaxD Source #

(~) * a Double => StatMonoid MinD a Source # 

Methods

addValue :: MinD -> a -> MinD Source #

singletonMonoid :: a -> MinD Source #

Real a => StatMonoid Variance a Source # 
Real a => StatMonoid WelfordMean a Source #

\[ s_n = s_{n-1} + \frac{x_n - s_{n-1}}{n} \]

Real a => StatMonoid MeanKBN a Source # 
Real a => StatMonoid MeanKahan a Source # 
(Num a, (~) * a a') => StatMonoid (Sum a) a' Source # 

Methods

addValue :: Sum a -> a' -> Sum a Source #

singletonMonoid :: a' -> Sum a Source #

(Num a, (~) * a a') => StatMonoid (Product a) a' Source # 

Methods

addValue :: Product a -> a' -> Product a Source #

singletonMonoid :: a' -> Product a Source #

(Ord a, (~) * a a') => StatMonoid (Max a) a' Source # 

Methods

addValue :: Max a -> a' -> Max a Source #

singletonMonoid :: a' -> Max a Source #

(Ord a, (~) * a a') => StatMonoid (Min a) a' Source # 

Methods

addValue :: Min a -> a' -> Min a Source #

singletonMonoid :: a' -> Min a Source #

Integral a => StatMonoid (CountG a) b Source # 

Methods

addValue :: CountG a -> b -> CountG a Source #

singletonMonoid :: b -> CountG a Source #

(StatMonoid a x, StatMonoid b x) => StatMonoid (Pair a b) x Source # 

Methods

addValue :: Pair a b -> x -> Pair a b Source #

singletonMonoid :: x -> Pair a b Source #

reduceSample :: (Foldable f, StatMonoid m a) => f a -> m Source #

Calculate statistic over Foldable. It's implemented in terms of foldl'.

reduceSampleVec :: (Vector v a, StatMonoid m a) => v a -> m Source #

Calculate statistic over vector. It's implemented in terms of foldl'.

Data types

data Pair a b Source #

Strict pair. It allows to calculate two statistics in parallel

Constructors

Pair !a !b 

Instances

(Unbox a0, Unbox b0) => Vector Vector (Pair a0 b0) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Pair a0 b0) -> m (Vector (Pair a0 b0)) #

basicUnsafeThaw :: PrimMonad m => Vector (Pair a0 b0) -> m (Mutable Vector (PrimState m) (Pair a0 b0)) #

basicLength :: Vector (Pair a0 b0) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Pair a0 b0) -> Vector (Pair a0 b0) #

basicUnsafeIndexM :: Monad m => Vector (Pair a0 b0) -> Int -> m (Pair a0 b0) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Pair a0 b0) -> Vector (Pair a0 b0) -> m () #

elemseq :: Vector (Pair a0 b0) -> Pair a0 b0 -> b -> b #

(Unbox a0, Unbox b0) => MVector MVector (Pair a0 b0) Source # 

Methods

basicLength :: MVector s (Pair a0 b0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Pair a0 b0) -> MVector s (Pair a0 b0) #

basicOverlaps :: MVector s (Pair a0 b0) -> MVector s (Pair a0 b0) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Pair a0 b0)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Pair a0 b0) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Pair a0 b0 -> m (MVector (PrimState m) (Pair a0 b0)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Pair a0 b0) -> Int -> m (Pair a0 b0) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Pair a0 b0) -> Int -> Pair a0 b0 -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Pair a0 b0) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Pair a0 b0) -> Pair a0 b0 -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Pair a0 b0) -> MVector (PrimState m) (Pair a0 b0) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Pair a0 b0) -> MVector (PrimState m) (Pair a0 b0) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Pair a0 b0) -> Int -> m (MVector (PrimState m) (Pair a0 b0)) #

(Eq b, Eq a) => Eq (Pair a b) Source # 

Methods

(==) :: Pair a b -> Pair a b -> Bool #

(/=) :: Pair a b -> Pair a b -> Bool #

(Data b, Data a) => Data (Pair a b) Source # 

Methods

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

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

toConstr :: Pair a b -> Constr #

dataTypeOf :: Pair a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Pair a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pair a b)) #

gmapT :: (forall c. Data c => c -> c) -> Pair a b -> Pair a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pair a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pair a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Pair a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Pair a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pair a b -> m (Pair a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pair a b -> m (Pair a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pair a b -> m (Pair a b) #

(Ord b, Ord a) => Ord (Pair a b) Source # 

Methods

compare :: Pair a b -> Pair a b -> Ordering #

(<) :: Pair a b -> Pair a b -> Bool #

(<=) :: Pair a b -> Pair a b -> Bool #

(>) :: Pair a b -> Pair a b -> Bool #

(>=) :: Pair a b -> Pair a b -> Bool #

max :: Pair a b -> Pair a b -> Pair a b #

min :: Pair a b -> Pair a b -> Pair a b #

(Show b, Show a) => Show (Pair a b) Source # 

Methods

showsPrec :: Int -> Pair a b -> ShowS #

show :: Pair a b -> String #

showList :: [Pair a b] -> ShowS #

Generic (Pair a b) Source # 

Associated Types

type Rep (Pair a b) :: * -> * #

Methods

from :: Pair a b -> Rep (Pair a b) x #

to :: Rep (Pair a b) x -> Pair a b #

(Monoid a, Monoid b) => Monoid (Pair a b) Source # 

Methods

mempty :: Pair a b #

mappend :: Pair a b -> Pair a b -> Pair a b #

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

(Unbox a0, Unbox b0) => Unbox (Pair a0 b0) Source # 
(StatMonoid a x, StatMonoid b x) => StatMonoid (Pair a b) x Source # 

Methods

addValue :: Pair a b -> x -> Pair a b Source #

singletonMonoid :: x -> Pair a b Source #

data MVector s (Pair a0 b0) Source # 
data MVector s (Pair a0 b0) = MV_Pair (MVector s (a, b))
type Rep (Pair a b) Source # 
type Rep (Pair a b) = D1 (MetaData "Pair" "Data.Monoid.Statistics.Class" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" False) (C1 (MetaCons "Pair" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))))
data Vector (Pair a0 b0) Source # 
data Vector (Pair a0 b0) = V_Pair (Vector (a, b))

Orphan instances