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
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to