[Haskell-cafe] Re: Exception handling in numeric computations

Luke Palmer lrpalmer at gmail.com
Tue Mar 24 17:28:14 EDT 2009


On Tue, Mar 24, 2009 at 3:14 PM, Xiao-Yong Jin <xj2106 at columbia.edu> wrote:

> Jake McArthur <jake at pikewerks.com> writes:
>
> > Xiao-Yong Jin wrote:
> > | The problem is that there will be many functions using such
> > | a function to invert a matrix, making this inversion
> > | function return Either/Maybe or packing it in a monad is
> > | just a big headache.
> >
> > I disagree. If you try to take the inverse of a noninvertable matrix,
> > this is an *error* in your code. Catching an error you created in pure
> > code and patching it with chewing gum it is just a hack. A monadic
> > approach (I'm putting Either/Maybe under the same umbrella for brevity)
> > is the only solution that makes any sense to me, and I don't think it's
> > ugly as you are making it out to be.
> >
>
> Then, why is 'div' not of type 'a -> a -> ArithExceptionMonad a' ?
> Why does it throws this /ugly/ /error/ when it is applied to
> 0?  Why is it not using some beautiful
> 'ArithExceptinoMonad'?  Is 'Control.Exception' just pure
> /ugly/ and doesn't make any sense?


It's a proof obligation, like using unsafePerformIO.  It is "okay" to use
unsafePerformIO when it exhibits purely functional semantics, but it's
possible to use it incorrectly, and there is no ImpureSemanticsException.
If you are being rigorous, you simply have to prove that the denominator
will not be zero, rather than relying on it to be caught at runtime.  You
can move the check to runtime easily:

safeDiv x 0 = Nothing
safeDiv x y = Just (x `div` y)

Going the other way, from a runtime check to an obligation, is impossible.


>
> >
> > | It is impractical to use method (a),
> > | because not every function that uses 'invMat' knows how to
> > | deal with 'invMat' not giving an answer.  So we need to use
> > | method (b), to use monad to parse our matrix around.
> > |
> > |> > invMat :: Matrix -> NumericCancerMonad Matrix
> > |
> > | It hides the exceptional nature of numerical computations
> > | very well, but it is cancer in the code.  Whenever any
> > | function wants to use invMat, it is mutated.  This is just
> > | madness.  You don't want to make all the code to be monadic
> > | just because of singularities in numeric calculation.
> >
> > For functions that don't know or don't care about failure, just use fmap
> > or one of its synonyms.
> >
> > ~    scalarMult 2 <$> invMat x
> >
> > See? The scalarMult function is pure, as it should be. There is no
> > madness here.
>
> Of course, 'scalarMult' is invulnerable and free of monad.
> But take a look at the following functions,
>
> > f1 = scalarMult 2 . invMat
> > f2 l r = l `multMat` invMat r
> > ff :: Matrix -> Matrix -> YetAnotherBiggerMonad Matrix
> > ff x y = do let ff' = f1 x + f2 y
> >             put . (addMat ff') . f1 << get
> >             tell $ f2 ff'
> >             when (matrixWeDontLike (f1 ff') $
> >                  throwError MatrixWeDontLike
> >             return $ scalarMult (1/2) ff'
>
> Yes, I know, it's not really complicate to rewrite the above
> code.  But, what do I really gain from this rewrite?
> --
>    c/*    __o/*
>    <\     * (__
>    */\      <
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090324/76c3b10b/attachment.htm


More information about the Haskell-Cafe mailing list