Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Why can't ContT be made an instance of MonadError?

I have a monad transformer stack including an ErrorT and I want to wrap a ContT r transformer around the whole thing. When I try to do that, my calls to throwError generate type errors - apparently ContT r isn't automatically an instance of MonadError. Fine, I thought - I'll just make it into one:

instance MonadError e m => MonadError e (ContT r m) where
  throwError = lift . throwError
  catchError = liftCatch . catchError

using some suitable definition of liftCatch. But now I get errors when compiling:

src\Language\Types.hs:68:10:
    Illegal instance declaration for `MonadError e (ContT r m)'
      (the Coverage Condition fails for one of the functional dependencies;
       Use -XUndecidableInstances to permit this)
    In the instance declaration for `MonadError e (ContT r m)'

I'm happy to use the UndecidableInstances pragma (I'm under the impression it's not too worrisome, e.g. see this question) but I wondered if there was a difficulty in making the continuation transformer into an instance of MonadError - I guess that if it was fine, the authors of the Control.Monad.Trans package would have done it already... right?

like image 740
Chris Taylor Avatar asked May 24 '12 17:05

Chris Taylor


1 Answers

ContT and ErrorT both allow non-standard control flow. There is a way to wrap the ErrorT type around ContT in mtl:

instance (Error e, MonadCont m) => MonadCont (ErrorT e m)

But these two monad transformers do not commute. Remembering:

newtype Identity a = Identity {runIdentity :: a}
newtype ErrorT e m a = ErrorT {runErrorT :: m (Either e a)}
newtype ContT r m a = ContT {runContT :: (a -> m r) -> m r}

ErrorT String (ContT Bool Identity) () which is okay in package mtl could be:

ErrorT (ContT ( \ (k :: Either String () -> Identity Bool) -> k (Right ()) ) )

ContT r (ErrorT e Identity) a is not okay in package mtl. But you can write it.

What are the semantics of (>>=) you want in the combined monad? How do you expect your stack of nested error handlers to interact with nonlocal callCC?

Here is how I might write it:

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances   #-}
import Control.Monad
import Control.Monad.Cont
import Control.Monad.Error
import Data.Function
import Data.IORef

handleError :: MonadError e m => (e -> m a) -> m a -> m a
handleError = flip catchError

test2 :: ErrorT String (ContT () IO) ()
test2 = handleError (\e -> throwError (e ++ ":top")) $ do
  x <- liftIO $ newIORef 1
  label <- callCC (return . fix)
  v <- liftIO (readIORef x)
  liftIO (print v)
  handleError (\e -> throwError (e ++ ":middle")) $ do
    when (v==4) $ do
      throwError "ouch"
  when (v < 10) $ do
         liftIO (writeIORef x (succ v))
         handleError (\e -> throwError (e ++ ":" ++ show v)) label
  liftIO $ print "done"

go2 = runContT (runErrorT test2) (either error return)

{-

*Main> go2
1
2
3
4
*** Exception: ouch:middle:top

-}

So the above works with just the mtl, here is the new instance and how it works:

instance MonadError e m => MonadError e (ContT r m) where
  throwError = lift . throwError
  catchError op h = ContT $ \k -> catchError (runContT op k) (\e -> runContT (h e) k)

test3 :: ContT () (ErrorT String IO) ()
test3 = handleError (\e -> throwError (e ++ ":top")) $ do
  x <- liftIO $ newIORef 1
  label <- callCC (return . fix)
  v <- liftIO (readIORef x)
  liftIO (print v)
  handleError (\e -> throwError (e ++ ":middle")) $ do
    when (v==4) $ do
      throwError "ouch"
  when (v < 10) $ do
         liftIO (writeIORef x (succ v))
         handleError (\e -> throwError (e ++ ":" ++ show v)) label
  liftIO $ print "done"

go3 = runErrorT (runContT test3 return)

{-

*Main> go3
1
2
3
4
Left "ouch:middle:3:middle:2:middle:1:middle:top"

-}
like image 90
Chris Kuklewicz Avatar answered Nov 03 '22 01:11

Chris Kuklewicz