[EMAIL PROTECTED] writes:

> The implementation is quite trivial.
> 
> > class MonadIO m => CaughtMonadIO m where
> >     gcatch :: m a -> (Exception -> m a) -> m a
> >
> > instance CaughtMonadIO IO where
> >     gcatch = Control.Exception.catch
> 
> > instance (CaughtMonadIO m, Error e) => CaughtMonadIO (ErrorT e m)
where
> >     gcatch m f = mapErrorT (\m -> gcatch m (\e -> runErrorT $ f e))
m

Since the monad transformers in MTL all promote MonadError, you can also
use throwError and catchError with instances of MonadIO. Currently, the
error type associated with IO is IOError, not Exception, but it should
be possible to work around that with a wrapper:

    newtype IO' a = IO' { unIO' :: IO a } deriving (Monad, Functor)
    
    instance MonadIO IO' where
        liftIO = IO'
    
    instance MonadError Exception IO' where
        throwError = IO' . throwIO
        m `catchError` h = IO' $ catch (unIO' m) (unIO' . h)
-- 
David Menendez <[EMAIL PROTECTED]> | "In this house, we obey the laws
<http://www.eyrie.org/~zednenem>      |        of thermodynamics!"
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to