statistics-0.16.2.0: A library of statistical types, data, and functions
Copyright(c) 2009 2010 Bryan O'Sullivan
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Statistics.Sample.Powers

Description

Very fast statistics over simple powers of a sample. These can all be computed efficiently in just a single pass over a sample, with that pass subject to stream fusion.

The tradeoff is that some of these functions are less numerically robust than their counterparts in the Sample module. Where this is the case, the alternatives are noted.

Synopsis

Types

data Powers Source #

Instances

Instances details
FromJSON Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

ToJSON Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

Data Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

Methods

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

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

toConstr :: Powers -> Constr #

dataTypeOf :: Powers -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

Associated Types

type Rep Powers :: Type -> Type #

Methods

from :: Powers -> Rep Powers x #

to :: Rep Powers x -> Powers #

Read Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

Show Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

Binary Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

Methods

put :: Powers -> Put #

get :: Get Powers #

putList :: [Powers] -> Put #

Eq Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

Methods

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

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

type Rep Powers Source # 
Instance details

Defined in Statistics.Sample.Powers

type Rep Powers = D1 ('MetaData "Powers" "Statistics.Sample.Powers" "statistics-0.16.2.0-Iazw6pxXVUYHaurUiPE2b2" 'True) (C1 ('MetaCons "Powers" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Vector Double))))

Constructor

powers Source #

Arguments

:: Vector v Double 
=> Int

n, the number of powers, where n >= 2.

-> v Double 
-> Powers 

O(n) Collect the n simple powers of a sample.

Functions computed over a sample's simple powers require at least a certain number (or order) of powers to be collected.

  • To compute the kth centralMoment, at least k simple powers must be collected.
  • For the variance, at least 2 simple powers are needed.
  • For skewness, we need at least 3 simple powers.
  • For kurtosis, at least 4 simple powers are required.

This function is subject to stream fusion.

Descriptive functions

order :: Powers -> Int Source #

The order (number) of simple powers collected from a sample.

count :: Powers -> Int Source #

The number of elements in the original Sample. This is the sample's zeroth simple power.

sum :: Powers -> Double Source #

The sum of elements in the original Sample. This is the sample's first simple power.

Statistics of location

mean :: Powers -> Double Source #

The arithmetic mean of elements in the original Sample.

This is less numerically robust than the mean function in the Sample module, but the number is essentially free to compute if you have already collected a sample's simple powers.

Statistics of dispersion

variance :: Powers -> Double Source #

Maximum likelihood estimate of a sample's variance. Also known as the population variance, where the denominator is n. This is the second central moment of the sample.

This is less numerically robust than the variance function in the Sample module, but the number is essentially free to compute if you have already collected a sample's simple powers.

Requires Powers with order at least 2.

stdDev :: Powers -> Double Source #

Standard deviation. This is simply the square root of the maximum likelihood estimate of the variance.

varianceUnbiased :: Powers -> Double Source #

Unbiased estimate of a sample's variance. Also known as the sample variance, where the denominator is n-1.

Requires Powers with order at least 2.

Functions over central moments

centralMoment :: Int -> Powers -> Double Source #

Compute the kth central moment of a sample. The central moment is also known as the moment about the mean.

skewness :: Powers -> Double Source #

Compute the skewness of a sample. This is a measure of the asymmetry of its distribution.

A sample with negative skew is said to be left-skewed. Most of its mass is on the right of the distribution, with the tail on the left.

skewness . powers 3 $ U.to [1,100,101,102,103]
==> -1.497681449918257

A sample with positive skew is said to be right-skewed.

skewness . powers 3 $ U.to [1,2,3,4,100]
==> 1.4975367033335198

A sample's skewness is not defined if its variance is zero.

Requires Powers with order at least 3.

kurtosis :: Powers -> Double Source #

Compute the excess kurtosis of a sample. This is a measure of the "peakedness" of its distribution. A high kurtosis indicates that the sample's variance is due more to infrequent severe deviations than to frequent modest deviations.

A sample's excess kurtosis is not defined if its variance is zero.

Requires Powers with order at least 4.

References