Control.Exceptions and MonadIO

Robert Dockins wrote:
One additional (very unfortunate) point is that higher-order IO monad combinators will not work on your monad, eg, the ones in Control.Exception.
Although that is true in general, for many useful and interesting cases (including ReaderT, the state transformer, and the newtype wrapping of IO) one _can_ use catch, bracket etc. constructs in MonadIO. Please see this message and the follow-up discussion: http://www.haskell.org/pipermail/haskell/2006-February/017547.html

oleg@pobox.com wrote:
Robert Dockins wrote:
One additional (very unfortunate) point is that higher-order IO monad combinators will not work on your monad, eg, the ones in Control.Exception.
Although that is true in general, for many useful and interesting cases (including ReaderT, the state transformer, and the newtype wrapping of IO) one _can_ use catch, bracket etc. constructs in MonadIO. Please see this message and the follow-up discussion:
http://www.haskell.org/pipermail/haskell/2006-February/017547.html
I still don't see how this helps with the StateT transformer for example, because the state would be lost which isn't much use. For example, here is my attempt to implement a version of bracket_ which would work with an arbitrary StrictMonadIO: class MonadIO m => StrictMonadIO m where getUnliftIO :: m (m a -> IO a) instance StrictMonadIO IO where getUnliftIO = return id instance StrictMonadIO m => StrictMonadIO (StateT s m) where getUnliftIO = StateT $ \s -> do unliftIO <- getUnliftIO return (\(StateT s_mas) -> do (a, _) <- unliftIO (s_mas s) -- NEW STATE LOST return a , s) -- OLD STATE IS RETURNED bracket_ :: StrictMonadIO m => m a -> m b -> m c -> m c bracket_ a b c = do unliftIOa <- getUnliftIO unliftIOb <- getUnliftIO unliftIOc <- getUnliftIO liftIO $ bracket_ (unliftIOa a) (unliftIOb b) (unliftIOc c) There are some points that are problematic: 1) Any changes made to the state by unlifted actions are discarded 2) The implementation of bracket_ seems unnecessarily messy because of the strange limitation that higher rank polymorphism is not allowed ie the following definition gives a compiler error: getUnliftIO :: m (forall a. m a -> IO a) -- what's wrong with this? So the essential question is: does there exist any way to implement a bracket_ that will work properly with a state monad? I'm also wondering: exactly why is it impossible to implement the Exception functions for an arbitrary MonadIO? Surely the higher order functions could just be implemented using some very low level primitives like: push_block_async :: IO () pop_block_async :: IO () push_unblock_async :: IO () pop_unblock_async :: IO () block :: MonadIO m -> m a -> m a block x = do liftIO push_block_async a <- x liftIO pop_block_async return a bracket_ a b c = block $ do a unblock c b Thanks, Brian.

oleg@pobox.com wrote:
Robert Dockins wrote:
One additional (very unfortunate) point is that higher-order IO monad combinators will not work on your monad, eg, the ones in Control.Exception.
Although that is true in general, for many useful and interesting cases (including ReaderT, the state transformer, and the newtype wrapping of IO) one _can_ use catch, bracket etc. constructs in MonadIO. Please see this message and the follow-up discussion:
http://www.haskell.org/pipermail/haskell/2006-February/017547.html
If it is true that it is absolutely impossible to implement Control.Exception for any MonadIO (it would be useful to know why cf the old saying "there is no such word as can't"), the other option seems to be to re-organise Control.Exception to make use of different monads that could support the various subsets of operations, as you've begun in the thread above by defining CaughtMonadIO. Perhaps something like: class MonadIO m => MonadIOE m where catch :: m a-> (Exception -> m a) -> m a throw catchDyn throwDyn -- etc instance MonadIOE m => StateT s m where ... instance MonadIOE m => ReaderT r m where ... blockIO :: IO a -> IO a class MonadIO m => MonadIOB m where getUnliftIO :: m (m a -> IO a) block :: m a -> m a block x = do unliftIO <- getUnliftIO liftIO (blockIO (unliftIO x)) unblock :: m a -> m a bracket_ :: m a -> m b -> m c -> m c -- etc instance MonadIOB m => ReaderT r m where ... and then we could just get rid of all the other exception handling functions scattered all over the code base eg Prelude.catch etc. StateT s can be an instance of MonadIOE but not of MonadIOB because although it is sometimes fine to discard state changes when an exception arises, it is not ok to discard the state changes inside a block (or unblock, bracket_ etc). Does the above look like a good way of organising things? (I don't know whether MonadIOB would require MonadIOE or not since I haven't tried to implement all these functions yet - if it did I would use the name MonadIOEB instead) I'm about to make an attempt along these lines myself since I can't go further in my own work without a proper exception api that doesn't drag everything down to concrete IO (unless someone else has already done this?) Also, would it be worth modifying http://hackage.haskell.org/trac/haskell-prime/ticket/110 to include something like this (someone more knowledgeable than me would have to do it)? Regards, Brian.

Brian Hulley wrote:
instance MonadIOE m => StateT s m where ... instance MonadIOE m => ReaderT r m where ...
instance MonadIOB m => ReaderT r m where ...
Ooops! ;-) instance MonadIOE m => MonadIOE (StateT s m) where ... instance MonadIOE m => MonadIOE (ReaderT r m) where ... instance MonadIOB m => MonadIOB (ReaderT r m) where ...

