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

Safe HaskellNone
LanguageHaskell98

Statistics.Test.Types

Synopsis

Documentation

data Test distr #

Result of statistical test.

Constructors

Test 

Fields

Instances
Functor Test # 
Instance details

Defined in Statistics.Test.Types

Methods

fmap :: (a -> b) -> Test a -> Test b #

(<$) :: a -> Test b -> Test a #

Eq distr => Eq (Test distr) # 
Instance details

Defined in Statistics.Test.Types

Methods

(==) :: Test distr -> Test distr -> Bool #

(/=) :: Test distr -> Test distr -> Bool #

Data distr => Data (Test distr) # 
Instance details

Defined in Statistics.Test.Types

Methods

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

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

toConstr :: Test distr -> Constr #

dataTypeOf :: Test distr -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord distr => Ord (Test distr) # 
Instance details

Defined in Statistics.Test.Types

Methods

compare :: Test distr -> Test distr -> Ordering #

(<) :: Test distr -> Test distr -> Bool #

(<=) :: Test distr -> Test distr -> Bool #

(>) :: Test distr -> Test distr -> Bool #

(>=) :: Test distr -> Test distr -> Bool #

max :: Test distr -> Test distr -> Test distr #

min :: Test distr -> Test distr -> Test distr #

Show distr => Show (Test distr) # 
Instance details

Defined in Statistics.Test.Types

Methods

showsPrec :: Int -> Test distr -> ShowS #

show :: Test distr -> String #

showList :: [Test distr] -> ShowS #

Generic (Test distr) # 
Instance details

Defined in Statistics.Test.Types

Associated Types

type Rep (Test distr) :: Type -> Type #

Methods

from :: Test distr -> Rep (Test distr) x #

to :: Rep (Test distr) x -> Test distr #

NFData d => NFData (Test d) # 
Instance details

Defined in Statistics.Test.Types

Methods

rnf :: Test d -> () #

ToJSON d => ToJSON (Test d) # 
Instance details

Defined in Statistics.Test.Types

FromJSON d => FromJSON (Test d) # 
Instance details

Defined in Statistics.Test.Types

Binary d => Binary (Test d) # 
Instance details

Defined in Statistics.Test.Types

Methods

put :: Test d -> Put #

get :: Get (Test d) #

putList :: [Test d] -> Put #

type Rep (Test distr) # 
Instance details

Defined in Statistics.Test.Types

type Rep (Test distr) = D1 (MetaData "Test" "Statistics.Test.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" False) (C1 (MetaCons "Test" PrefixI True) (S1 (MetaSel (Just "testSignificance") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (PValue Double)) :*: (S1 (MetaSel (Just "testStatistics") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double) :*: S1 (MetaSel (Just "testDistribution") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 distr))))

isSignificant :: PValue Double -> Test d -> TestResult #

Check whether test is significant for given p-value.

data TestResult #

Result of hypothesis testing

Constructors

Significant

Null hypothesis should be rejected

NotSignificant

Data is compatible with hypothesis

Instances
Eq TestResult # 
Instance details

Defined in Statistics.Test.Types

Data TestResult # 
Instance details

Defined in Statistics.Test.Types

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 # 
Instance details

Defined in Statistics.Test.Types

Show TestResult # 
Instance details

Defined in Statistics.Test.Types

Generic TestResult # 
Instance details

Defined in Statistics.Test.Types

Associated Types

type Rep TestResult :: Type -> Type #

NFData TestResult # 
Instance details

Defined in Statistics.Test.Types

Methods

rnf :: TestResult -> () #

ToJSON TestResult # 
Instance details

Defined in Statistics.Test.Types

FromJSON TestResult # 
Instance details

Defined in Statistics.Test.Types

Binary TestResult # 
Instance details

Defined in Statistics.Test.Types

type Rep TestResult # 
Instance details

Defined in Statistics.Test.Types

type Rep TestResult = D1 (MetaData "TestResult" "Statistics.Test.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" False) (C1 (MetaCons "Significant" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NotSignificant" PrefixI False) (U1 :: Type -> Type))

significant :: Bool -> TestResult #

significant if parameter is True, not significant otherwise

data PositionTest #

Test type for test which compare positional (mean,median etc.) information of samples.

Constructors

SamplesDiffer

Test whether samples differ in position. Null hypothesis is samples are not different

AGreater

Test if first sample (A) is larger than second (B). Null hypothesis is first sample is not larger than second.

BGreater

Test if second sample is larger than first.

Instances
Eq PositionTest # 
Instance details

Defined in Statistics.Test.Types

Data PositionTest # 
Instance details

Defined in Statistics.Test.Types

Methods

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

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

toConstr :: PositionTest -> Constr #

dataTypeOf :: PositionTest -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PositionTest # 
Instance details

Defined in Statistics.Test.Types

Show PositionTest # 
Instance details

Defined in Statistics.Test.Types

Generic PositionTest # 
Instance details

Defined in Statistics.Test.Types

Associated Types

type Rep PositionTest :: Type -> Type #

NFData PositionTest # 
Instance details

Defined in Statistics.Test.Types

Methods

rnf :: PositionTest -> () #

ToJSON PositionTest # 
Instance details

Defined in Statistics.Test.Types

FromJSON PositionTest # 
Instance details

Defined in Statistics.Test.Types

Binary PositionTest # 
Instance details

Defined in Statistics.Test.Types

type Rep PositionTest # 
Instance details

Defined in Statistics.Test.Types

type Rep PositionTest = D1 (MetaData "PositionTest" "Statistics.Test.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" False) (C1 (MetaCons "SamplesDiffer" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AGreater" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "BGreater" PrefixI False) (U1 :: Type -> Type)))