[Haskell-cafe] error vs. MonadError vs. fail
Daniel McAllansmith
dagda at xtra.co.nz
Tue Mar 28 15:57:00 EST 2006
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? What do
you give to the handler in the instance of MonadError?
newtype ErrMaybeT e m a = ErrMaybeT { runErrMaybeT :: m (Maybe a) }
instance (Monad m, Error e) => Monad (ErrMaybeT e m) where
return a = ErrMaybeT $ return (Just a)
m >>= k = ErrMaybeT $ do
a <- runErrMaybeT m
case a of
Nothing -> return Nothing
Just r -> runErrMaybeT (k r)
fail msg = ErrMaybeT $ return Nothing
instance (Monad m, Error e) => MonadError e (ErrMaybeT e m) where
throwError l = ErrMaybeT $ return Nothing
m `catchError` h = ErrMaybeT $ do
a <- runErrMaybeT m
case a of
Nothing -> runErrMaybeT (h ???) --what to do here?
Just r -> return (Just r)
f :: (MonadError String m) => Bool -> m Int
f b = if b
then return 42
else throwError "The boolean was false."
test1 b = do
r <- runErrorT $ f b
putStrLn (show r) --Left "..." or Right 42
return ()
test2 b = do
r <- runErrMaybeT $ f b
putStrLn (show r) --Nothing or Just 42
return ()
Daniel
More information about the Haskell-Cafe
mailing list