I've started work on a module to replace Control.Exception by wrapping all the original Control.Exception functions in more general monadic functions and using two type classes as follows: class MonadIO m => MonadException m where catch :: m a -> (Exception -> m a) -> m a catchDyn :: Typeable exception => m a -> (exception -> m a) -> m a catchJust :: (Exception -> Maybe b) -> m a -> (b -> m a) -> m a try :: m a -> m (Either Exception a) tryJust :: (Exception -> Maybe b) -> m a -> m (Either b a) and class MonadIO m => MonadIOU m where getUnliftIO :: m (m a -> IO a) All the other functions can be implemented just using MonadIO or MonadIOU or MonadException in place of IO (depending on the function eg bracket needs MonadIOU) - just in case anyone is interested. As far as I can tell this seems to be the one and only way to do it with the minimal sized classes but I'd be interested if anyone has found a better way. Regards, Brian.

Brian Hulley wrote:
I've started work on a module to replace Control.Exception by wrapping all the original Control.Exception functions in more general monadic functions and using two type classes as follows:
class MonadIO m => MonadException m where catch :: m a -> (Exception -> m a) -> m a catchDyn :: Typeable exception => m a -> (exception -> m a) -> m a catchJust :: (Exception -> Maybe b) -> m a -> (b -> m a) -> m a try :: m a -> m (Either Exception a) tryJust :: (Exception -> Maybe b) -> m a -> m (Either b a)
and
class MonadIO m => MonadIOU m where getUnliftIO :: m (m a -> IO a)
All the other functions can be implemented just using MonadIO or MonadIOU or MonadException in place of IO (depending on the function eg bracket needs MonadIOU) - just in case anyone is interested.
After more thought, it seems that it *should* be possible to implement block and unblock for StateT monads under certain conditions, using a different unlift function to return IO (a,s) instead of just IO a. Therefore I've changed things around, and also by looking at the source code for the current Control.Exception module, arrived at the following revised design (I've implemented all the other functions in terms of the classes below) class MonadIO m => MonadException m where catch :: m a -> (Exception -> m a) -> m a catchDyn :: Typeable exception => m a -> (exception -> m a) -> m a block, unblock :: MonadException m => m a -> m a class MonadIO m => MonadIOU m where getUnliftIO :: m (m a -> IO a) However I then want to say that any instance of MonadIOU is also an instance of MonadException. I tried: instance MonadIOU m => MonadException m where catch action e_m = do unliftIOa <- getUnliftIO unliftIOb <- getUnliftIO liftIO $ C.catch (unliftIOa action) (\e -> unliftIOb(e_m e)) -- etc but this only compiles with -fallow-undecidable-instances. I'm puzzled at why there is a problem with such a simple instance declaration, and also don't know if this means my design is fatally flawed. The highlight of the above design is that all that's needed for many monads such as MonadIOU m => ReaderT r m is a definition of the one unlifting function, but it also allows instances of MonadException to be declared where the monad (eg a StateT s m) doesn't support this particular operation. Any ideas? Thanks, Brian.

On Sunday 23 April 2006 02:19 pm, you wrote: [snip some discussion]
Perhaps something like:
class MonadIO m => MonadIOE m where catch :: m a-> (Exception -> m a) -> m a throw catchDyn throwDyn -- etc
instance MonadIOE m => StateT s m where ... instance MonadIOE m => ReaderT r m where ...
blockIO :: IO a -> IO a
class MonadIO m => MonadIOB m where getUnliftIO :: m (m a -> IO a) block :: m a -> m a block x = do unliftIO <- getUnliftIO liftIO (blockIO (unliftIO x))
unblock :: m a -> m a bracket_ :: m a -> m b -> m c -> m c -- etc
instance MonadIOB m => ReaderT r m where ...
and then we could just get rid of all the other exception handling functions scattered all over the code base eg Prelude.catch etc.
StateT s can be an instance of MonadIOE but not of MonadIOB because although it is sometimes fine to discard state changes when an exception arises, it is not ok to discard the state changes inside a block (or unblock, bracket_ etc).
Does the above look like a good way of organising things?
I think the basic distinction is good; the added ability to "project" out the IO monad seems to be the important point (although I wonder if the other methods need to be in the class?). It seems to me, however, that the devil is in the details for something like this. It's hard to know if the whole thing hangs together without an implementation.
(I don't know whether MonadIOB would require MonadIOE or not since I haven't tried to implement all these functions yet - if it did I would use the name MonadIOEB instead) I'm about to make an attempt along these lines myself since I can't go further in my own work without a proper exception api that doesn't drag everything down to concrete IO (unless someone else has already done this?)
Also, would it be worth modifying http://hackage.haskell.org/trac/haskell-prime/ticket/110 to include something like this (someone more knowledgeable than me would have to do it)?
Well, I created the ticket without much in the way of details -- feel free to add a concrete proposal. I suppose we can take up discussion on the haskell-prime list when discussion is opened on topics besides concurrency and the class system.
Regards, Brian.
Rob Dockins
participants (3)
-
Brian Hulley
-
oleg@pobox.com
-
Robert Dockins