MonadCatchIO, finally and the error monad

Hey all, In case anyone noticed, Haskellers occassionally dies with a "Pool exhausted exception." I've traced this to a bug in Yesod, which in turn is a bug in the neither package, which I believe is a flawed design in the MonadCatchIO-transformers package. Here are my thoughts on this and what I think needs to be done to fix it. In Control.Exception, we define a number of different ways of dealing with exceptions. All of these can be expressed in terms of block, unblock and catch. For our purposes here, I'm going to ignore block and unblock: they deal with asynchronous exceptions, which is not my point here. Keep that in mind with the code samples. Anyway, with this caveat, we can define finally as: finally :: IO a -> IO b -> IO a a `finally` sequel = do r <- a `catch` \e -> sequel >> throwIO (e :: SomeException) _ <- sequel return r The idea is simple: try to perform the action. If any exceptions get thrown, call sequel and rethrow the exception. If we ever get to line 4, it's because no exceptions were thrown. Therefore, we know that sequel has not yet been called, so we call it. Said another way: there are precisely two cases: * An exception was thrown * An exception was not thrown A downside of this finally function (and catch, for that matter) is that it requires all of the actions to live in the IO monad, when in fact we all love to let things run in complicated monad transformer stacks. So along comes MonadCatchIO-(transformers, mtl) and gives us a new magical definition of catch: catch :: (MonadCatchIO m, Exception e) => m a -> (e -> m a) -> m a Using this new, extended definition of catch, we can define a finally function with the type signature finally :: MonadCatchIO m => m a -> m b -> m a (Note that we need to replace throwIO with liftIO . throwIO.) You can try this with writers, readers, etc, and everything works just fine. You can even use an Error/Either monad transformer, throw an exception, and the finally function will correctly run your sequel function. However, things don't work out so well when you use a throwError. Let's see the code: {-# LANGUAGE PackageImports #-} import Control.Monad.Trans.Error import "MonadCatchIO-transformers" Control.Monad.CatchIO (finally) import Control.Monad.IO.Class main = runErrorT $ finally go $ liftIO $ putStrLn "sequel called" go :: ErrorT String IO String --go = return "return" --go = error "error" --go = throwError "throwError" Try running the code with each version of go uncommented. In the first two, "sequel called" gets printed. However, in the third, it does not. The reason is short-circuiting: if we remember from the definition of finally, there are two cases we account for. If an exception is called, catch addresses it. If not, we assume that the next line will be called. However, in the presence of short-circuiting monads like ErrorT, that line of code will never get called! I have a recommendation of how to fix this: the MonadCatchIO typeclass should be extended to include finally, onException and everything else. We can provide default definitions which will work for most monads, and short-circuiting monads like ErrorT (and I imagine ContT as well) will need to override them. Michael

