Copyright | (c) 2009 Bryan O'Sullivan |
---|---|
License | BSD3 |
Maintainer | bos@serpentine.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
Data types common used in statistics
- data CL a
- confidenceLevel :: Num a => CL a -> a
- significanceLevel :: CL a -> a
- mkCL :: (Ord a, Num a) => a -> CL a
- mkCLE :: (Ord a, Num a) => a -> Maybe (CL a)
- mkCLFromSignificance :: (Ord a, Num a) => a -> CL a
- mkCLFromSignificanceE :: (Ord a, Num a) => a -> Maybe (CL a)
- cl90 :: Fractional a => CL a
- cl95 :: Fractional a => CL a
- cl99 :: Fractional a => CL a
- nSigma :: Double -> PValue Double
- nSigma1 :: Double -> PValue Double
- getNSigma :: PValue Double -> Double
- getNSigma1 :: PValue Double -> Double
- data PValue a
- pValue :: PValue a -> a
- mkPValue :: (Ord a, Num a) => a -> PValue a
- mkPValueE :: (Ord a, Num a) => a -> Maybe (PValue a)
- data Estimate e a = Estimate {}
- newtype NormalErr a = NormalErr {
- normalError :: a
- data ConfInt a = ConfInt {
- confIntLDX :: !a
- confIntUDX :: !a
- confIntCL :: !(CL Double)
- data UpperLimit a = UpperLimit {
- upperLimit :: !a
- ulConfidenceLevel :: !(CL Double)
- data LowerLimit a = LowerLimit {
- lowerLimit :: !a
- llConfidenceLevel :: !(CL Double)
- estimateNormErr :: a -> a -> Estimate NormalErr a
- (±) :: a -> a -> Estimate NormalErr a
- estimateFromInterval :: Num a => a -> (a, a) -> CL Double -> Estimate ConfInt a
- estimateFromErr :: a -> (a, a) -> CL Double -> Estimate ConfInt a
- confidenceInterval :: Num a => Estimate ConfInt a -> (a, a)
- asymErrors :: Estimate ConfInt a -> (a, a)
- class Scale e where
- type Sample = Vector Double
- type WeightedSample = Vector (Double, Double)
- type Weights = Vector Double
Confidence level
Confidence level. In context of confidence intervals it's
probability of said interval covering true value of measured
value. In context of statistical tests it's 1-α
where α is
significance of test.
Since confidence level are usually close to 1 they are stored as
1-CL
internally. There are two smart constructors for CL
:
mkCL
and mkCLFromSignificance
(and corresponding variant
returning Maybe
). First creates CL
from confidence level and
second from 1 - CL
or significance level.
>>>
cl95
mkCLFromSignificance 0.05
Prior to 0.14 confidence levels were passed to function as plain
Doubles
. Use mkCL
to convert them to CL
.
Unbox a0 => Vector Vector (CL a0) Source # | |
Unbox a0 => MVector MVector (CL a0) Source # | |
Eq a => Eq (CL a) Source # | |
Data a => Data (CL a) Source # | |
Ord a => Ord (CL a) Source # |
|
(Num a, Ord a, Read a) => Read (CL a) Source # | |
Show a => Show (CL a) Source # | |
Generic (CL a) Source # | |
NFData a => NFData (CL a) Source # | |
ToJSON a => ToJSON (CL a) Source # | |
(FromJSON a, Num a, Ord a) => FromJSON (CL a) Source # | |
(Binary a, Num a, Ord a) => Binary (CL a) Source # | |
Unbox a0 => Unbox (CL a0) Source # | |
data MVector s (CL a0) Source # | |
type Rep (CL a) Source # | |
data Vector (CL a0) Source # | |
Accessors
confidenceLevel :: Num a => CL a -> a Source #
Get confidence level. This function is subject to rounding
errors. If 1 - CL
is needed use significanceLevel
instead
significanceLevel :: CL a -> a Source #
Get significance level.
Constructors
mkCL :: (Ord a, Num a) => a -> CL a Source #
Create confidence level from probability β or probability confidence interval contain true value of estimate. Will throw exception if parameter is out of [0,1] range
>>>
mkCL 0.95 -- same as cl95
mkCLFromSignificance 0.05
mkCLE :: (Ord a, Num a) => a -> Maybe (CL a) Source #
Same as mkCL
but returns Nothing
instead of error if
parameter is out of [0,1] range
>>>
mkCLE 0.95 -- same as cl95
Just (mkCLFromSignificance 0.05)
mkCLFromSignificance :: (Ord a, Num a) => a -> CL a Source #
Create confidence level from probability α or probability that confidence interval does not contain true value of estimate. Will throw exception if parameter is out of [0,1] range
>>>
mkCLFromSignificance 0.05 -- same as cl95
mkCLFromSignificance 0.05
mkCLFromSignificanceE :: (Ord a, Num a) => a -> Maybe (CL a) Source #
Same as mkCLFromSignificance
but returns Nothing
instead of error if
parameter is out of [0,1] range
>>>
mkCLFromSignificanceE 0.05 -- same as cl95
Just (mkCLFromSignificance 0.05)
Constants and conversion to nσ
cl90 :: Fractional a => CL a Source #
90% confidence level
cl95 :: Fractional a => CL a Source #
95% confidence level
cl99 :: Fractional a => CL a Source #
99% confidence level
Normal approximation
nSigma :: Double -> PValue Double Source #
P-value expressed in sigma. This is convention widely used in experimental physics. N sigma confidence level corresponds to probability within N sigma of normal distribution.
Note that this correspondence is for normal distribution. Other distribution will have different dependency. Also experimental distribution usually only approximately normal (especially at extreme tails).
nSigma1 :: Double -> PValue Double Source #
P-value expressed in sigma for one-tail hypothesis. This correspond to
probability of obtaining value less than N·σ
.
getNSigma1 :: PValue Double -> Double Source #
Express confidence level in sigmas for one-tailed hypothesis.
p-value
Newtype wrapper for p-value.
Unbox a0 => Vector Vector (PValue a0) Source # | |
Unbox a0 => MVector MVector (PValue a0) Source # | |
Eq a => Eq (PValue a) Source # | |
Data a => Data (PValue a) Source # | |
Ord a => Ord (PValue a) Source # | |
(Num a, Ord a, Read a) => Read (PValue a) Source # | |
Show a => Show (PValue a) Source # | |
Generic (PValue a) Source # | |
NFData a => NFData (PValue a) Source # | |
ToJSON a => ToJSON (PValue a) Source # | |
(FromJSON a, Num a, Ord a) => FromJSON (PValue a) Source # | |
(Binary a, Num a, Ord a) => Binary (PValue a) Source # | |
Unbox a0 => Unbox (PValue a0) Source # | |
data MVector s (PValue a0) Source # | |
type Rep (PValue a) Source # | |
data Vector (PValue a0) Source # | |
Accessors
Constructors
mkPValue :: (Ord a, Num a) => a -> PValue a Source #
Construct PValue. Throws error if argument is out of [0,1] range.
mkPValueE :: (Ord a, Num a) => a -> Maybe (PValue a) Source #
Construct PValue. Returns Nothing
if argument is out of [0,1] range.
Estimates and upper/lower limits
A point estimate and its confidence interval. It's parametrized by
both error type e
and value type a
. This module provides two
types of error: NormalErr
for normally distributed errors and
ConfInt
for error with normal distribution. See their
documentation for more details.
For example 144 ± 5
(assuming normality) could be expressed as
Estimate { estPoint = 144 , estError = NormalErr 5 }
Or if we want to express 144 + 6 - 4
at CL95 we could write:
Estimate { estPoint = 144 , estError = ConfInt { confIntLDX = 4 , confIntUDX = 6 , confIntCL = cl95 }
Prior to statistics 0.14 Estimate
data type used following definition:
data Estimate = Estimate { estPoint :: {-# UNPACK #-} !Double , estLowerBound :: {-# UNPACK #-} !Double , estUpperBound :: {-# UNPACK #-} !Double , estConfidenceLevel :: {-# UNPACK #-} !Double }
Now type Estimate ConfInt Double
should be used instead. Function
estimateFromInterval
allow to easily construct estimate from same inputs.
(Unbox a0, Unbox (e0 a0)) => Vector Vector (Estimate e0 a0) Source # | |
(Unbox a0, Unbox (e0 a0)) => MVector MVector (Estimate e0 a0) Source # | |
Scale e => Scale (Estimate e) Source # | |
(Eq (e a), Eq a) => Eq (Estimate e a) Source # | |
(Data (e a), Data a, Typeable (* -> *) e) => Data (Estimate e a) Source # | |
(Read (e a), Read a) => Read (Estimate e a) Source # | |
(Show (e a), Show a) => Show (Estimate e a) Source # | |
Generic (Estimate e a) Source # | |
(NFData (e a), NFData a) => NFData (Estimate e a) Source # | |
(ToJSON (e a), ToJSON a) => ToJSON (Estimate e a) Source # | |
(FromJSON (e a), FromJSON a) => FromJSON (Estimate e a) Source # | |
(Binary (e a), Binary a) => Binary (Estimate e a) Source # | |
(Unbox a0, Unbox (e0 a0)) => Unbox (Estimate e0 a0) Source # | |
data MVector s (Estimate e0 a0) Source # | |
type Rep (Estimate e a) Source # | |
data Vector (Estimate e0 a0) Source # | |
Normal errors. They are stored as 1σ errors which corresponds to 68.8% CL. Since we can recalculate them to any confidence level if needed we don't store it.
NormalErr | |
|
Scale NormalErr Source # | |
Unbox a0 => Vector Vector (NormalErr a0) Source # | |
Unbox a0 => MVector MVector (NormalErr a0) Source # | |
Eq a => Eq (NormalErr a) Source # | |
Data a => Data (NormalErr a) Source # | |
Read a => Read (NormalErr a) Source # | |
Show a => Show (NormalErr a) Source # | |
Generic (NormalErr a) Source # | |
NFData a => NFData (NormalErr a) Source # | |
ToJSON a => ToJSON (NormalErr a) Source # | |
FromJSON a => FromJSON (NormalErr a) Source # | |
Binary a => Binary (NormalErr a) Source # | |
Unbox a0 => Unbox (NormalErr a0) Source # | |
data MVector s (NormalErr a0) Source # | |
type Rep (NormalErr a) Source # | |
data Vector (NormalErr a0) Source # | |
Confidence interval. It assumes that confidence interval forms single interval and isn't set of disjoint intervals.
ConfInt | |
|
Scale ConfInt Source # | |
Unbox a0 => Vector Vector (ConfInt a0) Source # | |
Unbox a0 => MVector MVector (ConfInt a0) Source # | |
Eq a => Eq (ConfInt a) Source # | |
Data a => Data (ConfInt a) Source # | |
Read a => Read (ConfInt a) Source # | |
Show a => Show (ConfInt a) Source # | |
Generic (ConfInt a) Source # | |
NFData a => NFData (ConfInt a) Source # | |
ToJSON a => ToJSON (ConfInt a) Source # | |
FromJSON a => FromJSON (ConfInt a) Source # | |
Binary a => Binary (ConfInt a) Source # | |
Unbox a0 => Unbox (ConfInt a0) Source # | |
data MVector s (ConfInt a0) Source # | |
type Rep (ConfInt a) Source # | |
data Vector (ConfInt a0) Source # | |
data UpperLimit a Source #
Upper limit. They are usually given for small non-negative values when it's not possible detect difference from zero.
UpperLimit | |
|
Unbox a0 => Vector Vector (UpperLimit a0) Source # | |
Unbox a0 => MVector MVector (UpperLimit a0) Source # | |
Eq a => Eq (UpperLimit a) Source # | |
Data a => Data (UpperLimit a) Source # | |
Read a => Read (UpperLimit a) Source # | |
Show a => Show (UpperLimit a) Source # | |
Generic (UpperLimit a) Source # | |
NFData a => NFData (UpperLimit a) Source # | |
ToJSON a => ToJSON (UpperLimit a) Source # | |
FromJSON a => FromJSON (UpperLimit a) Source # | |
Binary a => Binary (UpperLimit a) Source # | |
Unbox a0 => Unbox (UpperLimit a0) Source # | |
data MVector s (UpperLimit a0) Source # | |
type Rep (UpperLimit a) Source # | |
data Vector (UpperLimit a0) Source # | |
data LowerLimit a Source #
Lower limit. They are usually given for large quantities when it's not possible to measure them. For example: proton half-life
LowerLimit | |
|
Unbox a0 => Vector Vector (LowerLimit a0) Source # | |
Unbox a0 => MVector MVector (LowerLimit a0) Source # | |
Eq a => Eq (LowerLimit a) Source # | |
Data a => Data (LowerLimit a) Source # | |
Read a => Read (LowerLimit a) Source # | |
Show a => Show (LowerLimit a) Source # | |
Generic (LowerLimit a) Source # | |
NFData a => NFData (LowerLimit a) Source # | |
ToJSON a => ToJSON (LowerLimit a) Source # | |
FromJSON a => FromJSON (LowerLimit a) Source # | |
Binary a => Binary (LowerLimit a) Source # | |
Unbox a0 => Unbox (LowerLimit a0) Source # | |
data MVector s (LowerLimit a0) Source # | |
type Rep (LowerLimit a) Source # | |
data Vector (LowerLimit a0) Source # | |
Constructors
Create estimate with normal errors
:: Num a | |
=> a | Point estimate. Should lie within interval but it's not checked. |
-> (a, a) | Lower and upper bounds of interval |
-> CL Double | Confidence level for interval |
-> Estimate ConfInt a |
Create estimate with asymmetric error.
:: a | Central estimate |
-> (a, a) | Lower and upper errors. Both should be positive but it's not checked. |
-> CL Double | Confidence level for interval |
-> Estimate ConfInt a |
Create estimate with asymmetric error.
Accessors
asymErrors :: Estimate ConfInt a -> (a, a) Source #
Get asymmetric errors
Data types which could be multiplied by constant.