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

Copyright(c) 2009 Bryan O'Sullivan
LicenseBSD3
Maintainerbos@serpentine.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Statistics.Types

Contents

Description

Data types common used in statistics

Synopsis

Confidence level

data CL a #

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

Defined in Statistics.Types

Methods

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

elemseq :: Vector (CL a) -> CL a -> b -> b #

Unbox a => MVector MVector (CL a) # 
Instance details

Defined in Statistics.Types

Methods

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

Defined in Statistics.Types

Methods

(==) :: CL a -> CL a -> Bool #

(/=) :: CL a -> CL a -> Bool #

Data a => Data (CL a) # 
Instance details

Defined in Statistics.Types

Methods

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

toConstr :: CL a -> Constr #

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) #
>>> cl95 > cl90
True
Instance details

Defined in Statistics.Types

Methods

compare :: CL a -> CL a -> Ordering #

(<) :: CL a -> CL a -> Bool #

(<=) :: CL a -> CL a -> Bool #

(>) :: CL a -> CL a -> Bool #

(>=) :: CL a -> CL a -> Bool #

max :: CL a -> CL a -> CL a #

min :: CL a -> CL a -> CL a #

(Num a, Ord a, Read a) => Read (CL a) # 
Instance details

Defined in Statistics.Types

Show a => Show (CL a) # 
Instance details

Defined in Statistics.Types

Methods

showsPrec :: Int -> CL a -> ShowS #

show :: CL a -> String #

showList :: [CL a] -> ShowS #

Generic (CL a) # 
Instance details

Defined in Statistics.Types

Associated Types

type Rep (CL a) :: Type -> Type #

Methods

from :: CL a -> Rep (CL a) x #

to :: Rep (CL a) x -> CL a #

NFData a => NFData (CL a) # 
Instance details

Defined in Statistics.Types

Methods

rnf :: CL a -> () #

ToJSON a => ToJSON (CL a) # 
Instance details

Defined in Statistics.Types

Methods

toJSON :: CL a -> Value #

toEncoding :: CL a -> Encoding #

toJSONList :: [CL a] -> Value #

toEncodingList :: [CL a] -> Encoding #

(FromJSON a, Num a, Ord a) => FromJSON (CL a) # 
Instance details

Defined in Statistics.Types

Methods

parseJSON :: Value -> Parser (CL a) #

parseJSONList :: Value -> Parser [CL a] #

(Binary a, Num a, Ord a) => Binary (CL a) # 
Instance details

Defined in Statistics.Types

Methods

put :: CL a -> Put #

get :: Get (CL a) #

putList :: [CL a] -> Put #

