[Haskell-cafe] error vs. MonadError vs. fail

Andrew Pimlott andrew at pimlott.net
Mon Mar 27 14:29:21 EST 2006


On Mon, Mar 27, 2006 at 02:53:58PM +1200, Daniel McAllansmith wrote:
> Is there a consensus on how anticipatable failure situations should be 
> handled?
> 
> There was a thread, "haskell programming guidelines", from 2006-02-25 where 
> John Meacham and Cale Gibbard had a bit of back-and-forth about using 
> Monad.fail or a purpose specific MonadFail class.
> 
> Using fail certainly seems quick and easy, but I find it a bit
> distasteful for a few different reasons:

All of your reasons are good, but I recently tripped over an even better
one:  While fail must be defined in all monads, it has no sensible
definition in many, and so throws an exception.  I got burned because I
wrote a function to run some monad of mine, which might result in an
answer or an error, and I used fail for the error case:

    run :: Monad m => MyMonad a -> m a
    run m = ... if ... then return x else fail e

Then, I accidentally (this was spread across two functions) ran my monad
twice:

    run (run m)

This typechecked and crashed.  The inner run was given type

    MyMonad a -> MyMonad a

and you can guess what fail does in MyMonad.  Ugh.  If I had used
MonadError for the return value of run, run would only typecheck in a
monad that can sensibly handle errors, catching my bug.

> Apparently the advantage of fail is that user of the library can choose to 
> receive failures as eg Maybes, Eithers, [], or whatever they like.
...
> MonadError is not up to this task as far as I can tell.

Why not?  All that needs to be done is write the missing instances, eg

    instance MonadError () Maybe where
      throwError x           = Nothing
      Nothing `catchError` f = f ()
      Just x `catchError` f  = Just x

    instance Error () where
      noMsg                  = ()
      strMsg s               = () 

As you might tell, I would like to see this instance in MonadError.  An
instance for [] is however questionable, IMO.

BTW, I've posted about these issues several times, eg

    http://www.haskell.org/pipermail/haskell-cafe/2005-June/010361.html

Andrew


More information about the Haskell-Cafe mailing list