[Haskell-cafe] Generalized monadic exception handling with monad-peel

Anders Kaseorg andersk at MIT.EDU
Wed Nov 3 05:59:03 EDT 2010


I just released the monad-peel library to Hackage.
  http://hackage.haskell.org/package/monad-peel

MonadPeelIO is a simple class that allows lifting monadic control 
operations, such as those in Control.Exception and Foreign.Marshal.Alloc, 
through layers of monad transformers.  It comes with instances for every 
transformer in the transformers package except ContT, and uses no Haskell 
extensions.

class MonadTrans t => MonadTransPeel t where
  peel :: (Monad m, Monad n, Monad o) => t n (t m a -> m (t o a))
class MonadIO m => MonadPeelIO m where
  peelIO :: m (m a -> IO (m a))

I’ve included a wrapped version of Control.Exception with types 
generalized to all monads in MonadPeelIO, for example:

catch :: (MonadPeelIO m, Exception e) => m a -> (e -> m a) -> m a
catch a handler = do
  k <- peelIO
  join $ liftIO $ Control.Exception.catch (k a) (\e -> k $ handler e)

I’m hoping this package can become a suitable replacement for 
MonadCatchIO, whose implementation of ‘finally’ was recently shown to be 
broken with certain monads (see “MonadCatchIO, finally and the error 
monad” on this list).

The home page has links to a Git repository and has references to older 
mailing list threads providing some background:
  http://andersk.mit.edu/haskell/monad-peel/
Thanks to everyone who contributed to those threads and helped shape the 
ideas that led to this package (and if it turns out more ideas are needed, 
thanks for those too!).

Anders


More information about the Haskell-Cafe mailing list