[Haskell-cafe] Uncertainty analysis library?

Tom Nielsen tanielsen at gmail.com
Sun Mar 20 22:46:34 CET 2011


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".)

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

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.

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

On Sun, Mar 20, 2011 at 8:38 PM, Edward Kmett <ekmett at gmail.com> wrote:
> I have a package for interval arithmetic in hackage
> http://hackage.haskell.org/package/intervals-0.2.0
> However it does not currently properly adjust the floating point rounding
> mode so containment isn't perfect.
> However, we are actively working on fixing up the Haskell MPFR bindings,
> which will let us reliably set rounding modes, cleaning up the interval
> arithmetic library to be just a little bit more pedantic. Due to the way GHC
> interacts with GMP this is a disturbingly difficult process.
> I have an unreleased library for working with Taylor models that builds on
> top of that and my automatic differentiation library, but without working
> MPFR bindings, it isn't sufficiently accurate for me to comfortably release.
> -Edward
>
> On Sun, Mar 20, 2011 at 4:27 PM, Edward Amsden <eca7215 at cs.rit.edu> wrote:
>>
>> Hi cafe,
>>
>> I'm looking for a library that provides an instance of Num,
>> Fractional, Floating, etc, but carries uncertainty values through
>> calculations. A scan of hackage didn't turn anything up. Does anyone
>> know of a library like this?
>>
>> Thanks!
>>
>> --
>> Edward Amsden
>> Student
>> Computer Science
>> Rochester Institute of Technology
>> www.edwardamsden.com
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



More information about the Haskell-Cafe mailing list