Copyright | (c) Justin Le 2016 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Provides the Corr
monad, which allows one to describe complex
relationships between random variables and evaluate their propagated
uncertainties respecting their inter-correlations.
See the Numeric.Uncertain.Correlated.Interactive module for an "interactive" and exploratory interface for this module's functionality.
Synopsis
- data Corr s a b
- evalCorr :: Fractional a => (forall s. Corr s a b) -> b
- data CVar s a
- sampleUncert :: Uncert a -> Corr s a (CVar s a)
- sampleExact :: a -> Corr s a (CVar s a)
- constC :: a -> CVar s a
- resolveUncert :: CVar s a -> Corr s a (Uncert a)
- liftC :: (forall t. AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a
- liftC2 :: (forall t. AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a -> CVar s a
- liftC3 :: (forall t. AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a -> CVar s a -> CVar s a
- liftC4 :: (forall t. AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a -> CVar s a -> CVar s a -> CVar s a
- liftC5 :: (forall t. AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a -> CVar s a -> CVar s a -> CVar s a -> CVar s a
- liftCF :: Functor f => (forall t. f (AD t (Sparse a)) -> AD t (Sparse a)) -> f (CVar s a) -> CVar s a
Corr
The Corr
monad allows us to keep track of correlated and
non-independent samples. It fixes a basic "failure" of the Uncert
type, which can't describe correlated samples.
For example, consider the difference between:
ghci> sum $ replicate 10 (12.5 +/-
0.8)
125 +/- 3
ghci> 10 * (12.5 +/- 0.8)
125 +/- 8
The first one represents the addition of ten independent samples, whose errors will in general cancel eachother out. The second one represents sampling once and multiplying it by ten, which will amplify any error by a full factor of 10.
See how the Corr
monad expresses the above computations:
ghci>evalCorr
$ do x <-sampleUncert
$ 12.5+/-
0.8 y1 <-resolveUncert
$ sum (replicate 10 x) y2 <- resolveUncert $ 10 * x return (y1, y2) (125 +/- 8, 125 +/- 8) ghci>evalCorr
$ do xs <- replicateM 10 (sampleUncert
(12.5 +/- 0.8))resolveUncert
$ sum xs 125 +/- 3
The first example samples once and describes operations on the single
sample; the second example samples 10 times with replicateM
and sums
all of the results.
Things are more interesting when you sample multiple variables:
ghci>evalCorr
$ do x <-sampleUncert
$ 12.5+/-
0.8 y <- sampleUncert $ 15.9 +/- 0.5 z <- sampleUncert $ 1.52 +/- 0.07 let k = y ** xresolveUncert
$ (x+z) * logBase z k 1200 +/- 200
The first parameter is a dummy phantom parameter used to prevent CVar
s
from leaking out of the computation (see evalCorr
). The second
parameter is the numeric type of all samples within the description (for
example, if you ever sample an
, the second parameter wil
be Uncert
Double
Double
). The third parameter is the result type of the
computation -- the value the Corr
is describing.
evalCorr :: Fractional a => (forall s. Corr s a b) -> b Source #
Evaluates the value described by a Corr
monad, taking into account
inter-correlations between samples.
Takes a universally qualified Corr
, which should not affect usage.
See the examples in the documentation for Corr
. The univeral
qualification is mostly a type system trick to ensure that you aren't
allowed to ever use evalCorr
to evaluate a CVar
.
Uncertain and Correlated Values
Represents a single sample (or a value calculated from samples) within
the Corr
monad. These can be created with sampleUncert
,
sampleExact
, and constC
, or made by combinining others with its
numeric typeclass instances (like Num
) or its functions lifting
arbitrary numeric functions (like liftC2
). These keep track of
inter-correlations between sources, and if you add together two CVar
s
that are correlated, their results will reflect this.
Can be "resolved" into the uncertain value they represent using
resolveUncert
.
Note that these are parameterized by a dummy phantom parameter s
so
that they can't be "evaluated" out of the Corr
they live in with
evalCorr
.
Note that a
can only ever meaningfully "exist" in a CVar
s a
, meaning that the all samples within that Corr
s aCorr
are of the same
type.
Instances
Floating a => Floating (CVar s a) Source # | |
Defined in Numeric.Uncertain.Correlated.Internal sqrt :: CVar s a -> CVar s a # (**) :: CVar s a -> CVar s a -> CVar s a # logBase :: CVar s a -> CVar s a -> CVar s a # asin :: CVar s a -> CVar s a # acos :: CVar s a -> CVar s a # atan :: CVar s a -> CVar s a # sinh :: CVar s a -> CVar s a # cosh :: CVar s a -> CVar s a # tanh :: CVar s a -> CVar s a # asinh :: CVar s a -> CVar s a # acosh :: CVar s a -> CVar s a # atanh :: CVar s a -> CVar s a # log1p :: CVar s a -> CVar s a # expm1 :: CVar s a -> CVar s a # | |
Fractional a => Num (CVar s a) Source # | |
Defined in Numeric.Uncertain.Correlated.Internal | |
Fractional a => Fractional (CVar s a) Source # | |
Sampling
sampleExact :: a -> Corr s a (CVar s a) Source #
Generate an exact sample in Corr
with zero uncertainty,
independently from all other samples.
Not super useful, since you can do something equivalent with constC
or the numeric instances:
sampleExact x ≡ return (constC
x)
sampleExact 10 ≡ return 10
But is provided for completeness alongside sampleUncert
.
Note that you can exactly sample an a
within a
, meaning
that all other "sampled" values are also Corr
s aa
s.
Resolving
resolveUncert :: CVar s a -> Corr s a (Uncert a) Source #
Resolve an Uncert
from a CVar
using its potential multiple
samples and sample sources, taking into account inter-correlations
between CVar
s and samples.
Note that if you use sampleUncert
on the result, the new sample will
be treated as something completely independent. Usually this should
only be used as the "exit point" of a Corr
description.
Applying arbitrary functions
:: (forall t. AD t (Sparse a) -> AD t (Sparse a)) | Function on values to lift |
-> CVar s a |
|
-> CVar s a |
Lifts a numeric function over the sample represented by a CVar
.
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>evalCorr
$ do x <-sampleUncert
$ 12.5+/-
0.8 y <- sampleUncert $ 15.9 +/- 0.5resolveUncert
$ liftC (\z -> log z ^ 2) (x + y) 11.2 +/- 0.2
liftC2 :: (forall t. AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a -> CVar s a Source #
Lifts a two-argument (curried) function over the samples represented
by two CVar
s. Correctly propagates the uncertainty according to the
second-order (multivariate) taylor expansion expansion of the function,
and properly takes into account and keeps track of all
inter-correlations between the CVar
samples. 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>evalCorr
$ do x <-sampleUncert
$ 12.5+/-
0.8 y <- sampleUncert $ 15.9 +/- 0.5resolveUncert
$ liftC2 (\a b -> log (a + b) ^ 2) x y 11.2 +/- 0.2
liftC3 :: (forall t. AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a -> CVar s a -> CVar s a Source #
liftC4 :: (forall t. AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a -> CVar s a -> CVar s a -> CVar s a Source #
liftC5 :: (forall t. AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a) -> AD t (Sparse a)) -> CVar s a -> CVar s a -> CVar s a -> CVar s a -> CVar s a -> CVar s a Source #
:: Functor f | |
=> (forall t. f (AD t (Sparse a)) -> AD t (Sparse a)) | Function on container of values to lift |
-> f (CVar s a) | Container of |
-> CVar s a |
Lifts a multivariate numeric function on a container (given as an f
a -> a
) to work on a container of CVar
s. Correctly propagates the
uncertainty according to the second-order (multivariate) taylor
expansion of the function, and properly takes into account and keeps
track of all inter-correlations between the CVar
samples. 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>evalCorr
$ do x <-sampleUncert
$ 12.5+/-
0.8 y <- sampleUncert $ 15.9 +/- 0.5 z <- sampleUncert $ 1.52 +/- 0.07resolveUncert
$ liftCF (\[a,b,c] -> (a+c) * logBase c (b**a)) x y z 1200 +/- 200