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

Safe HaskellNone
LanguageHaskell2010

Data.Monoid.Statistics.Numeric

Contents

Synopsis

Mean & Variance

Number of elements

newtype CountG a Source #

Calculate number of elements in the sample.

Constructors

CountG 

Fields

Instances

Unbox a0 => Vector Vector (CountG a0) Source # 
Unbox a0 => MVector MVector (CountG a0) Source # 

Methods

basicLength :: MVector s (CountG a0) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (CountG a0) -> MVector s (CountG a0) #

basicOverlaps :: MVector s (CountG a0) -> MVector s (CountG a0) -> Bool #

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

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

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

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

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

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

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

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

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

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

Eq a => Eq (CountG a) Source # 

Methods

(==) :: CountG a -> CountG a -> Bool #

(/=) :: CountG a -> CountG a -> Bool #

Ord a => Ord (CountG a) Source # 

Methods

compare :: CountG a -> CountG a -> Ordering #

(<) :: CountG a -> CountG a -> Bool #

(<=) :: CountG a -> CountG a -> Bool #

(>) :: CountG a -> CountG a -> Bool #

(>=) :: CountG a -> CountG a -> Bool #

max :: CountG a -> CountG a -> CountG a #

min :: CountG a -> CountG a -> CountG a #

Show a => Show (CountG a) Source # 

Methods

showsPrec :: Int -> CountG a -> ShowS #

show :: CountG a -> String #

showList :: [CountG a] -> ShowS #

Integral a => Monoid (CountG a) Source # 

Methods

mempty :: CountG a #

mappend :: CountG a -> CountG a -> CountG a #

mconcat :: [CountG a] -> CountG a #

Unbox a0 => Unbox (CountG a0) Source # 
CalcCount (CountG Int) Source # 
Integral a => StatMonoid (CountG a) b Source # 

Methods

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

singletonMonoid :: b -> CountG a Source #

data MVector s (CountG a0) Source # 
data MVector s (CountG a0) = MV_CountG (MVector s a)
data Vector (CountG a0) Source # 
data Vector (CountG a0) = V_CountG (Vector a)

asCount :: CountG a -> CountG a Source #

Type restricted id

Mean

data MeanKBN Source #

Incremental calculation of mean. Sum of elements is calculated using Kahan-Babuška-Neumaier summation.

Constructors

MeanKBN !Int !KBNSum 

Instances

Eq MeanKBN Source # 

Methods

(==) :: MeanKBN -> MeanKBN -> Bool #

(/=) :: MeanKBN -> MeanKBN -> Bool #

Data MeanKBN Source # 

Methods

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

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

toConstr :: MeanKBN -> Constr #

dataTypeOf :: MeanKBN -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> MeanKBN -> MeanKBN #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MeanKBN -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MeanKBN -> r #

gmapQ :: (forall d. Data d => d -> u) -> MeanKBN -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MeanKBN -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MeanKBN -> m MeanKBN #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MeanKBN -> m MeanKBN #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MeanKBN -> m MeanKBN #

Show MeanKBN Source # 
Generic MeanKBN Source # 

Associated Types

type Rep MeanKBN :: * -> * #

Methods

from :: MeanKBN -> Rep MeanKBN x #

to :: Rep MeanKBN x -> MeanKBN #

