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
{-# LANGUAGE PackageImports #-} import qualified "MonadCatchIO-transformers" Control.Monad.CatchIO as C import Control.Monad.IO.Class import Control.Monad.Trans.Cont f :: ContT (Either String String) IO String f = do C.bracket_ (say "acquired") (say "released") (say "executed") () <- error "error" return "success" where say = liftIO . putStrLn main :: IO () main = flip runContT (return . Right) f >>= print
{-# LANGUAGE PackageImports #-} import qualified Control.Exception as E cthrow :: E.SomeException -> ContT a cthrow = cliftIO . E.throwIO cliftIO :: IO a -> ContT a cliftIO m = (m >>=) ccatch :: ContT a -> (E.SomeException -> ContT a) -> ContT a ccatch m f c = m c `E.catch` flip f c type ContT a = (a -> IO Bool) -> IO Bool creturn :: a -> ContT a creturn a = ($ a) cbind :: ContT a -> (a -> ContT b) -> ContT b cbind m k c = m $ flip k c cbind' :: ContT a -> ContT b -> ContT b cbind' m k c = m $ const $ k c conException :: ContT a -> ContT b -> ContT a conException a onEx = a `ccatch` (\e -> onEx `cbind'` cthrow e) cbracket_ :: ContT a -> ContT b -> ContT c -> ContT c cbracket_ before after thing = before `cbind'` thing `conException` after `cbind` \r -> after `cbind'` creturn r f :: ContT String f = cbracket_ (say "acquired") (say "released") (say "executed") `cbind'` error "error" `cbind'` creturn "success" where say = cliftIO . putStrLn main :: IO () main = f (return . null) >>= print
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe