statistics-0.13.3.0: A library of statistical types, data, and functions

Copyright(c) 2011 Aleksey Khudyakov
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Statistics.Test.KolmogorovSmirnov

Contents

Description

Kolmogov-Smirnov tests are non-parametric tests for assesing whether given sample could be described by distribution or whether two samples have the same distribution. It's only applicable to continous distributions.

Synopsis

Kolmogorov-Smirnov test

kolmogorovSmirnovTest Source #

Arguments

:: Distribution d 
=> d

Distribution

-> Double

p-value

-> Sample

Data sample

-> TestResult 

Check that sample could be described by distribution. Significant means distribution is not compatible with data for given p-value.

This test uses Marsaglia-Tsang-Wang exact alogorithm for calculation of p-value.

kolmogorovSmirnovTestCdf Source #

Arguments

:: (Double -> Double)

CDF of distribution

-> Double

p-value

-> Sample

Data sample

-> TestResult 

Variant of kolmogorovSmirnovTest which uses CFD in form of function.

kolmogorovSmirnovTest2 Source #

Arguments

:: Double

p-value

-> Sample

Sample 1

-> Sample

Sample 2

-> TestResult 

Two sample Kolmogorov-Smirnov test. It tests whether two data samples could be described by the same distribution without making any assumptions about it.

This test uses approxmate formula for computing p-value.

Evaluate statistics

kolmogorovSmirnovCdfD Source #

Arguments

:: (Double -> Double)

CDF function

-> Sample

Sample

-> Double 

Calculate Kolmogorov's statistic D for given cumulative distribution function (CDF) and data sample. If sample is empty returns 0.

kolmogorovSmirnovD Source #

Arguments

:: Distribution d 
=> d

Distribution

-> Sample

Sample

-> Double 

Calculate Kolmogorov's statistic D for given cumulative distribution function (CDF) and data sample. If sample is empty returns 0.

kolmogorovSmirnov2D Source #

Arguments

:: Sample

First sample

-> Sample

Second sample

-> Double 

Calculate Kolmogorov's statistic D for two data samples. If either of samples is empty returns 0.

Probablities

kolmogorovSmirnovProbability Source #

Arguments

:: Int

Size of the sample

-> Double

D value

-> Double 

Calculate cumulative probability function for Kolmogorov's distribution with n parameters or probability of getting value smaller than d with n-elements sample.

It uses algorithm by Marsgalia et. al. and provide at least 7-digit accuracy.

Data types

data TestType Source #

Test type. Exact meaning depends on a specific test. But generally it's tested whether some statistics is too big (small) for OneTailed or whether it too big or too small for TwoTailed

Constructors

OneTailed 
TwoTailed 

Instances

Eq TestType Source # 
Data TestType Source # 

Methods

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

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

toConstr :: TestType -> Constr #

dataTypeOf :: TestType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TestType Source # 
Show TestType Source # 
Generic TestType Source # 

Associated Types

type Rep TestType :: * -> * #

Methods

from :: TestType -> Rep TestType x #

to :: Rep TestType x -> TestType #

ToJSON TestType Source # 
FromJSON TestType Source # 
type Rep TestType Source # 
type Rep TestType = D1 (MetaData "TestType" "Statistics.Test.Types" "statistics-0.13.3.0-4cjYwUsSjEQGDMfnb5oeqe" False) ((:+:) (C1 (MetaCons "OneTailed" PrefixI False) U1) (C1 (MetaCons "TwoTailed" PrefixI False) U1))

data TestResult Source #

Result of hypothesis testing

Constructors

Significant

Null hypothesis should be rejected

NotSignificant

Data is compatible with hypothesis

Instances

Eq TestResult Source # 
Data TestResult Source # 

Methods

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

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

toConstr :: TestResult -> Constr #

dataTypeOf :: TestResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TestResult Source # 
Show TestResult Source # 
Generic TestResult Source # 

Associated Types

type Rep TestResult :: * -> * #

ToJSON TestResult Source # 
FromJSON TestResult Source # 
type Rep TestResult Source # 
type Rep TestResult = D1 (MetaData "TestResult" "Statistics.Test.Types" "statistics-0.13.3.0-4cjYwUsSjEQGDMfnb5oeqe" False) ((:+:) (C1 (MetaCons "Significant" PrefixI False) U1) (C1 (MetaCons "NotSignificant" PrefixI False) U1))

References

  • G. Marsaglia, W. W. Tsang, J. Wang (2003) Evaluating Kolmogorov's distribution, Journal of Statistical Software, American Statistical Association, vol. 8(i18).