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

Xiao-Yong Jin xj2106 at columbia.edu
Wed Mar 25 10:21:55 EDT 2009


John Lato <jwlato at gmail.com> writes:

>> Yes, I know, it's not really complicate to rewrite the above
>> code.  But, what do I really gain from this rewrite?
>
> Apologies if this discussion has moved on, but I wanted to comment on this.
>

Thanks for elaborating it more.

>
> You gain correctness.  Any functions that need to be
>rewritten in this
> case should be rewritten anyway, because they're already wrong.  Your
> function ff can fail for certain inputs.  This statement:
>>> | 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.
>
> is conceptually wrong.  What does it mean to multiply the inverse of a
> non-invertible matrix by a scalar?  Obviously this is nonsensical.  If
> a computation can fail (as this can), the type of the function should
> reflect it.  The above functions
>
>>> f1 = scalarMult 2 . invMat
>>> f2 l r = l `multMat` invMat r
>
> should be
>
> f1 :: Matrix -> Maybe Matrix
> f1 = fmap (scalarMult 2) . invMat
>
> f2 :: Matrix -> Matrix -> Maybe Matrix
> f2 l r = fmap (multMat l) $ invMat r
>
> Of course these could be written with Control.Applicative as well:
>
> f1 m = scalarMult 2 <$> invMat m
> f2 l r = multMat l <$> invMat r
>
>
>>> ff :: Matrix -> Matrix -> YetAnotherBiggerMonad Matrix
>>> ff x y = let ff' = f1 x + f2 y
>  ...
>          in scalarMult (1/2) ff'
>
> (I think you may be missing an argument to f2 here.)
>
> This computation can fail as well, if the constituent parts fail.  The
> separate parts can be combined with applicative style:
>
> ff :: Matrix -> Matrix -> Maybe Matrix
> ff x y = scalarMult (1/2) <$> ( (+) <$> f1 x <*> f2 y)
>
> Compare this to the same code using monadic Maybe:
>
> ff :: Matrix -> Matrix -> Maybe Matrix
> ff x y = do
>   x' <- f1 x
>   y' <- f2 y
>   scalarMult (1/2) $ x' + y'
>
> You gain clarity and brevity.  Both examples are shorter and easier to
> understand because you aren't messing with all the plumbing of error
> handling using exceptions, although I find the Applicative version
> especially clear.  If you would like to keep track of why a
> computation failed, then use Either instead of Maybe with the Left
> carrying a reason for failure (e.g. NonInvertibleMatrix)
>
> Finally, you gain safety.  When you use a function f1 :: Matrix ->
> Matrix, you can be assured that you will get an actual, meaningful
> answer.  If you use a function f2 :: Matrix -> Maybe Matrix, you know
> that you may not get a meaningful answer, and it is simple to handle
> at the appropriate level of your code.  I (and many other Haskell
> users) find this to be conceptually cleaner than throwing dynamic
> exceptions or using undefined.
>
> Incidentally, this is one reason why many experienced Haskellers like
> the applicative style.  It allows you to express your computations
> without obtrusive error handling mixed in.  It's also more general
> than monads, so can be applied in more instances.
>
> div (and other non-total functions in the Prelude like head), are also
> frequently considered ugly hacks.  Just because we're stuck with
> something from H98 doesn't mean that it's necessarily good or elegant
> (the fail monad method and Functor not being a superclass of Monad
> come to mind).  In some ways FP has moved on since Haskell was
> formalized.
>
> There is an alternative approach that I believe was suggested by
> somebody else on the list:
>
> newtype InvMatrix = Invert {unWrap :: Matrix}
>
> then you can do
> invertMatrix :: Matrix -> Maybe InvMatrix
> invertMatrix = fmap Invert . invMat
>
> If you put these in a separate module and export InvMatrix, unwrap,
> and invertMatrix, but not Invert, then the only way to create an
> InvMatrix is with invertMatrix, so any data of type InvMatrix is
> guaranteed to be invertible (and inverted from what you used to create
> it).
>
> Then your ff function becomes:
>
> ff :: InvMatrix -> InvMatrix -> Matrix
>
> the final value of the function could be InvMatrix if you can prove
> that it's invertible after your operations (although to be efficient,
> this would require exporting the Invert constructor and a proof from
> the programmer).  This keeps ff pure; you don't even have to deal with
> Maybe (although there are other ramifications to doing this that
> should be considered).
>
> John
>
>
>

-- 
    c/*    __o/*
    <\     * (__
    */\      <


More information about the Haskell-Cafe mailing list