[Haskell-cafe] MonadCatchIO-transformers and ContT

Neil Brown nccb2 at kent.ac.uk
Mon Jun 21 07:04:28 EDT 2010


Hi,

Here's my guess.  Take a look at this version, and try running it:

===
{-# LANGUAGE PackageImports #-}

import qualified "MonadCatchIO-transformers" Control.Monad.CatchIO as C
import Control.Monad.IO.Class
import Control.Monad.Trans.Cont


bracket_' :: C.MonadCatchIO m
          => m a  -- ^ computation to run first (\"acquire resource\")
          -> m b  -- ^ computation to run last when successful 
(\"release resource\")
          -> m b  -- ^ computation to run last when an exception occurs
          -> m c  -- ^ computation to run in-between
          -> m c  -- returns the value from the in-between computation
bracket_' before after afterEx thing = C.block $ do
   _ <- before
   r <- C.unblock thing `C.onException` afterEx
   _ <- after
   return r


f :: ContT (Either String String) IO String
f = do
     bracket_' (say "acquired") (say "released-successful") (say 
"released-exception") (say "executed")
     say "Hello!"
     () <- error "error"
     return "success"
   where
     say = liftIO . putStrLn

main :: IO ()
main = flip runContT (return . Right) f >>= print
===

I get:

acquired
executed
released-successful
Hello!
released-exception
Tmp.hs: error

So the exception handler is running after the code that follows the 
whole bracket_' call -- and after the bracket_' call has completed 
succesfully!

Here's my speculation, based on glancing at the libraries involved: I 
believe the reason for this may be the MonadCatchIO instance for ContT:

===
instance MonadCatchIO m => MonadCatchIO (ContT r m) where
   m `catch` f = ContT $ \c -> runContT m c `catch` \e -> runContT (f e) c
===

To my eye, that code takes the continuation to run after the block, c 
(which in your case involves the after-action from bracket_, and then 
the error), and runs that inside the catch block.  This causes a 
successful completion of bracket_ (first release), followed by the 
error, which triggers the catch block which then runs the final actions 
(second release) and rethrows the error.  Does that sound possible to 
anyone else?

Thanks,

Neil.

On 21/06/10 09:39, Michael Snoyman wrote:
> Hi cafe,
>
> I ran into a segfault while working on some database code. I 
> eventually traced it back to a double-finalizing of a statement (read: 
> freeing memory twice), which ultimately led back to switching my code 
> to use the ContT monad transformer. I was able to isolate this down to 
> a minimal test case (catch.hs); when run, it prints the line 
> "released" twice.
>
> In an attempt to understand what's going on, I rewrote the code to 
> avoid the libraries entirely (catch-simplified.hs); it didn't give me 
> any insight into the problem, but maybe it will help someone else.
>
> If someone sees an obvious mistake I'm making in my usage of the 
> bracket_ function, please let me know. Otherwise, I'd really like to 
> get a fix for this so I can use this library.
>
> Thanks,
> Michael
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>    

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20100621/5e721687/attachment.html


More information about the Haskell-Cafe mailing list