Copyright | (c) Justin Le 2016 |
---|---|
License | BSD3 |
Maintainer | justin@jle.im |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Exports all of the interface of Numeric.Uncertain.Correlated, except
meant to be run in a ghci session "interactively" for exploratory
purposes, or in a plain IO
action (instead of inside a Corr
monad).
For example, with the Numeric.Uncertain.Correlated interface:
ghci>evalCorr
$ do x <- sampleUncert $ 12.5+/-
0.8 y <- sampleUncert $ 15.9 +/- 0.5 z <- sampleUncert $ 1.52 +/- 0.07 let k = y**x resolveUncert $ (x+z) * logBase z k 1200 +/- 200
And with the interface from this "interactive" module:
ghci> x <-sampleUncert
$ 12.5 +/- 0.8 ghci> y <- sampleUncert $ 15.9 +/- 0.5 ghci> z <- sampleUncert $ 1.52 +/- 0.07 ghci> let k = y**x ghci>resolveUncert
$ (x+z) * logBase z k 1200 +/- 200
The main purpose of this module is to allow one to use ghci as a fancy "calculator" for computing and exploring propagated uncertainties of complex and potentially correlated samples with uncertainty.
Because many of the names overlap with the names from the Numeric.Uncertain.Correlated module, it is recommended that you never have both imported at the same time in ghci or in a file, or import them qualified if you must.
Also note that all of these methods only work with
s,
and are not polymorphic over different numeric types.Uncert
Double
Be aware that this module is not robustly tested in heavily concurrent situations/applications.
Synopsis
- data CVar s a
- type CVarIO = CVar RealWorld Double
- sampleUncert :: Uncert Double -> IO CVarIO
- sampleExact :: Double -> IO CVarIO
- constC :: a -> CVar s a
- resolveUncert :: CVarIO -> IO (Uncert Double)
- 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
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 :: Double -> IO CVarIO Source #
Generate an exact sample in IO
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
.
Resolving
resolveUncert :: CVarIO -> IO (Uncert Double) Source #
Resolve an Uncert
from a CVarIO
using its potential multiple
samples and sample sources, taking into account inter-correlations
between CVarIO
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 "final value" of your computation or exploration.
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