[Haskell-cafe] How to reliably open and close resources in MonadIO in the presence of exceptions?

Bas van Dijk v.dijk.bas at gmail.com
Fri Oct 16 05:15:12 EDT 2009


> 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


More information about the Haskell-Cafe mailing list