Unbox a => Unbox (CL a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (CL a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (CL a) = MV_CL (MVector s a)
type Rep (CL a) # 
Instance details

Defined in Statistics.Types

type Rep (CL a) = D1 (MetaData "CL" "Statistics.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" True) (C1 (MetaCons "CL" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
newtype Vector (CL a) # 
Instance details

Defined in Statistics.Types

newtype Vector (CL a) = V_CL (Vector a)

Accessors

confidenceLevel :: Num a => CL a -> a #

Get confidence level. This function is subject to rounding errors. If 1 - CL is needed use significanceLevel instead

significanceLevel :: CL a -> a #

Get significance level.

Constructors

mkCL :: (Ord a, Num a) => a -> CL a #

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

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 #

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

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 #

90% confidence level

cl95 :: Fractional a => CL a #

95% confidence level

cl99 :: Fractional a => CL a #

99% confidence level

Normal approximation

nSigma :: Double -> PValue Double #

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 #

P-value expressed in sigma for one-tail hypothesis. This correspond to probability of obtaining value less than N·σ.

getNSigma :: PValue Double -> Double #

Express confidence level in sigmas

getNSigma1 :: PValue Double -> Double #

Express confidence level in sigmas for one-tailed hypothesis.

p-value

data PValue a #

Newtype wrapper for p-value.

Instances
Unbox a => Vector Vector (PValue a) # 
Instance details

Defined in Statistics.Types

Unbox a => MVector MVector (PValue a) # 
Instance details

Defined in Statistics.Types

Eq a => Eq (PValue a) # 
Instance details

Defined in Statistics.Types

Methods

(==) :: PValue a -> PValue a -> Bool #

(/=) :: PValue a -> PValue a -> Bool #

Data a => Data (PValue a) # 
Instance details

Defined in Statistics.Types

Methods

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

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

toConstr :: PValue a -> Constr #

dataTypeOf :: PValue a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (PValue a) # 
Instance details

Defined in Statistics.Types

Methods

compare :: PValue a -> PValue a -> Ordering #

(<) :: PValue a -> PValue a -> Bool #

(<=) :: PValue a -> PValue a -> Bool #

(>) :: PValue a -> PValue a -> Bool #

(>=) :: PValue a -> PValue a -> Bool #

max :: PValue a -> PValue a -> PValue a #

min :: PValue a -> PValue a -> PValue a #

(Num a, Ord a, Read a) => Read (PValue a) # 
Instance details

Defined in Statistics.Types

Show a => Show (PValue a) # 
Instance details

Defined in Statistics.Types

Methods

showsPrec :: Int -> PValue a -> ShowS #

show :: PValue a -> String #

showList :: [PValue a] -> ShowS #

Generic (PValue a) # 
Instance details

Defined in Statistics.Types

Associated Types

type Rep (PValue a) :: Type -> Type #

Methods

from :: PValue a -> Rep (PValue a) x #

to :: Rep (PValue a) x -> PValue a #

NFData a => NFData (PValue a) # 
Instance details

Defined in Statistics.Types

Methods

rnf :: PValue a -> () #

ToJSON a => ToJSON (PValue a) # 
Instance details

Defined in Statistics.Types

(FromJSON a, Num a, Ord a) => FromJSON (PValue a) # 
Instance details

Defined in Statistics.Types

(Binary a, Num a, Ord a) => Binary (PValue a) # 
Instance details

Defined in Statistics.Types

Methods

put :: PValue a -> Put #

get :: Get (PValue a) #

putList :: [PValue a] -> Put #

Unbox a => Unbox (PValue a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (PValue a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (PValue a) = MV_PValue (MVector s a)
type Rep (PValue a) # 
Instance details

Defined in Statistics.Types

type Rep (PValue a) = D1 (MetaData "PValue" "Statistics.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" True) (C1 (MetaCons "PValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
newtype Vector (PValue a) # 
Instance details

Defined in Statistics.Types

newtype Vector (PValue a) = V_PValue (Vector a)

Accessors

pValue :: PValue a -> a #

Get p-value

Constructors

mkPValue :: (Ord a, Num a) => a -> PValue a #

Construct PValue. Throws error if argument is out of [0,1] range.

mkPValueE :: (Ord a, Num a) => a -> Maybe (PValue a) #

Construct PValue. Returns Nothing if argument is out of [0,1] range.

Estimates and upper/lower limits

data Estimate e a #

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.

Constructors

Estimate 

Fields

  • estPoint :: !a

    Point estimate.

  • estError :: !(e a)

    Confidence interval for estimate.

Instances
(Unbox a, Unbox (e a)) => Vector Vector (Estimate e a) # 
Instance details

Defined in Statistics.Types

(Unbox a, Unbox (e a)) => MVector MVector (Estimate e a) # 
Instance details

Defined in Statistics.Types

Scale e => Scale (Estimate e) # 
Instance details

Defined in Statistics.Types

Methods

scale :: (Ord a, Num a) => a -> Estimate e a -> Estimate e a #

(Eq a, Eq (e a)) => Eq (Estimate e a) # 
Instance details

Defined in Statistics.Types

Methods

(==) :: Estimate e a -> Estimate e a -> Bool #

(/=) :: Estimate e a -> Estimate e a -> Bool #

(Typeable e, Data a, Data (e a)) => Data (Estimate e a) # 
Instance details

Defined in Statistics.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Estimate e a -> c (Estimate e a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Estimate e a) #

toConstr :: Estimate e a -> Constr #

dataTypeOf :: Estimate e a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Estimate e a -> Estimate e a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Estimate e a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Estimate e a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Estimate e a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Estimate e a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Estimate e a -> m (Estimate e a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Estimate e a -> m (Estimate e a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Estimate e a -> m (Estimate e a) #

(Read a, Read (e a)) => Read (Estimate e a) # 
Instance details

Defined in Statistics.Types

(Show a, Show (e a)) => Show (Estimate e a) # 
Instance details

Defined in Statistics.Types

Methods

showsPrec :: Int -> Estimate e a -> ShowS #

show :: Estimate e a -> String #

showList :: [Estimate e a] -> ShowS #

Generic (Estimate e a) # 
Instance details

Defined in Statistics.Types

Associated Types

type Rep (Estimate e a) :: Type -> Type #

Methods

from :: Estimate e a -> Rep (Estimate e a) x #

to :: Rep (Estimate e a) x -> Estimate e a #

(NFData (e a), NFData a) => NFData (Estimate e a) # 
Instance details

Defined in Statistics.Types

Methods

rnf :: Estimate e a -> () #

(ToJSON (e a), ToJSON a) => ToJSON (Estimate e a) # 
Instance details

Defined in Statistics.Types

(FromJSON (e a), FromJSON a) => FromJSON (Estimate e a) # 
Instance details

Defined in Statistics.Types

(Binary (e a), Binary a) => Binary (Estimate e a) # 
Instance details

Defined in Statistics.Types

Methods

put :: Estimate e a -> Put #

get :: Get (Estimate e a) #

putList :: [Estimate e a] -> Put #

(Unbox a, Unbox (e a)) => Unbox (Estimate e a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (Estimate e a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (Estimate e a) = MV_Estimate (MVector s (a, e a))
type Rep (Estimate e a) # 
Instance details

Defined in Statistics.Types

type Rep (Estimate e a) = D1 (MetaData "Estimate" "Statistics.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" False) (C1 (MetaCons "Estimate" PrefixI True) (S1 (MetaSel (Just "estPoint") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "estError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (e a))))
newtype Vector (Estimate e a) # 
Instance details

Defined in Statistics.Types

newtype Vector (Estimate e a) = V_Estimate (Vector (a, e a))

newtype NormalErr a #

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.

Constructors

NormalErr 

Fields

Instances
Scale NormalErr # 
Instance details

Defined in Statistics.Types

Methods

scale :: (Ord a, Num a) => a -> NormalErr a -> NormalErr a #

Unbox a => Vector Vector (NormalErr a) # 
Instance details

Defined in Statistics.Types

Unbox a => MVector MVector (NormalErr a) # 
Instance details

Defined in Statistics.Types

Eq a => Eq (NormalErr a) # 
Instance details

Defined in Statistics.Types

Methods

(==) :: NormalErr a -> NormalErr a -> Bool #

(/=) :: NormalErr a -> NormalErr a -> Bool #

Data a => Data (NormalErr a) # 
Instance details

Defined in Statistics.Types

Methods

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

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

toConstr :: NormalErr a -> Constr #

dataTypeOf :: NormalErr a -> DataType #

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

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

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

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

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

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

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

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

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

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

Read a => Read (NormalErr a) # 
Instance details

Defined in Statistics.Types

Show a => Show (NormalErr a) # 
Instance details

Defined in Statistics.Types

Generic (NormalErr a) # 
Instance details

Defined in Statistics.Types

Associated Types

type Rep (NormalErr a) :: Type -> Type #

Methods

from :: NormalErr a -> Rep (NormalErr a) x #

to :: Rep (NormalErr a) x -> NormalErr a #

NFData a => NFData (NormalErr a) # 
Instance details

Defined in Statistics.Types

Methods

rnf :: NormalErr a -> () #

ToJSON a => ToJSON (NormalErr a) # 
Instance details

Defined in Statistics.Types

FromJSON a => FromJSON (NormalErr a) # 
Instance details

Defined in Statistics.Types

Binary a => Binary (NormalErr a) # 
Instance details

Defined in Statistics.Types

Methods

put :: NormalErr a -> Put #

get :: Get (NormalErr a) #

putList :: [NormalErr a] -> Put #

Unbox a => Unbox (NormalErr a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (NormalErr a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (NormalErr a) = MV_NormalErr (MVector s a)
type Rep (NormalErr a) # 
Instance details

Defined in Statistics.Types

type Rep (NormalErr a) = D1 (MetaData "NormalErr" "Statistics.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" True) (C1 (MetaCons "NormalErr" PrefixI True) (S1 (MetaSel (Just "normalError") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
newtype Vector (NormalErr a) # 
Instance details

Defined in Statistics.Types

data ConfInt a #

Confidence interval. It assumes that confidence interval forms single interval and isn't set of disjoint intervals.

Constructors

ConfInt 

Fields

  • confIntLDX :: !a

    Lower error estimate, or distance between point estimate and lower bound of confidence interval.

  • confIntUDX :: !a

    Upper error estimate, or distance between point estimate and upper bound of confidence interval.

  • confIntCL :: !(CL Double)

    Confidence level corresponding to given confidence interval.

Instances
Scale ConfInt # 
Instance details

Defined in Statistics.Types

Methods

scale :: (Ord a, Num a) => a -> ConfInt a -> ConfInt a #

Unbox a => Vector Vector (ConfInt a) # 
Instance details

Defined in Statistics.Types

Unbox a => MVector MVector (ConfInt a) # 
Instance details

Defined in Statistics.Types

Eq a => Eq (ConfInt a) # 
Instance details

Defined in Statistics.Types

Methods

(==) :: ConfInt a -> ConfInt a -> Bool #

(/=) :: ConfInt a -> ConfInt a -> Bool #

Data a => Data (ConfInt a) # 
Instance details

Defined in Statistics.Types

Methods

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

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

toConstr :: ConfInt a -> Constr #

dataTypeOf :: ConfInt a -> DataType #

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

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

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

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

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

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

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

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

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

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

Read a => Read (ConfInt a) # 
Instance details

Defined in Statistics.Types

Show a => Show (ConfInt a) # 
Instance details

Defined in Statistics.Types

Methods

showsPrec :: Int -> ConfInt a -> ShowS #

show :: ConfInt a -> String #

showList :: [ConfInt a] -> ShowS #

Generic (ConfInt a) # 
Instance details

Defined in Statistics.Types

Associated Types

type Rep (ConfInt a) :: Type -> Type #

Methods

from :: ConfInt a -> Rep (ConfInt a) x #

to :: Rep (ConfInt a) x -> ConfInt a #

NFData a => NFData (ConfInt a) # 
Instance details

Defined in Statistics.Types

Methods

rnf :: ConfInt a -> () #

ToJSON a => ToJSON (ConfInt a) # 
Instance details

Defined in Statistics.Types

FromJSON a => FromJSON (ConfInt a) # 
Instance details

Defined in Statistics.Types

Binary a => Binary (ConfInt a) # 
Instance details

Defined in Statistics.Types

Methods

put :: ConfInt a -> Put #

get :: Get (ConfInt a) #

putList :: [ConfInt a] -> Put #

Unbox a => Unbox (ConfInt a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (ConfInt a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (ConfInt a) = MV_ConfInt (MVector s (a, a, CL Double))
type Rep (ConfInt a) # 
Instance details

Defined in Statistics.Types

type Rep (ConfInt a) = D1 (MetaData "ConfInt" "Statistics.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" False) (C1 (MetaCons "ConfInt" PrefixI True) (S1 (MetaSel (Just "confIntLDX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: (S1 (MetaSel (Just "confIntUDX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "confIntCL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (CL Double)))))
newtype Vector (ConfInt a) # 
Instance details

Defined in Statistics.Types

newtype Vector (ConfInt a) = V_ConfInt (Vector (a, a, CL Double))

data UpperLimit a #

Upper limit. They are usually given for small non-negative values when it's not possible detect difference from zero.

Constructors

UpperLimit 

Fields

Instances
Unbox a => Vector Vector (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Unbox a => MVector MVector (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Eq a => Eq (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Methods

(==) :: UpperLimit a -> UpperLimit a -> Bool #

(/=) :: UpperLimit a -> UpperLimit a -> Bool #

Data a => Data (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Methods

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

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

toConstr :: UpperLimit a -> Constr #

dataTypeOf :: UpperLimit a -> DataType #

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

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

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

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

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

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

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

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

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

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

Read a => Read (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Show a => Show (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Generic (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Associated Types

type Rep (UpperLimit a) :: Type -> Type #

Methods

from :: UpperLimit a -> Rep (UpperLimit a) x #

to :: Rep (UpperLimit a) x -> UpperLimit a #

NFData a => NFData (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Methods

rnf :: UpperLimit a -> () #

ToJSON a => ToJSON (UpperLimit a) # 
Instance details

Defined in Statistics.Types

FromJSON a => FromJSON (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Binary a => Binary (UpperLimit a) # 
Instance details

Defined in Statistics.Types

Methods

put :: UpperLimit a -> Put #

get :: Get (UpperLimit a) #

putList :: [UpperLimit a] -> Put #

Unbox a => Unbox (UpperLimit a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (UpperLimit a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (UpperLimit a) = MV_UpperLimit (MVector s (a, CL Double))
type Rep (UpperLimit a) # 
Instance details

Defined in Statistics.Types

type Rep (UpperLimit a) = D1 (MetaData "UpperLimit" "Statistics.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" False) (C1 (MetaCons "UpperLimit" PrefixI True) (S1 (MetaSel (Just "upperLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "ulConfidenceLevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (CL Double))))
newtype Vector (UpperLimit a) # 
Instance details

Defined in Statistics.Types

data LowerLimit a #

Lower limit. They are usually given for large quantities when it's not possible to measure them. For example: proton half-life

Constructors

LowerLimit 

Fields

Instances
Unbox a => Vector Vector (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Unbox a => MVector MVector (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Eq a => Eq (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Methods

(==) :: LowerLimit a -> LowerLimit a -> Bool #

(/=) :: LowerLimit a -> LowerLimit a -> Bool #

Data a => Data (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Methods

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

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

toConstr :: LowerLimit a -> Constr #

dataTypeOf :: LowerLimit a -> DataType #

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

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

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

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

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

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

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

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

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

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

Read a => Read (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Show a => Show (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Generic (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Associated Types

type Rep (LowerLimit a) :: Type -> Type #

Methods

from :: LowerLimit a -> Rep (LowerLimit a) x #

to :: Rep (LowerLimit a) x -> LowerLimit a #

NFData a => NFData (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Methods

rnf :: LowerLimit a -> () #

ToJSON a => ToJSON (LowerLimit a) # 
Instance details

Defined in Statistics.Types

FromJSON a => FromJSON (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Binary a => Binary (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Methods

put :: LowerLimit a -> Put #

get :: Get (LowerLimit a) #

putList :: [LowerLimit a] -> Put #

Unbox a => Unbox (LowerLimit a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (LowerLimit a) # 
Instance details

Defined in Statistics.Types

newtype MVector s (LowerLimit a) = MV_LowerLimit (MVector s (a, CL Double))
type Rep (LowerLimit a) # 
Instance details

Defined in Statistics.Types

type Rep (LowerLimit a) = D1 (MetaData "LowerLimit" "Statistics.Types" "statistics-0.15.0.0-KYJLg9h4jsl1bBm8KLc3A8" False) (C1 (MetaCons "LowerLimit" PrefixI True) (S1 (MetaSel (Just "lowerLimit") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Just "llConfidenceLevel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (CL Double))))
newtype Vector (LowerLimit a) # 
Instance details

Defined in Statistics.Types

Constructors

estimateNormErr #

Arguments

:: a

Point estimate

-> a

1σ error

-> Estimate NormalErr a 

Create estimate with normal errors

(±) #

Arguments

:: a

Point estimate

-> a

1σ error

-> Estimate NormalErr a 

Synonym for estimateNormErr

estimateFromInterval #

Arguments

:: 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.

estimateFromErr #

Arguments

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

confidenceInterval :: Num a => Estimate ConfInt a -> (a, a) #

Get confidence interval

asymErrors :: Estimate ConfInt a -> (a, a) #

Get asymmetric errors

class Scale e where #

Data types which could be multiplied by constant.

Methods

scale :: (Ord a, Num a) => a -> e a -> e a #

Instances
Scale ConfInt # 
Instance details

Defined in Statistics.Types

Methods

scale :: (Ord a, Num a) => a -> ConfInt a -> ConfInt a #

Scale NormalErr # 
Instance details

Defined in Statistics.Types

Methods

scale :: (Ord a, Num a) => a -> NormalErr a -> NormalErr a #

Scale e => Scale (Estimate e) # 
Instance details

Defined in Statistics.Types

Methods

scale :: (Ord a, Num a) => a -> Estimate e a -> Estimate e a #

Other

type Sample = Vector Double #

Sample data.

type WeightedSample = Vector (Double, Double) #

Sample with weights. First element of sample is data, second is weight

type Weights = Vector Double #

Weights for affecting the importance of elements of a sample.