[Haskell-cafe] Uncertainty analysis library?

Edward Kmett ekmett at gmail.com
Mon Mar 21 18:36:12 CET 2011


On Sun, Mar 20, 2011 at 5:46 PM, Tom Nielsen <tanielsen at gmail.com> wrote:

> Interval arithmetic is of course not the same as uncertainty, although
> computer scientists like to pretend that is the case. (and uncertainty
> estimates do not have the be "rough".)
>

Very true.


> In general the propagation of errors depends on whether the errors are
> independent or not. The rules are given in Taylor: An introduction to
> Error analysis (1997). Interval artihmetic corresponds to the worst
> case of non-independent and non-random errors. In the case of
> independent of random errors, you get:
>


> data Approximately a = a :+/-: a
>
> instance Num a => Num (Approximately a) where
>  (m1 :+/-: err1) +  (m2 :+/-: err2) = (m1+m2) :+/-: (sqrt(err1^2+err2^2)
>  (m1 :+/-: err1) -  (m2 :+/-: err2) = (m1-m2) :+/-: (sqrt(err1^2+err2^2)
>  (m1 :+/-: err1) *  (m2 :+/-: err2) = (m1*m2) :+/-:
> (sqrt((err1/m1)^2+(err2/m2)^2)
>
> the general rule is
>
> if y = f xs where xs :: [Approximately a], i.e f :: [Approximately a]
> -> Approximately a
>
> the error term= sqrt $ sum $ map (^2) $ map (\(ym :+/-: yerr) ->
> partial-derivative-of-yerr-with-respect-to-partial-ym * yerr) xs
>
The danger here is, of course, the side-condition of independence, which can
make inhabitants of that type very difficult to reason about. e.g. x + x and
2*x in that world are very different.

In this sense the interval arithmetic bounds _are_ safer to work with in the
absence of sharing information even if they are less useful in the hands of
an expert.


> You can verify these things by running your calculation through soem
> sort of randomness monad (monte-carlo or random-fu packages) Anyways,
> I ended up not going down this route this because probabilistic data
> analysis gives you the correct error estimate without propagating
> error terms.


We are in total agreement here. =)


> Tom
>
> PS if you're a scientist and your accuracy estimate is on the same
> order as your rounding error, your are doing pretty well :-) At least
> in my field...


True enough, but in the case of interval arithmetic I like to be able to
preserve the invariant that if I am working with intervals (even if only to
collect accumulated rounding error in a Taylor model) that the answer lies
within the interval, and doesn't escape due to some tight boundary condition
or accumulated rounding error from when I was working too close to a pole.

In the case of Taylor models we try to keep the size of the intervals as
small as possible by using the first k terms of a Taylor polynomial and only
catching the slop in an interval.This is important because of course adding
and multiplying intervals will cause the size of the intervals to baloon
very quickly. Since the intervals in question are very close to the scale of
floating point rounding error as possible, and we often have to
conservatively slop the rounding error over from the Taylor coefficients
into the interval, accurate handling of tight corner cases is critical.

-Edward
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110321/cad5a38d/attachment.htm>


More information about the Haskell-Cafe mailing list