Monoid MeanKBN Source # 
Unbox MeanKBN Source # 
CalcMean MeanKBN Source # 
CalcCount MeanKBN Source # 
Vector Vector MeanKBN Source # 
MVector MVector MeanKBN Source # 
Real a => StatMonoid MeanKBN a Source # 
type Rep MeanKBN Source # 
type Rep MeanKBN = D1 (MetaData "MeanKBN" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" False) (C1 (MetaCons "MeanKBN" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 KBNSum))))
data Vector MeanKBN Source # 
data MVector s MeanKBN Source # 

data WelfordMean Source #

Incremental calculation of mean. One of algorithm's advantage is protection against double overflow:

λ> calcMean $ asMeanKBN     $ reduceSample (replicate 100 1e308)
Just NaN
λ> calcMean $ asWelfordMean $ reduceSample (replicate 100 1e308)
Just 1.0e308

Algorithm is due to Welford [Welford1962]

Constructors

WelfordMean !Int !Double 

Instances

Eq WelfordMean Source # 
Data WelfordMean Source # 

Methods

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

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

toConstr :: WelfordMean -> Constr #

dataTypeOf :: WelfordMean -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> WelfordMean -> WelfordMean #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WelfordMean -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WelfordMean -> r #

gmapQ :: (forall d. Data d => d -> u) -> WelfordMean -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WelfordMean -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WelfordMean -> m WelfordMean #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WelfordMean -> m WelfordMean #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WelfordMean -> m WelfordMean #

Show WelfordMean Source # 
Generic WelfordMean Source # 

Associated Types

type Rep WelfordMean :: * -> * #

Monoid WelfordMean Source # 
Unbox WelfordMean Source # 
CalcMean WelfordMean Source # 
CalcCount WelfordMean Source # 
Vector Vector WelfordMean Source # 
MVector MVector WelfordMean Source # 
Real a => StatMonoid WelfordMean a Source #

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

type Rep WelfordMean Source # 
type Rep WelfordMean = D1 (MetaData "WelfordMean" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" False) (C1 (MetaCons "WelfordMean" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Double))))
data Vector WelfordMean Source # 
data MVector s WelfordMean Source # 

data MeanKahan Source #

Incremental calculation of mean. Sum of elements is calculated using compensated Kahan summation.

Constructors

MeanKahan !Int !KahanSum 

Instances

Eq MeanKahan Source # 
Data MeanKahan Source # 

Methods

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

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

toConstr :: MeanKahan -> Constr #

dataTypeOf :: MeanKahan -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> MeanKahan -> MeanKahan #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MeanKahan -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MeanKahan -> r #

gmapQ :: (forall d. Data d => d -> u) -> MeanKahan -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MeanKahan -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MeanKahan -> m MeanKahan #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MeanKahan -> m MeanKahan #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MeanKahan -> m MeanKahan #

Show MeanKahan Source # 
Generic MeanKahan Source # 

Associated Types

type Rep MeanKahan :: * -> * #

Monoid MeanKahan Source # 
CalcMean MeanKahan Source # 
CalcCount MeanKahan Source # 
Real a => StatMonoid MeanKahan a Source # 
type Rep MeanKahan Source # 
type Rep MeanKahan = D1 (MetaData "MeanKahan" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" False) (C1 (MetaCons "MeanKahan" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 KahanSum))))

Variance

data Variance Source #

Incremental algorithms for calculation the standard deviation.

Constructors

Variance !Int !Double !Double 

Instances

Eq Variance Source # 
Show Variance Source # 
Monoid Variance Source #

Iterative algorithm for calculation of variance [Chan1979]

Unbox Variance Source # 
CalcVariance Variance Source # 
CalcMean Variance Source # 
CalcCount Variance Source # 
Vector Vector Variance Source # 
MVector MVector Variance Source # 
Real a => StatMonoid Variance a Source # 
data Vector Variance Source # 
data MVector s Variance Source # 

asVariance :: Variance -> Variance Source #

Type restricted 'id '

Maximum and minimum

newtype Max a Source #

Calculate maximum of sample

Constructors

Max 

Fields

Instances

Eq a => Eq (Max a) Source # 

Methods

(==) :: Max a -> Max a -> Bool #

(/=) :: Max a -> Max a -> Bool #

Data a => Data (Max a) Source # 

Methods

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

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

toConstr :: Max a -> Constr #

dataTypeOf :: Max a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Max a) Source # 

Methods

compare :: Max a -> Max a -> Ordering #

(<) :: Max a -> Max a -> Bool #

(<=) :: Max a -> Max a -> Bool #

(>) :: Max a -> Max a -> Bool #

(>=) :: Max a -> Max a -> Bool #

max :: Max a -> Max a -> Max a #

min :: Max a -> Max a -> Max a #

Show a => Show (Max a) Source # 

Methods

showsPrec :: Int -> Max a -> ShowS #

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Generic (Max a) Source # 

Associated Types

type Rep (Max a) :: * -> * #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Ord a => Monoid (Max a) Source # 

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

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

Methods

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

singletonMonoid :: a' -> Max a Source #

type Rep (Max a) Source # 
type Rep (Max a) = D1 (MetaData "Max" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" True) (C1 (MetaCons "Max" PrefixI True) (S1 (MetaSel (Just Symbol "calcMax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))

newtype Min a Source #

Calculate minimum of sample

Constructors

Min 

Fields

Instances

Eq a => Eq (Min a) Source # 

Methods

(==) :: Min a -> Min a -> Bool #

(/=) :: Min a -> Min a -> Bool #

Data a => Data (Min a) Source # 

Methods

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

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

toConstr :: Min a -> Constr #

dataTypeOf :: Min a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Min a) Source # 

