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

Andrew Pimlott andrew at pimlott.net
Tue Mar 28 16:49:55 EST 2006


On Wed, Mar 29, 2006 at 08:57:00AM +1200, Daniel McAllansmith wrote:
> On Tuesday 28 March 2006 07:29, Andrew Pimlott wrote:
> > > 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               = ()
> >
> 
> How would you go about writing the Maybe based analogue of ErrorT?

Maybe is a MonadError only with a dummy error type, which is why I used
() above.  Same with your ErrMaybeT:

    newtype ErrMaybeT m a = ErrMaybeT { runErrMaybeT :: m (Maybe a) } 

    instance Monad m => MonadError () (ErrMaybeT m) where
        throwError l     = ErrMaybeT $ return Nothing
        m `catchError` h = ErrMaybeT $ do
            a <- runErrMaybeT m 
            case a of
                Nothing -> runErrMaybeT (h ())
                Just r -> return (Just r)

If you want to write a MonadError operation that can be used with Maybe
or Either, it would look like

    f :: (MonadError e m, Error e) => Bool -> m Int 
    f b = if b
        then return 42
        else throwError (strMsg "The boolean was false.")

But I see your point now about MonadFail (having throw but not catch)
being perhaps preferable for this use.

Andrew


More information about the Haskell-Cafe mailing list