statistics-0.16.1.2: A library of statistical types, data, and functions
Copyright (c) 2009 Bryan O'Sullivan
License BSD3
Maintainer bos@serpentine.com
Stability experimental
Portability portable
Safe Haskell None
Language Haskell2010

Statistics.Types

Description

Data types common used in statistics

Synopsis

Confidence level

data CL a Source #

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

Instances details
Unbox a => Vector Vector ( CL a) Source #
Instance details

Defined in Statistics.Types

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

Defined in Statistics.Types

Eq a => Eq ( CL a) Source #
Instance details

Defined in Statistics.Types

Data a => Data ( CL a) Source #
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) Source #

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

toConstr :: CL a -> Constr Source #

dataTypeOf :: CL a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord ( CL a) Source #
>>> cl95 > cl90
True
Instance details

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Generic ( CL a) Source #
Instance details

Defined in Statistics.Types

Associated Types

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Methods

rnf :: CL a -> () Source #

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

Defined in Statistics.Types

newtype MVector s ( CL a) Source #
Instance details

Defined in Statistics.Types

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

Defined in Statistics.Types

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

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·σ .

getNSigma :: PValue Double -> Double Source #

Express confidence level in sigmas

getNSigma1 :: PValue Double -> Double Source #

Express confidence level in sigmas for one-tailed hypothesis.

p-value

data PValue a Source #

Newtype wrapper for p-value.

Instances

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Data a => Data ( PValue a) Source #
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) Source #

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

toConstr :: PValue a -> Constr Source #

dataTypeOf :: PValue a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Generic ( PValue a) Source #
Instance details

Defined in Statistics.Types

Associated Types

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Methods

rnf :: PValue a -> () Source #

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

Defined in Statistics.Types

newtype MVector s ( PValue a) Source #
Instance details

Defined in Statistics.Types

type Rep ( PValue a) Source #
Instance details

Defined in Statistics.Types

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

Defined in Statistics.Types

Accessors

pValue :: PValue a -> a Source #

Get p-value

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

data Estimate e a Source #

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

Instances

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Methods

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

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

Defined in Statistics.Types

( Typeable e, Data a, Data (e a)) => Data ( Estimate e a) Source #
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) Source #

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

toConstr :: Estimate e a -> Constr Source #

dataTypeOf :: Estimate e a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Generic ( Estimate e a) Source #
Instance details

Defined in Statistics.Types

Associated Types

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Methods

rnf :: Estimate e a -> () Source #

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

Defined in Statistics.Types

newtype MVector s ( Estimate e a) Source #
Instance details

Defined in Statistics.Types

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

Defined in Statistics.Types

type Rep ( Estimate e a) = D1 (' MetaData "Estimate" "Statistics.Types" "statistics-0.16.1.2-IkOne9g3oJ1vhHVSRLPUO" ' 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) Source #
Instance details

Defined in Statistics.Types

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

newtype NormalErr a 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.

Constructors

NormalErr

Fields

Instances

Instances details
Scale NormalErr Source #
Instance details

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Data a => Data ( NormalErr a) Source #
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) Source #

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

toConstr :: NormalErr a -> Constr Source #

dataTypeOf :: NormalErr a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Generic ( NormalErr a) Source #
Instance details

Defined in Statistics.Types

Associated Types

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

newtype MVector s ( NormalErr a) Source #
Instance details

Defined in Statistics.Types

type Rep ( NormalErr a) Source #
Instance details

Defined in Statistics.Types

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

Defined in Statistics.Types

data ConfInt a Source #

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

Instances details
Scale ConfInt Source #
Instance details

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Data a => Data ( ConfInt a) Source #
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) Source #

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

toConstr :: ConfInt a -> Constr Source #

dataTypeOf :: ConfInt a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Generic ( ConfInt a) Source #
Instance details

Defined in Statistics.Types

Associated Types

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

newtype MVector s ( ConfInt a) Source #
Instance details

Defined in Statistics.Types

type Rep ( ConfInt a) Source #
Instance details

Defined in Statistics.Types

newtype Vector ( ConfInt a) Source #
Instance details

Defined in Statistics.Types

data UpperLimit a Source #

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

Constructors

UpperLimit

Fields

Instances

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Data a => Data ( UpperLimit a) Source #
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) Source #

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

toConstr :: UpperLimit a -> Constr Source #

dataTypeOf :: UpperLimit a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Generic ( UpperLimit a) Source #
Instance details

Defined in Statistics.Types

Associated Types

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

newtype MVector s ( UpperLimit a) Source #
Instance details

Defined in Statistics.Types

type Rep ( UpperLimit a) Source #
Instance details

Defined in Statistics.Types

type Rep ( UpperLimit a) = D1 (' MetaData "UpperLimit" "Statistics.Types" "statistics-0.16.1.2-IkOne9g3oJ1vhHVSRLPUO" ' 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) Source #
Instance details

Defined in Statistics.Types

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

Constructors

LowerLimit

Fields

Instances

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Data a => Data ( LowerLimit a) Source #
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) Source #

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

toConstr :: LowerLimit a -> Constr Source #

dataTypeOf :: LowerLimit a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

Generic ( LowerLimit a) Source #
Instance details

Defined in Statistics.Types

Associated Types

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

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

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

Defined in Statistics.Types

newtype MVector s ( LowerLimit a) Source #
Instance details

Defined in Statistics.Types

type Rep ( LowerLimit a) Source #
Instance details

Defined in Statistics.Types

type Rep ( LowerLimit a) = D1 (' MetaData "LowerLimit" "Statistics.Types" "statistics-0.16.1.2-IkOne9g3oJ1vhHVSRLPUO" ' 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) Source #
Instance details

Defined in Statistics.Types

Constructors

estimateNormErr Source #

Arguments

:: a

Point estimate

-> a

1σ error

-> Estimate NormalErr a

Create estimate with normal errors

(±) Source #

Arguments

:: a

Point estimate

-> a

1σ error

-> Estimate NormalErr a

Synonym for estimateNormErr

estimateFromInterval Source #

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

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

Get confidence interval

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

Get asymmetric errors

class Scale e where Source #

Data types which could be multiplied by constant.

Methods

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

Other

type WeightedSample = Vector ( Double , Double ) Source #

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

type Weights = Vector Double Source #

Weights for affecting the importance of elements of a sample.