monad-peel-0.3: Lift control operations like exception catching through monad transformers
Copyright© Anders Kaseorg 2010
LicenseBSD-style
MaintainerAnders Kaseorg <andersk@mit.edu>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.IO.Peel

Description

This module defines the class MonadPeelIO of IO-based monads into which control operations on IO (such as exception catching; see Control.Exception.Peel) can be lifted.

liftIOOp and liftIOOp_ enable convenient lifting of two common special cases of control operation types.

Synopsis

Documentation

class MonadIO m => MonadPeelIO m where Source #

MonadPeelIO is the class of IO-based monads supporting an extra operation peelIO, enabling control operations on IO to be lifted into the monad.

Methods

peelIO :: m (m a -> IO (m a)) Source #

peelIO is a version of peel that operates through an arbitrary stack of monad transformers directly to an inner IO (analagously to how liftIO is a version of lift). So it can be used with liftIO to lift control operations on IO into any monad in MonadPeelIO. For example:

   foo :: IO a -> IO a
   foo' :: MonadPeelIO m => m a -> m a
   foo' a = do
     k <- peelIO  -- k :: m a -> IO (m a)
     join $ liftIO $ foo (k a)  -- uses foo :: IO (m a) -> IO (m a)

Note that the "obvious" term of this type (peelIO = return return) does not work correctly. Instances of MonadPeelIO should be constructed via MonadTransPeel, using peelIO = liftPeel peelIO.

Instances

Instances details
MonadPeelIO IO Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: IO (IO a -> IO (IO a)) Source #

MonadPeelIO m => MonadPeelIO (MaybeT m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: MaybeT m (MaybeT m a -> IO (MaybeT m a)) Source #

MonadPeelIO m => MonadPeelIO (ExceptT e m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: ExceptT e m (ExceptT e m a -> IO (ExceptT e m a)) Source #

MonadPeelIO m => MonadPeelIO (IdentityT m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: IdentityT m (IdentityT m a -> IO (IdentityT m a)) Source #

MonadPeelIO m => MonadPeelIO (ReaderT r m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: ReaderT r m (ReaderT r m a -> IO (ReaderT r m a)) Source #

MonadPeelIO m => MonadPeelIO (StateT s m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: StateT s m (StateT s m a -> IO (StateT s m a)) Source #

MonadPeelIO m => MonadPeelIO (StateT s m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: StateT s m (StateT s m a -> IO (StateT s m a)) Source #

(Monoid w, MonadPeelIO m) => MonadPeelIO (WriterT w m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: WriterT w m (WriterT w m a -> IO (WriterT w m a)) Source #

(Monoid w, MonadPeelIO m) => MonadPeelIO (WriterT w m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: WriterT w m (WriterT w m a -> IO (WriterT w m a)) Source #

(Monoid w, MonadPeelIO m) => MonadPeelIO (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: RWST r w s m (RWST r w s m a -> IO (RWST r w s m a)) Source #

(Monoid w, MonadPeelIO m) => MonadPeelIO (RWST r w s m) Source # 
Instance details

Defined in Control.Monad.IO.Peel

Methods

peelIO :: RWST r w s m (RWST r w s m a -> IO (RWST r w s m a)) Source #

liftIOOp :: MonadPeelIO m => ((a -> IO (m b)) -> IO (m c)) -> (a -> m b) -> m c Source #

liftIOOp is a particular application of peelIO that allows lifting control operations of type (a -> IO b) -> IO b (e.g. alloca, withMVar v) to MonadPeelIO m => (a -> m b) -> m b.

   liftIOOp f g = do
     k <- peelIO
     join $ liftIO $ f (k . g)

liftIOOp_ :: MonadPeelIO m => (IO (m a) -> IO (m b)) -> m a -> m b Source #

liftIOOp_ is a particular application of peelIO that allows lifting control operations of type IO a -> IO a (e.g. block) to MonadPeelIO m => m a -> m a.

   liftIOOp_ f m = do
     k <- peelIO
     join $ liftIO $ f (k m)