By the way, here is how I would implement the ErrorT MonadCatchIO instance:
instance (MonadCatchIO m, Error e) => MonadCatchIO (ErrorT e m) where
m `catch` f = mapErrorT (\m' -> m' `catch` \e -> runErrorT $ f e) m
block = mapErrorT block
unblock = mapErrorT unblock
bracket before after thing = block $ do
a <- before
unblock $ thing a `finally` after a
bracket_ before after thing = block $ do
_ <- before
unblock $ thing `finally` after
finally thing after = mapErrorT (`finally` runErrorT after) thing
By using "finally" inside of the definitions of bracket, bracket_ and
finally, we can ensure that if there is any "special" monad underneath
our ErrorT, the cleanup function will still run.
Michael
On Thu, Oct 14, 2010 at 12:01 PM, Michael Snoyman
Hey all,
In case anyone noticed, Haskellers occassionally dies with a "Pool exhausted exception." I've traced this to a bug in Yesod, which in turn is a bug in the neither package, which I believe is a flawed design in the MonadCatchIO-transformers package. Here are my thoughts on this and what I think needs to be done to fix it.
In Control.Exception, we define a number of different ways of dealing with exceptions. All of these can be expressed in terms of block, unblock and catch. For our purposes here, I'm going to ignore block and unblock: they deal with asynchronous exceptions, which is not my point here. Keep that in mind with the code samples. Anyway, with this caveat, we can define finally as:
finally :: IO a -> IO b -> IO a a `finally` sequel = do r <- a `catch` \e -> sequel >> throwIO (e :: SomeException) _ <- sequel return r
The idea is simple: try to perform the action. If any exceptions get thrown, call sequel and rethrow the exception. If we ever get to line 4, it's because no exceptions were thrown. Therefore, we know that sequel has not yet been called, so we call it. Said another way: there are precisely two cases:
* An exception was thrown * An exception was not thrown
A downside of this finally function (and catch, for that matter) is that it requires all of the actions to live in the IO monad, when in fact we all love to let things run in complicated monad transformer stacks. So along comes MonadCatchIO-(transformers, mtl) and gives us a new magical definition of catch:
catch :: (MonadCatchIO m, Exception e) => m a -> (e -> m a) -> m a
Using this new, extended definition of catch, we can define a finally function with the type signature
finally :: MonadCatchIO m => m a -> m b -> m a
(Note that we need to replace throwIO with liftIO . throwIO.) You can try this with writers, readers, etc, and everything works just fine. You can even use an Error/Either monad transformer, throw an exception, and the finally function will correctly run your sequel function.
However, things don't work out so well when you use a throwError. Let's see the code:
{-# LANGUAGE PackageImports #-} import Control.Monad.Trans.Error import "MonadCatchIO-transformers" Control.Monad.CatchIO (finally) import Control.Monad.IO.Class
main = runErrorT $ finally go $ liftIO $ putStrLn "sequel called"
go :: ErrorT String IO String --go = return "return" --go = error "error" --go = throwError "throwError"
Try running the code with each version of go uncommented. In the first two, "sequel called" gets printed. However, in the third, it does not. The reason is short-circuiting: if we remember from the definition of finally, there are two cases we account for. If an exception is called, catch addresses it. If not, we assume that the next line will be called. However, in the presence of short-circuiting monads like ErrorT, that line of code will never get called!
I have a recommendation of how to fix this: the MonadCatchIO typeclass should be extended to include finally, onException and everything else. We can provide default definitions which will work for most monads, and short-circuiting monads like ErrorT (and I imagine ContT as well) will need to override them.
Michael

On Thu, Oct 14, 2010 at 7:15 AM, Michael Snoyman
By the way, here is how I would implement the ErrorT MonadCatchIO instance:
instance (MonadCatchIO m, Error e) => MonadCatchIO (ErrorT e m) where m `catch` f = mapErrorT (\m' -> m' `catch` \e -> runErrorT $ f e) m block = mapErrorT block unblock = mapErrorT unblock bracket before after thing = block $ do a <- before unblock $ thing a `finally` after a bracket_ before after thing = block $ do _ <- before unblock $ thing `finally` after finally thing after = mapErrorT (`finally` runErrorT after) thing
By using "finally" inside of the definitions of bracket, bracket_ and finally, we can ensure that if there is any "special" monad underneath our ErrorT, the cleanup function will still run.
Michael
A while back I wrote a small package built on MonadCatchIO to give the equivalent of alloca and the like[1]. I haven't used it much because I couldn't convince myself that the resources would eventually be freed in a monad with non-standard control flow (such as the continuation based iteratee-0.4[2]). Antoine [1] http://hackage.haskell.org/packages/archive/MonadCatchIO-mtl-foreign/0.1/doc... [2] http://hackage.haskell.org/package/iteratee

On Thu, Oct 14, 2010 at 4:28 PM, Antoine Latter
On Thu, Oct 14, 2010 at 7:15 AM, Michael Snoyman
wrote: By the way, here is how I would implement the ErrorT MonadCatchIO instance:
instance (MonadCatchIO m, Error e) => MonadCatchIO (ErrorT e m) where m `catch` f = mapErrorT (\m' -> m' `catch` \e -> runErrorT $ f e) m block = mapErrorT block unblock = mapErrorT unblock bracket before after thing = block $ do a <- before unblock $ thing a `finally` after a bracket_ before after thing = block $ do _ <- before unblock $ thing `finally` after finally thing after = mapErrorT (`finally` runErrorT after) thing
By using "finally" inside of the definitions of bracket, bracket_ and finally, we can ensure that if there is any "special" monad underneath our ErrorT, the cleanup function will still run.
Michael
A while back I wrote a small package built on MonadCatchIO to give the equivalent of alloca and the like[1].
I haven't used it much because I couldn't convince myself that the resources would eventually be freed in a monad with non-standard control flow (such as the continuation based iteratee-0.4[2]).
I think proper exception control in monad transformer stacks is something too important to simply give up on. It seems to me that the MonadCatchIO family is broken, and that the maintainer isn't interested in fixing it. Given that, perhaps we need to design a new approach that works properly and is thoroughly tested, and perhaps deprecate the MonadCatchIO family of packages so as not to leave a stumbling block for people trying to do proper exception handling. Did you have particular reasons why you thought the resources would not be freed correctly Antoine? I'd love any insight you have on this. Michael

On Thu, Oct 14, 2010 at 10:20 AM, Michael Snoyman
Did you have particular reasons why you thought the resources would not be freed correctly Antoine? I'd love any insight you have on this.
I didn't have a good reason at the time, but your email above crystallized it for me - it's that that the MonadCatchIO package doesn't provide the things I need as primitives. Here's my implementation of allocaBytes:
allocaBytes :: (MonadCatchIO m) => Int -> (Ptr a -> m b) -> m b allocaBytes size = bracket (liftIO $ F.mallocBytes size) (liftIO . F.free)
As you've described above, if someone is using this in ErrorT (or even MaybeT) I can't promise that F.free is ever run:
bracket :: MonadCatchIO m => m a -> (a -> m b) -> (a -> m c) -> m c bracket before after thing = block (do a <- before r <- unblock (thing a) `onException` after a _void $ after a return r)
Because the 'do' runs in 'ErrorT', then nothing promises that the line "_void $ after a" is run. If there are one or two primitives we can add to MonadCatchIO to make it so bracket and finally can be implemented safely I'm all for it. Maybe the simple thing is to just lift them all into the class, but I'm hoping there is a better way to describe what we want. Antoine

On Thu, Oct 14, 2010 at 8:10 PM, Antoine Latter
On Thu, Oct 14, 2010 at 10:20 AM, Michael Snoyman
wrote: Did you have particular reasons why you thought the resources would not be freed correctly Antoine? I'd love any insight you have on this.
I didn't have a good reason at the time, but your email above crystallized it for me - it's that that the MonadCatchIO package doesn't provide the things I need as primitives. Here's my implementation of allocaBytes:
allocaBytes :: (MonadCatchIO m) => Int -> (Ptr a -> m b) -> m b allocaBytes size = bracket (liftIO $ F.mallocBytes size) (liftIO . F.free)
As you've described above, if someone is using this in ErrorT (or even MaybeT) I can't promise that F.free is ever run:
bracket :: MonadCatchIO m => m a -> (a -> m b) -> (a -> m c) -> m c bracket before after thing = block (do a <- before r <- unblock (thing a) `onException` after a _void $ after a return r)
Because the 'do' runs in 'ErrorT', then nothing promises that the line "_void $ after a" is run.
If there are one or two primitives we can add to MonadCatchIO to make it so bracket and finally can be implemented safely I'm all for it. Maybe the simple thing is to just lift them all into the class, but I'm hoping there is a better way to describe what we want.
I thought a bit about this, and I believe the only extra primitive we need is one of bracket, bracket_ or finally. I also noticed the exception-transformers package[1], which seems to be a good replacement for MonadCatchIO. I contacted the author about adding a MonadBracket typeclass, and he said he'll try to get to it. I'm planning on making that my replacement for MonadCatchIO (assuming it turns out correctly), and if so I'd recommend others do the same. Michael [1] http://hackage.haskell.org/package/exception-transformers-0.2

On Thu, Oct 14, 2010 at 1:28 PM, Michael Snoyman
I thought a bit about this, and I believe the only extra primitive we need is one of bracket, bracket_ or finally. I also noticed the exception-transformers package[1], which seems to be a good replacement for MonadCatchIO. I contacted the author about adding a MonadBracket typeclass, and he said he'll try to get to it. I'm planning on making that my replacement for MonadCatchIO (assuming it turns out correctly), and if so I'd recommend others do the same.
Ah! I didn't notice at first that the Exception type class was simply re-exported from base. At first glance, that package looked like entirely too much for what I wanted.
[1] http://hackage.haskell.org/package/exception-transformers-0.2
Antione

On Thu, Oct 14, 2010 at 11:13 PM, Antoine Latter
On Thu, Oct 14, 2010 at 1:28 PM, Michael Snoyman
wrote: I thought a bit about this, and I believe the only extra primitive we need is one of bracket, bracket_ or finally. I also noticed the exception-transformers package[1], which seems to be a good replacement for MonadCatchIO. I contacted the author about adding a MonadBracket typeclass, and he said he'll try to get to it. I'm planning on making that my replacement for MonadCatchIO (assuming it turns out correctly), and if so I'd recommend others do the same.
Ah!
I didn't notice at first that the Exception type class was simply re-exported from base. At first glance, that package looked like entirely too much for what I wanted.
For a while now I've had the idea of "inverting" monads: flipping them inside out so that we can automatically apply any of the special IO-specific functions to them. I always got caught when implementing Reader and State, but last night I had a break-through and finally got it to work. For the moment, the code is up in my neither repo on github[1], and it has a fairly complete test suite[2]. It's a pretty complicated implementation, since it needs to be generic enough to address a wide variety of monads, but I'm fairly certain that the theoretical foundations are sound. I intend to write a full blog post to explain the idea. With this, I have been able to implement catch, finally, bracket, alloca, allocaBytes and withForeignPtr simply by calling the standard IO-specific functions. I'm excited about this approach: I think it has the possibility to liberate us from a lot of tedious, error-prone code. Michael [1] http://github.com/snoyberg/neither/blob/master/Control/Monad/Invert.hs [2] http://github.com/snoyberg/neither/blob/master/runtests.hs

On Thu, 14 Oct 2010 12:01:59 +0200, Michael Snoyman
[...] which I believe is a flawed design in the MonadCatchIO-transformers package. Here are my thoughts on this and what I think needs to be done to fix it.
[...]
Try running the code with each version of go uncommented. In the first two, "sequel called" gets printed. However, in the third, it does not. The reason is short-circuiting: if we remember from the definition of finally, there are two cases we account for. If an exception is called, catch addresses it. If not, we assume that the next line will be called. However, in the presence of short-circuiting monads like ErrorT, that line of code will never get called!
Yes. That is the behaviour I would expect. There are two kinds of exceptional values in, for instance, 'ErrorT e IO a': • IO exceptions, in the "underlying monad" 'IO'; • error values of type 'e', in the monad transformer 'ErrorT e'. The MonadCatchIO instance for ErrorT deals with the first kind only. Catching IO exceptions, and cleaning up after them, is what MonadCatchIO was invented for. I feel that I should not decide for all users how these two layers of exceptions should interact; keeping the MonadCatchIO instance oblivious to the underlying monad as much as possible seems like the safest/most general thing to do. Meanwhile, I can see why you would want 'finally' to also catch the ErrorT errors, in your example, and circumvent the short-circuiting. However, I'm not convinced that this is always the right (expected, most useful, ...) behaviour. Maybe I just need more convincing :-). By the way: my apologies for not being more responsive and proactive in this matter. At the moment, I have very little time for my haskell endeavours. But more importantly, my maintainership of MonadCatchIO-transformers is mostly coincidental. (I found the MonadCatchIO-mtl code very useful, except I needed it for 'transformers' instead of 'mtl'. So, I forked it (at that time, only the cabal file needed editing), and put it on hackage.) If you feel that as maintainer I'm more of a roadblock than helping you make effective use of this library, then perhaps you should take over maintainership. Regards, Arie

On Sun, Oct 17, 2010 at 1:04 PM, Arie Peterson
On Thu, 14 Oct 2010 12:01:59 +0200, Michael Snoyman
wrote: [...] which I believe is a flawed design in the MonadCatchIO-transformers package. Here are my thoughts on this and what I think needs to be done to fix it.
[...]
Try running the code with each version of go uncommented. In the first two, "sequel called" gets printed. However, in the third, it does not. The reason is short-circuiting: if we remember from the definition of finally, there are two cases we account for. If an exception is called, catch addresses it. If not, we assume that the next line will be called. However, in the presence of short-circuiting monads like ErrorT, that line of code will never get called!
Yes. That is the behaviour I would expect.
There are two kinds of exceptional values in, for instance, 'ErrorT e IO a': • IO exceptions, in the "underlying monad" 'IO'; • error values of type 'e', in the monad transformer 'ErrorT e'. The MonadCatchIO instance for ErrorT deals with the first kind only. Catching IO exceptions, and cleaning up after them, is what MonadCatchIO was invented for. I feel that I should not decide for all users how these two layers of exceptions should interact; keeping the MonadCatchIO instance oblivious to the underlying monad as much as possible seems like the safest/most general thing to do.
Meanwhile, I can see why you would want 'finally' to also catch the ErrorT errors, in your example, and circumvent the short-circuiting. However, I'm not convinced that this is always the right (expected, most useful, ...) behaviour. Maybe I just need more convincing :-).
I think the big thing I would look for is that the second argument to 'finally' always run (barring calls to System.Exit or the universe ending or whatever). Otherwise I wouldn't expect any other interaction with the 'Left' half of ErrorT. For example I wouldn't expect the 'error' half of 'try' to be run on Left, but I would expect the cleanup tasks in 'bracket' to be executed. Otherwise the function just isn't useful. Antoine

On Sun, Oct 17, 2010 at 8:04 PM, Arie Peterson
On Thu, 14 Oct 2010 12:01:59 +0200, Michael Snoyman
wrote: [...] which I believe is a flawed design in the MonadCatchIO-transformers package. Here are my thoughts on this and what I think needs to be done to fix it.
[...]
Try running the code with each version of go uncommented. In the first two, "sequel called" gets printed. However, in the third, it does not. The reason is short-circuiting: if we remember from the definition of finally, there are two cases we account for. If an exception is called, catch addresses it. If not, we assume that the next line will be called. However, in the presence of short-circuiting monads like ErrorT, that line of code will never get called!
Yes. That is the behaviour I would expect.
There are two kinds of exceptional values in, for instance, 'ErrorT e IO a': • IO exceptions, in the "underlying monad" 'IO'; • error values of type 'e', in the monad transformer 'ErrorT e'. The MonadCatchIO instance for ErrorT deals with the first kind only. Catching IO exceptions, and cleaning up after them, is what MonadCatchIO was invented for. I feel that I should not decide for all users how these two layers of exceptions should interact; keeping the MonadCatchIO instance oblivious to the underlying monad as much as possible seems like the safest/most general thing to do.
Meanwhile, I can see why you would want 'finally' to also catch the ErrorT errors, in your example, and circumvent the short-circuiting. However, I'm not convinced that this is always the right (expected, most useful, ...) behaviour. Maybe I just need more convincing :-).
I can't think of a single use case where the current behavior is desired. On the other hand, many common cases would require the semantics I'm looking for: * My use case: returning a resource to a resource pool upon completion of an action. * Freeing allocated memory (probably better to use bracket there, but the same issue exists for that function). * Closing a file handle at the end of an action (again, a good use case for bracket). While we're on the topic, I also found a problem with the ContT instance of MonadCatchIO which resulted in double-freeing of memory[1]. I understand from Oleg's comments earlier in this thread that this is an expected behavior of the ContT monad, but I *don't* think it's an expected behavior of the bracket_ function. If there's no way to define a MonadCatchIO instance of ContT that only calls the cleanup code once, perhaps it doesn't make sense to define that instance at all.
By the way: my apologies for not being more responsive and proactive in this matter. At the moment, I have very little time for my haskell endeavours. But more importantly, my maintainership of MonadCatchIO-transformers is mostly coincidental. (I found the MonadCatchIO-mtl code very useful, except I needed it for 'transformers' instead of 'mtl'. So, I forked it (at that time, only the cabal file needed editing), and put it on hackage.)
I hadn't realized that you weren't the maintainer of MonadCatchIO-mtl (I simply never looked). I've CCed him on this issue as well.
If you feel that as maintainer I'm more of a roadblock than helping you make effective use of this library, then perhaps you should take over maintainership.
Thank you for the offer, but I don't think I'm in a position to take over maintainership of another library. However, I think that my original suggestion of moving all of the exception-handling functions into the type class itself would solve the current issue; is there a reason not to do so? I'm still not sure what to do about ContT. Michael [1] http://www.mail-archive.com/haskell-cafe@haskell.org/msg77183.html

On Oct 18, 2010, at 6:31 AM, Michael Snoyman wrote:
Thank you for the offer, but I don't think I'm in a position to take over maintainership of another library. However, I think that my original suggestion of moving all of the exception-handling functions into the type class itself would solve the current issue; is there a reason not to do so? I'm still not sure what to do about ContT.
As I posted some time ago, the scheme community has long know that genuine unwind-protect (i.e. bracket) is impossible in the presence of call/CC. I suggest that the instance simply be removed from the catchIO libraries to avoid confusion, and that the reason for its omission be documented. Cheers, Sterl.

On 14/10/2010 12:01, Michael Snoyman wrote:
I have a recommendation of how to fix this: the MonadCatchIO typeclass should be extended to include finally, onException and everything else. We can provide default definitions which will work for most monads, and short-circuiting monads like ErrorT (and I imagine ContT as well) will need to override them.
Hi Michael, As an haskell newbie, I've got some questions on this matter. Is it using ErrorT instead of extensible exeptions really necessary? I've read your comment stating that we cannot pass function arguments to Exceptions because of the Show class constraint. But is that really limiting? Wouldn't your use case (e.g. HTTP redirection in Yesod) be implementable with extensible exceptions? I would guess that the rule of thumb would be not to mix extensible exception and ErrorT whenever it is possibile. I've quickly read your post on inverting transformer stacks and, from my newbie point of view, I feel that the extra complexity isn't worth the gain. Thanks Paolo My own rule of thumb would be not using
participants (5)
-
Antoine Latter
-
Arie Peterson
-
Michael Snoyman
-
Paolo Losi
-
Sterling Clover