How to reliably open and close resources in MonadIO in the presence of exceptions?

import Control.Monad.Trans ( MonadIO, liftIO ) import Control.Exception ( throwIO, ArithException(DivideByZero), onException ) import Foreign.Marshal.Alloc ( malloc, free ) import Foreign.Storable ( poke, peek )
Suppose we define a function which receives a computation in an arbitrary monad that is capable of lifting IO actions and returns a computation in the same monad:
foo :: MonadIO m => m () -> m ()
In 'foo', I would like to open some resource (in this case: allocate memory) and after performing some lifted IO actions and some arbitrary computations in 'm' I want to close the resource (in this case: freeing the allocated memory). Of course the resource should also be closed when an exception is thrown in some lifted IO computation. If I was performing a computation directly in IO I could use: alloca :: Storable a => (Ptr a -> IO b) -> IO b which allocates the memory, performs some action on it and frees the memory after the action terminates (either normally or via an exception). Unfortunately the type of 'alloca' does not allow it to be used in our arbitrary monad 'm'. So it looks like I'm forced to manually allocate the memory using 'malloc' and finally free it using 'free'. To handle exceptions in lifted IO computations I have to put a (`onException` free ptr) around every lifted IO computation: For example:
foo action = do ptr <- liftIO malloc liftIO $ putStrLn "aaa" `onException` free ptr liftIO $ poke ptr (3 :: Int) `onException` free ptr liftIO $ putStrLn "bbb" `onException` free ptr action x <- liftIO $ peek ptr `onException` free ptr liftIO $ print x `onException` free ptr liftIO $ putStrLn "ccc" `onException` free ptr liftIO $ free ptr
I find this rather ugly. What's worse is that exceptions, thrown in lifted IO computations in 'action' can't be handled! For example, the following won't free the memory:
bar :: MonadIO m => m () bar = foo action where action = liftIO $ throwIO DivideByZero
So my question is: How can I reliably open and close resources in MonadIO? And as a supplementary question: Is it possible to define a generalized alloca: genAlloca :: (MonadIO m, Storable a) => (Ptr a -> m b) -> m b Thanks, Bas

On Fri, Oct 16, 2009 at 11:15 AM, Bas van Dijk
import Control.Monad.Trans ( MonadIO, liftIO ) import Control.Exception ( throwIO, ArithException(DivideByZero), onException ) import Foreign.Marshal.Alloc ( malloc, free ) import Foreign.Storable ( poke, peek )
Suppose we define a function which receives a computation in an arbitrary monad that is capable of lifting IO actions and returns a computation in the same monad:
foo :: MonadIO m => m () -> m ()
In 'foo', I would like to open some resource (in this case: allocate memory) and after performing some lifted IO actions and some arbitrary computations in 'm' I want to close the resource (in this case: freeing the allocated memory). Of course the resource should also be closed when an exception is thrown in some lifted IO computation.
If I was performing a computation directly in IO I could use:
alloca :: Storable a => (Ptr a -> IO b) -> IO b
which allocates the memory, performs some action on it and frees the memory after the action terminates (either normally or via an exception).
Unfortunately the type of 'alloca' does not allow it to be used in our arbitrary monad 'm'.
So it looks like I'm forced to manually allocate the memory using 'malloc' and finally free it using 'free'. To handle exceptions in lifted IO computations I have to put a (`onException` free ptr) around every lifted IO computation:
For example:
foo action = do ptr <- liftIO malloc liftIO $ putStrLn "aaa" `onException` free ptr liftIO $ poke ptr (3 :: Int) `onException` free ptr liftIO $ putStrLn "bbb" `onException` free ptr action x <- liftIO $ peek ptr `onException` free ptr liftIO $ print x `onException` free ptr liftIO $ putStrLn "ccc" `onException` free ptr liftIO $ free ptr
I find this rather ugly. What's worse is that exceptions, thrown in lifted IO computations in 'action' can't be handled! For example, the following won't free the memory:
bar :: MonadIO m => m () bar = foo action where action = liftIO $ throwIO DivideByZero
So my question is: How can I reliably open and close resources in MonadIO?
And as a supplementary question: Is it possible to define a generalized alloca:
genAlloca :: (MonadIO m, Storable a) => (Ptr a -> m b) -> m b
Thanks,
Bas
I could of course write a genAlloca if the MonadIO class was extended with a bracket method: ---------------------------------------------------------------------------------------------------- import qualified Control.Exception as E import Control.Exception ( throwIO, ArithException(DivideByZero) ) import Foreign.Marshal.Alloc ( malloc, free ) import Foreign.Ptr ( Ptr ) import Foreign.Storable ( Storable, poke, peek ) class Monad m => MonadIO m where liftIO :: IO a -> m a bracket :: IO a -> (a -> IO b) -> (a -> m c) -> m c instance MonadIO IO where liftIO = id bracket = E.bracket genAlloca :: (MonadIO m, Storable a) => (Ptr a -> m b) -> m b genAlloca = bracket malloc free foo :: MonadIO m => m () -> m () foo action = genAlloca $ \ptr -> do liftIO $ putStrLn "aaa" liftIO $ poke ptr (3 :: Int) liftIO $ putStrLn "bbb" action x <- liftIO $ peek ptr liftIO $ print x liftIO $ putStrLn "ccc" bar :: MonadIO m => m () bar = foo action where action = liftIO $ throwIO DivideByZero ---------------------------------------------------------------------------------------------------- Besides extending MonadIO with bracket, maybe it's also useful to extend it with: catch :: Exception e => m a -> (e -> m a) -> m a regards, Bas

-----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Bas van Dijk
I could of course write a genAlloca if the MonadIO class was extended with a bracket method:
Besides extending MonadIO with bracket, maybe it's also useful to extend it with:
catch :: Exception e => m a -> (e -> m a) -> m a
You might want this library: http://hackage.haskell.org/packages/archive/MonadCatchIO-transformers/0. 0.1.0/doc/html/Control-Monad-CatchIO.html There's also an mtl version; not sure which is to be prefered. Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

On Fri, Oct 16, 2009 at 1:16 PM, Bayley, Alistair
You might want this library: http://hackage.haskell.org/packages/archive/MonadCatchIO-transformers/0. 0.1.0/doc/html/Control-Monad-CatchIO.html
Thanks, this is exactly what I need! regards, Bas
participants (2)
-
Bas van Dijk
-
Bayley, Alistair