Copyright | (c) Justin Le 2016 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data Uncert a where
- (+/-) :: Num a => a -> a -> Uncert a
- exact :: Num a => a -> Uncert a
- withPrecision :: (Floating a, RealFrac a) => a -> Int -> Uncert a
- withPrecisionAtBase :: (Floating a, RealFrac a) => Int -> a -> Int -> Uncert a
- withVar :: Num a => a -> a -> Uncert a
- fromSamples :: Fractional a => [a] -> Uncert a
- uMean :: Uncert a -> a
- uVar :: Uncert a -> a
- uStd :: Floating a => Uncert a -> a
- uMeanVar :: Uncert a -> (a, a)
- uMeanStd :: Floating a => Uncert a -> (a, a)
- uRange :: Floating a => Uncert a -> (a, a)
- liftU :: Fractional a => (forall s. AD s (Tower a) -> AD s (Tower a)) -> Uncert a -> Uncert a
- liftU2 :: Fractional a => (forall s. AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a)) -> Uncert a -> Uncert a -> Uncert a
- liftU3 :: Fractional a => (forall s. AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a)) -> Uncert a -> Uncert a -> Uncert a -> Uncert a
- liftU4 :: Fractional a => (forall s. AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a)) -> Uncert a -> Uncert a -> Uncert a -> Uncert a -> Uncert a
- liftU5 :: Fractional a => (forall s. AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a)) -> Uncert a -> Uncert a -> Uncert a -> Uncert a -> Uncert a -> Uncert a
- liftUF :: (Traversable f, Fractional a) => (forall s. f (AD s (Sparse a)) -> AD s (Sparse a)) -> f (Uncert a) -> Uncert a
- uNormalize :: (Floating a, RealFrac a) => Uncert a -> Uncert a
- uNormalizeAtBase :: (Floating a, RealFrac a) => Int -> Uncert a -> Uncert a
- uShow :: (Show a, Floating a) => Uncert a -> String
- uShowsPrec :: (Show a, Floating a) => Int -> Uncert a -> ShowS
Uncert
Represents an independent experimental value centered around a mean value with "inherent" and independent uncertainty.
Mostly useful due to its instances of numeric typeclasses like Num
,
Fractional
, etc., which allows you to add and multiply and apply
arbitrary numerical functions to them and have the uncertainty
propagate appropriately. You can also lift arbitrary (sufficiently
polymorphic) functions with liftU
, liftUF
, liftU2
and family.
ghci> let x = 1.52+/-
0.07 ghci> let y = 781.4 +/- 0.3 ghci> let z = 1.53e-1 `withPrecision'
3 ghci> cosh x 2.4 +/- 0.2 ghci> exp x / z * sin (y ** z) 10.9 +/- 0.9 ghci> pi + 3 * logBase x y 52 +/- 5
Uncertaintly is properly propagated according to the second-degree taylor series approximations of the applied functions. However, if the higher-degree terms are large with respect to to the means and variances of the uncertain values, these approximations may be inaccurate.
Can be created with exact
to represent an "exact" measurement with no
uncertainty, +/-
and :+/-
to specify a standard deviation as
a range, withPrecision
to specify through decimal precision, and
withVar
to specify with a variance. Can also be inferred from a list
of samples with fromSamples
7.13+/-
0.05 91800 +/- 100 12.5 `withVar'
0.36exact
7.9512 81.42 `withPrecision'
4 7 :: Uncertain Double 9.18 :: Uncertain DoublefromSamples
[12.5, 12.7, 12.6, 12.6, 12.5]
Can be deconstructed with :+/-
, the pattern synonym/pseudo-constructor
which matches on the mean and a standard deviation (supported on GHC
7.8+, with bidirectional constructor functionality supported on GHC
7.10+). You can also access properties with uMean
, uStd
, uVar
,
uMeanStd
, uMeanVar
, uRange
, etc.
It's important to remember that each "occurrence" represents a unique independent sample, so:
ghci> let x = 15 +/-
2 in x + x
30 +/- 3
ghci> let x = 15 +/- 2 in x*2
30 +/- 4
x + x
does not represent adding the same sample to itself twice, it
represents independently sampling two values within the range 15 +/- 2
and adding them together. In general, errors and deviations will cancel
each-other out, leading to a smaller uncertainty.
However, x*2
represents taking one sample and multiplying it by two.
This yields a greater uncertainty, because errors and deviations are
amplified.
Also be aware that the Show
instance "normalizes" the result, and
won't show any mean/central point to a decimal precision smaller than
the uncertainty, rounding off the excess.
pattern (:+/-) :: Floating a => a -> a -> Uncert a infixl 6 | Pattern match on an Can also be used to construct an Note: Only supported on GHC 7.8 and above. Bidirectional functionality (to allow use as a constructor) only supported on GHC 7.10 and above. |
Instances
Creating Uncert
values
:: Num a | |
=> a | The mean or central value |
-> a | The standard deviation of the underlying uncertainty |
-> Uncert a |
Create an Uncert
around a central value and a given "range" of
uncertainty. The range is interpreted as the standard deviation of the
underlying random variable. Might be preferrable over :+/-
because it
is more general (doesn't require a Floating
constraint) and looks
a bit nicer.
See uStd
for more details.
Create an Uncert
with an exact value and 0 uncertainty.
:: (Floating a, RealFrac a) | |
=> a | The approximate value of the |
-> Int | The number of "digits" of precision to take |
-> Uncert a |
Create an Uncert
about a given approximate central value, with the
given number of digits of precision (in decimal notation).
5.21withPrecision
3 ≡ 5.21+/-
0.01
:: (Floating a, RealFrac a) | |
=> Int | The base to determine precision with respect to |
-> a | The approximate value of the |
-> Int | The number of "digits" of precision to take |
-> Uncert a |
Like withPrecision
, except takes a number of "digits" of precision in
the desired numeric base. For example, in base 2, takes the number of
bits of precision.
withPrecision
≡ withPrecisionAtBase 10
fromSamples :: Fractional a => [a] -> Uncert a Source #
Infer an Uncert
from a given list of independent samples of an
underlying uncertain or random distribution.
Inspecting properties
uStd :: Floating a => Uncert a -> a Source #
Get the standard deviation of the uncertainty of an Uncert
,
proportional to "how uncertain" a value is.
Very informally, it can be thought of as the interval above and below the mean that about 68% of sampled values will fall under after repeated sampling, or as the range that one is 68% sure the true value is within.
Is the square root of uVar
.
uRange :: Floating a => Uncert a -> (a, a) Source #
Retrieve the "range" of the underlying distribution of an Uncert
,
derived from the standard deviation, where which approximly 68% of
sampled values are expected to occur (or within which you are 68%
certain the true value is).
uRange (x +/- dx) ≡ (x - dx, x + dx)
Applying arbitrary functions
:: Fractional a | |
=> (forall s. AD s (Tower a) -> AD s (Tower a)) | Function on values to lift |
-> Uncert a |
|
-> Uncert a |
Lifts a numeric function over an Uncert
. Correctly propagates the
uncertainty according to the second-order taylor expansion expansion of
the function. Note that if the higher-degree taylor series terms are
large with respect to the mean and variance, this approximation may be
inaccurate.
Should take any function sufficiently polymorphic over numeric types, so
you can use things like sqrt
, sin
, negate
, etc.
ghci> liftU (\x -> log x ^ 2) (12.2 +/- 0.5) 6.3 +/- 0.2
liftU2 :: Fractional a => (forall s. AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a)) -> Uncert a -> Uncert a -> Uncert a Source #
Lifts a two-argument (curried) function over two Uncert
s. Correctly
propagates the uncertainty according to the second-order (multivariate)
taylor expansion expansion of the function. Note that if the
higher-degree taylor series terms are large with respect to the mean and
variance, this approximation may be inaccurate.
Should take any function sufficiently polymorphic over numeric types, so
you can use things like *
, atan2
, **
, etc.
ghci> liftU2 (\x y -> x**y) (13.5 +- 0.1) (1.64 +- 0.08) 70 +/- 10
liftU3 :: Fractional a => (forall s. AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a)) -> Uncert a -> Uncert a -> Uncert a -> Uncert a Source #
liftU4 :: Fractional a => (forall s. AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a)) -> Uncert a -> Uncert a -> Uncert a -> Uncert a -> Uncert a Source #
liftU5 :: Fractional a => (forall s. AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a) -> AD s (Sparse a)) -> Uncert a -> Uncert a -> Uncert a -> Uncert a -> Uncert a -> Uncert a Source #
:: (Traversable f, Fractional a) | |
=> (forall s. f (AD s (Sparse a)) -> AD s (Sparse a)) | Function on container of values to lift |
-> f (Uncert a) | Container of |
-> Uncert a |
Lifts a multivariate numeric function on a container (given as an f
a -> a
) to work on a container of Uncert
s. Correctly propagates the
uncertainty according to the second-order (multivariate) taylor
expansion of the function. Note that if the higher-degree taylor series
terms are large with respect to the means and variances, this
approximation may be inaccurate.
Should take any function sufficiently polymorphic over numeric types, so
you can use things like *
, sqrt
, atan2
, etc.
ghci> liftUF (\[x,y,z] -> x*y+z) [12.2 +- 0.5, 56 +- 2, 0.12 +/- 0.08] 680 +/- 40
Utility functions
uNormalize :: (Floating a, RealFrac a) => Uncert a -> Uncert a Source #
Attempts to "normalize" an Uncert
. Rounds the uncertainty (the
standard deviation) to one digit of precision, and rounds the central
moment up to the implied precision.
For example, it makes no real sense to have 542.185433 +/- 83.584
,
because the extra digits of 542.185433
past the tens place has no
meaning because of the overpowering uncertainty. Normalizing this
results in 540 +/- 80
.
Note that the Show
instance for Uncert
normalizes values before
showing them.
Like uNormalize
, but takes a numerical base to round with respect
to.
uNormalize
≡ uNormalizeAtBase 10