Methods

compare :: Min a -> Min a -> Ordering #

(<) :: Min a -> Min a -> Bool #

(<=) :: Min a -> Min a -> Bool #

(>) :: Min a -> Min a -> Bool #

(>=) :: Min a -> Min a -> Bool #

max :: Min a -> Min a -> Min a #

min :: Min a -> Min a -> Min a #

Show a => Show (Min a) Source # 

Methods

showsPrec :: Int -> Min a -> ShowS #

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Generic (Min a) Source # 

Associated Types

type Rep (Min a) :: * -> * #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Ord a => Monoid (Min a) Source # 

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

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

Methods

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

singletonMonoid :: a' -> Min a Source #

type Rep (Min a) Source # 
type Rep (Min a) = D1 (MetaData "Min" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" True) (C1 (MetaCons "Min" PrefixI True) (S1 (MetaSel (Just Symbol "calcMin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe a))))

newtype MaxD Source #

Calculate maximum of sample. For empty sample returns NaN. Any NaN encountered will be ignored.

Constructors

MaxD 

Fields

Instances

Eq MaxD Source # 

Methods

(==) :: MaxD -> MaxD -> Bool #

(/=) :: MaxD -> MaxD -> Bool #

Data MaxD Source # 

Methods

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

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

toConstr :: MaxD -> Constr #

dataTypeOf :: MaxD -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> MaxD -> MaxD #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MaxD -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MaxD -> r #

gmapQ :: (forall d. Data d => d -> u) -> MaxD -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MaxD -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MaxD -> m MaxD #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MaxD -> m MaxD #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MaxD -> m MaxD #

Show MaxD Source # 

Methods

showsPrec :: Int -> MaxD -> ShowS #

show :: MaxD -> String #

showList :: [MaxD] -> ShowS #

Generic MaxD Source # 

Associated Types

type Rep MaxD :: * -> * #

Methods

from :: MaxD -> Rep MaxD x #

to :: Rep MaxD x -> MaxD #

Monoid MaxD Source # 

Methods

mempty :: MaxD #

mappend :: MaxD -> MaxD -> MaxD #

mconcat :: [MaxD] -> MaxD #

Unbox MaxD Source # 
Vector Vector MaxD Source # 
MVector MVector MaxD Source # 
(~) * a Double => StatMonoid MaxD a Source # 

Methods

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

singletonMonoid :: a -> MaxD Source #

