[Haskell-cafe] MonadCatchIO-transformers and ContT

2010-06-21 Thread Michael Snoyman
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


Re: [Haskell-cafe] MonadCatchIO-transformers and ContT

2010-06-21 Thread Neil Brown

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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
   


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MonadCatchIO-transformers and ContT

2010-06-21 Thread Michael Snoyman
I think you're correct, but I still don't know how to solve it. Any thoughts
on that front? I'm at the point of just attaching a finalizer to the
statement, or sticking in an IORef to ensure it doesn't get
double-finalized.

On Mon, Jun 21, 2010 at 2:04 PM, Neil Brown nc...@kent.ac.uk wrote:

  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 
 listhaskell-c...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MonadCatchIO-transformers and ContT

2010-06-21 Thread David Menendez
On Mon, Jun 21, 2010 at 7:04 AM, Neil Brown nc...@kent.ac.uk wrote:

 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?

Sounds possible to me.

ContT does not play well with control operations from other monads.
Most people would expect, e.g., lift m `catch` lift . f = lift (m
`catch` f), but ContT does not have such an operation.

If you really want explicit continuations and exceptions, you need a
monad written specifically for that.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe