welford-online-mean-variance-0.2.0.0: 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.2.0.0-L6Fs4vF6LiXEfWZpb878mM" '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 structures 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 infixl 6 Source #

Arguments

:: a 
-> a 
-> a

Addition.

minus infixl 6 Source #

Arguments

:: a 
-> a 
-> a

Subtraction.

multiply infixl 7 Source #

Arguments

:: a 
-> a 
-> a

Multiplication.

divide infixl 7 Source #

Arguments

:: a 
-> a 
-> a

Division.

divideInt infixl 7 Source #

Arguments

:: a 
-> Int 
-> a

Division by Integer.

constInt Source #

Arguments

:: a 
-> Int 
-> a

Takes one example vector and a integer value and returns a vector of this integer.

squareRootMax Source #

Arguments

:: a 
-> a

Compute the square root. Ensure the output is >=1e-3. Used for normalisation.

clipValue Source #

Arguments

:: Double 
-> a 
-> a

Clip the value(s) to the given range. Used for normalisation.

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

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

Defined in Statistics.Sample.WelfordOnlineMeanVariance

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

Defined in Statistics.Sample.WelfordOnlineMeanVariance

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.

mWelfordMean :: WelfordExistingAggregate a -> Maybe a Source #

Get mean safely, returns Nothing if WelfordExistingAggregateEmpty as the type of a (e.g. length of vector) is unknown.

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

Get mean 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

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

Normalise the given input assuming the learned standard deviation with sample variance to zero mean and unit variance. For the first 100 values the output is clipped to (-3, 3).

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

Denormalise from a zero mean unit variance normalised value (see normaliseToZeroMeanUnitVariance) to the original value(s).

type Mean a = a Source #

type Variance a = a Source #