type Rep MaxD Source # 
type Rep MaxD = D1 (MetaData "MaxD" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" True) (C1 (MetaCons "MaxD" PrefixI True) (S1 (MetaSel (Just Symbol "calcMaxD") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))
data Vector MaxD Source # 
data MVector s MaxD Source # 

newtype MinD Source #

Calculate minimum of sample of Doubles. For empty sample returns NaN. Any NaN encountered will be ignored.

Constructors

MinD 

Fields

Instances

Eq MinD Source # 

Methods

(==) :: MinD -> MinD -> Bool #

(/=) :: MinD -> MinD -> Bool #

Data MinD Source # 

Methods

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

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

toConstr :: MinD -> Constr #

dataTypeOf :: MinD -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> MinD -> MinD #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MinD -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MinD -> r #

gmapQ :: (forall d. Data d => d -> u) -> MinD -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MinD -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MinD -> m MinD #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MinD -> m MinD #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MinD -> m MinD #

Show MinD Source # 

Methods

showsPrec :: Int -> MinD -> ShowS #

show :: MinD -> String #

showList :: [MinD] -> ShowS #

Generic MinD Source # 

Associated Types

type Rep MinD :: * -> * #

Methods

from :: MinD -> Rep MinD x #

to :: Rep MinD x -> MinD #

Monoid MinD Source # 

Methods

mempty :: MinD #

mappend :: MinD -> MinD -> MinD #

mconcat :: [MinD] -> MinD #

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

Methods

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

singletonMonoid :: a -> MinD Source #

type Rep MinD Source # 
type Rep MinD = D1 (MetaData "MinD" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" True) (C1 (MetaCons "MinD" PrefixI True) (S1 (MetaSel (Just Symbol "calcMinD") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)))
data Vector MinD Source # 
data MVector s MinD Source # 

Binomial trials

data BinomAcc Source #

Accumulator for binomial trials.

Constructors

BinomAcc 

Instances

Eq BinomAcc Source # 
Data BinomAcc Source # 

Methods

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

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

toConstr :: BinomAcc -> Constr #

dataTypeOf :: BinomAcc -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> BinomAcc -> BinomAcc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinomAcc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinomAcc -> r #

gmapQ :: (forall d. Data d => d -> u) -> BinomAcc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BinomAcc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinomAcc -> m BinomAcc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinomAcc -> m BinomAcc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinomAcc -> m BinomAcc #

Ord BinomAcc Source # 
Show BinomAcc Source # 
Generic BinomAcc Source # 

Associated Types

type Rep BinomAcc :: * -> * #

Methods

from :: BinomAcc -> Rep BinomAcc x #

to :: Rep BinomAcc x -> BinomAcc #

Monoid BinomAcc Source # 
StatMonoid BinomAcc Bool Source # 
type Rep BinomAcc Source # 
type Rep BinomAcc = D1 (MetaData "BinomAcc" "Data.Monoid.Statistics.Numeric" "monoid-statistics-1.0.0-BUUsxAADO983sT5IMhaEGM" False) (C1 (MetaCons "BinomAcc" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "binomAccSuccess") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Just Symbol "binomAccTotal") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int))))

asBinomAcc :: BinomAcc -> BinomAcc Source #

Type restricted id

Accessors

class CalcCount m where Source #

Accumulator could be used to evaluate number of elements in sample.

Minimal complete definition

calcCount

Methods

calcCount :: m -> Int Source #

Number of elements in sample

class CalcMean m where Source #

Monoids which could be used to calculate sample mean:

\[ \bar{x} = \frac{1}{N}\sum_{i=1}^N{x_i} \]

Minimal complete definition

calcMean

Methods

calcMean :: m -> Maybe Double Source #

Returns Nothing if there isn't enough data to make estimate.

class CalcVariance m where Source #

Monoids which could be used to calculate sample variance. Both methods return Nothing if there isn't enough data to make estimate.

Minimal complete definition

calcVariance, calcVarianceML

Methods

calcVariance :: m -> Maybe Double Source #

Calculate unbiased estimate of variance:

\[ \sigma^2 = \frac{1}{N-1}\sum_{i=1}^N(x_i - \bar{x})^2 \]

calcVarianceML :: m -> Maybe Double Source #

Calculate maximum likelihood estimate of variance:

\[ \sigma^2 = \frac{1}{N}\sum_{i=1}^N(x_i - \bar{x})^2 \]

calcStddev :: CalcVariance m => m -> Maybe Double Source #

Calculate sample standard deviation from unbiased estimation of variance:

\[ \sigma = \sqrt{\frac{1}{N-1}\sum_{i=1}^N(x_i - \bar{x})^2 } \]

calcStddevML :: CalcVariance m => m -> Maybe Double Source #

Calculate sample standard deviation from maximum likelihood estimation of variance:

\[ \sigma = \sqrt{\frac{1}{N}\sum_{i=1}^N(x_i - \bar{x})^2 } \]

References

  • [Welford1962] Welford, B.P. (1962) Note on a method for calculating corrected sums of squares and products. Technometrics 4(3):419-420. http://www.jstor.org/stable/1266577
  • [Chan1979] Chan, Tony F.; Golub, Gene H.; LeVeque, Randall J. (1979), Updating Formulae and a Pairwise Algorithm for Computing Sample Variances., Technical Report STAN-CS-79-773, Department of Computer Science, Stanford University. Page 4.