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

Safe HaskellNone
LanguageHaskell98

Statistics.Test.ChiSquared

Contents

Description

Pearson's chi squared test.

Synopsis

Documentation

chi2test Source #

Arguments

:: (Vector v (Int, Double), Vector v Double) 
=> Double

p-value

-> Int

Number of additional degrees of freedom. One degree of freedom is due to the fact that the are N observation in total and accounted for automatically.

-> v (Int, Double)

Observation and expectation.

-> TestResult 

Generic form of Pearson chi squared tests for binned data. Data sample is supplied in form of tuples (observed quantity, expected number of events). Both must be positive.

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))