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
Synopsis
- 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
.
Instances
Unbox a => Vector Vector (CL a) Source # | |
Defined in Statistics.Types basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (CL a) -> m (Vector (CL a)) # basicUnsafeThaw :: PrimMonad m => Vector (CL a) -> m (Mutable Vector (PrimState m) (CL a)) # basicLength :: Vector (CL a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (CL a) -> Vector (CL a) # basicUnsafeIndexM :: Monad m => Vector (CL a) -> Int -> m (CL a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (CL a) -> Vector (CL a) -> m () # | |
Unbox a => MVector MVector (CL a) Source # | |
Defined in Statistics.Types basicLength :: MVector s (CL a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (CL a) -> MVector s (CL a) # basicOverlaps :: MVector s (CL a) -> MVector s (CL a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (CL a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (CL a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> CL a -> m (MVector (PrimState m) (CL a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (CL a) -> Int -> m (CL a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (CL a) -> Int -> CL a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (CL a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (CL a) -> CL a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (CL a) -> MVector (PrimState m) (CL a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (CL a) -> MVector (PrimState m) (CL a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (CL a) -> Int -> m (MVector (PrimState m) (CL a)) # | |
Eq a => Eq (CL a) Source # | |
Data a => Data (CL a) Source # | |
Defined in Statistics.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CL a -> c (CL a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CL a) # dataTypeOf :: CL a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CL a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CL a)) # gmapT :: (forall b. Data b => b -> b) -> CL a -> CL a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CL a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CL a -> r # gmapQ :: (forall d. Data d => d -> u) -> CL a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CL a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CL a -> m (CL a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CL a -> m (CL a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CL a -> m (CL a) # | |
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 # | |
Defined in Statistics.Types | |
ToJSON a => ToJSON (CL a) Source # | |
Defined in Statistics.Types | |
(FromJSON a, Num a, Ord a) => FromJSON (CL a) Source # | |
(Binary a, Num a, Ord a) => Binary (CL a) Source # | |
Unbox a => Unbox (CL a) Source # | |
Defined in Statistics.Types | |
data MVector s (CL a) Source # | |
Defined in Statistics.Types | |
type Rep (CL a) Source # | |
Defined in Statistics.Types | |
data Vector (CL a) Source # | |
Defined in Statistics.Types |
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.
Instances
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.
Instances
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 | |
|
Instances
Confidence interval. It assumes that confidence interval forms single interval and isn't set of disjoint intervals.
ConfInt | |
|
Instances
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 | |
|
Instances
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 | |
|
Instances
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.