welford-online-mean-variance-0.1.0.4: Online computation of mean and variance using the Welford algorithm.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Statistics.Sample.WelfordOnlineMeanVariance

Synopsis

Documentation

data WelfordExistingAggregate a Source #

For the storage of required information.

Constructors

WelfordExistingAggregateEmpty

Emtpy aggregate. Needed as a can be of any type, which, hence, allows us to postpone determining a to when we receive the first value.

WelfordExistingAggregate 

Instances

Instances details
Generic (WelfordExistingAggregate a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

Associated Types

type Rep (WelfordExistingAggregate a) :: Type -> Type #

Read a => Read (WelfordExistingAggregate a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

Show a => Show (WelfordExistingAggregate a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

Serialize a => Serialize (WelfordExistingAggregate a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

NFData a => NFData (WelfordExistingAggregate a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

Methods

rnf :: WelfordExistingAggregate a -> () #

Eq a => Eq (WelfordExistingAggregate a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

type Rep (WelfordExistingAggregate a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

type Rep (WelfordExistingAggregate a) = D1 ('MetaData "WelfordExistingAggregate" "Statistics.Sample.WelfordOnlineMeanVariance" "welford-online-mean-variance-0.1.0.4-hxML6sAVpU3KBkNvVMB08" 'False) (C1 ('MetaCons "WelfordExistingAggregateEmpty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WelfordExistingAggregate" 'PrefixI 'True) (S1 ('MetaSel ('Just "welfordCountUnsafe") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "welfordMeanUnsafe") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Just "welfordM2Unsafe") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))))

class WelfordOnline a where Source #

Class for all data strucutres that can be used to computer the Welford approximation. For instance, this can be used to compute the Welford algorithm on a Vectors of Fractional, while only requiring to handle one WelfordExistingAggregate.

Methods

plus :: a -> a -> a Source #

minus :: a -> a -> a Source #

multiply :: a -> a -> a Source #

divideInt :: a -> Int -> a Source #

Instances

Instances details
WelfordOnline Rational Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

WelfordOnline Double Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

WelfordOnline Float Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

WelfordOnline a => WelfordOnline (Vector a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

Methods

plus :: Vector a -> Vector a -> Vector a Source #

minus :: Vector a -> Vector a -> Vector a Source #

multiply :: Vector a -> Vector a -> Vector a Source #

divideInt :: Vector a -> Int -> Vector a Source #

(WelfordOnline a, Storable a) => WelfordOnline (Vector a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

Methods

plus :: Vector a -> Vector a -> Vector a Source #

minus :: Vector a -> Vector a -> Vector a Source #

multiply :: Vector a -> Vector a -> Vector a Source #

divideInt :: Vector a -> Int -> Vector a Source #

(WelfordOnline a, Unbox a) => WelfordOnline (Vector a) Source # 
Instance details

Defined in Statistics.Sample.WelfordOnlineMeanVariance

Methods

plus :: Vector a -> Vector a -> Vector a Source #

minus :: Vector a -> Vector a -> Vector a Source #

multiply :: Vector a -> Vector a -> Vector a Source #

divideInt :: Vector a -> Int -> Vector a Source #

newWelfordAggregateDef :: WelfordOnline a => a -> WelfordExistingAggregate a Source #

Create a new empty Aggreate by specifying an example a value. It is safe to use the `*Unsafe` record field selectors from `WelfordExistingAggregate a`, when creating the data structure using this fuction.

newWelfordAggregate :: WelfordExistingAggregate a Source #

Create a new empty Aggreate for the calculation.

welfordCount :: WelfordExistingAggregate a -> Int Source #

Get counter safely, returns Nothing if WelfordExistingAggregateEmpty.

mWelfordMean :: WelfordExistingAggregate a -> Maybe a Source #

Get counter safely, returns Nothing if WelfordExistingAggregateEmpty.

welfordMeanDef :: WelfordOnline a => a -> WelfordExistingAggregate a -> a Source #

Get counter with specifying a default value.

addValue :: WelfordOnline a => WelfordExistingAggregate a -> a -> WelfordExistingAggregate a Source #

Add one value to the current aggregate.

addValues :: (WelfordOnline a, Foldable f) => WelfordExistingAggregate a -> f a -> WelfordExistingAggregate a Source #

Add multiple values to the current aggregate. This is `foldl addValue`.

mFinalize :: WelfordOnline a => WelfordExistingAggregate a -> Maybe (Mean a, Variance a, SampleVariance a) Source #

Calculate mean, variance and sample variance from aggregate. Safe function.

finalize :: WelfordOnline a => WelfordExistingAggregate a -> (Mean a, Variance a, SampleVariance a) Source #

Calculate mean, variance and sample variance from aggregate. Calls error for WelfordExistingAggregateEmpty.

nextValue :: WelfordOnline a => WelfordExistingAggregate a -> a -> (WelfordExistingAggregate a, (Mean a, Variance a, SampleVariance a)) Source #

Add a new sample to the aggregate and compute mean and variances.

isWelfordExistingAggregateEmpty :: WelfordExistingAggregate a -> Bool Source #

Check if it is aggregate is empty

type Mean a = a Source #

type Variance a = a Source #