
I just discovered Control.Monad.Error, and all sorts of questions and ideas came to mind. I would be happy for any comments or pointers. - Monad and MonadError are uncannily similar, especially if you ignore that ugly duckling fail: class (Monad m) => MonadError e m | m -> e where throwError :: e -> m a catchError :: m a -> (e -> m a) -> m a The instances for Either are exactly symmetrical. Is there some more general way to look at this that makes the symmetry stand out? - The instance MonadError IOError IO is problematic, because one might have preferred to use Control.Exception.Exception as the error type. I've been told that the latter is generally preferred, and it's what I usually want. Any chance of the instance being changed? - It's a shame that the utility functions in Control.Exception aren't defined in terms of MonadError. Maybe they should at least be duplicated in Control.Monad.Error. - Why not instance MonadError () Maybe where throwError x = Nothing Nothing `catchError` f = f () Just x `catchError` f = Just x instance Error () where noMsg = () strMsg s = () ? This would seem to facilitate a variation of the "NotJustMaybe" pattern, using MonadError instead of Monad. What I'm getting at is that it might be nice to see MonadError used more in preference to Monad. Then we can get rid of fail. ;-) - I found this function terribly useful: liftError :: (MonadError e m, MonadTrans t, MonadError e (t m)) => m a -> t m a liftError m = join (lift (liftM return m `catchError` (return . throwError))) However, I'm not sure exactly how to describe it (or what to call it--maybe liftTry). It basically pulls errors from the inner monad to the outer monad. One application is try :: MonadError e m => m a -> m (Either e a) try m = runErrorT (liftError m) The really nice thing for me is that I can use it with StateT to prevent errors from disturbing the state, as normally happens when you mix StateT with, say, IO: test1 = execStateT test 0 >>= print where test :: StateT Int IO () test = do put 2 lift (fail "foo") `catchError` \e -> modify (+1) This prints 1, because the IOError obliterates all state changes in the first argument to catchError. However, test2 = execStateT (runErrorT test) 0 >>= print where test :: ErrorT IOError (StateT Int IO) () test = do put 2 liftError (fail "foo") `catchError` \e -> modify (+1) prints 3, because the IOError was caught by liftError, then passed down along with the state change. Oh, and test2 = execStateT (runErrorT test) 0 >>= print where test :: ErrorT IOError (StateT Int IO) () test = do put 2 lift (fail "foo") `catchError` \e -> modify (+1) raises an IOError, because the error is never seen by the outer monad (and catchError). Andrew
participants (1)
-
Andrew Pimlott