monad-control-0.2.0.1: Lift control operations, like exception catching, through monad transformers

PortabilityRequires RankNTypes
Stabilityexperimental
MaintainerBas van Dijk <v.dijk.bas@gmail.com>

Control.Monad.IO.Control

Description

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

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

Synopsis

Documentation

class MonadIO m => MonadControlIO m whereSource

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

Methods

liftControlIO :: (RunInBase m IO -> IO α) -> m αSource

liftControlIO is a version of liftControl 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 to lift control operations on IO into any monad in MonadControlIO. For example:

  foo :: IO a -> IO a
  foo' :: MonadControlIO m => m a -> m a
  foo' a = controlIO $ runInIO ->    -- runInIO :: m a -> IO (m a)
             foo $ runInIO a         -- uses foo :: IO (m a) -> IO (m a)

Instances should satisfy similar laws as the MonadIO laws:

liftControlIO . const . return = return
liftControlIO (const (m >>= f)) = liftControlIO (const m) >>= liftControlIO . const . f

Additionally instances should satisfy:

controlIO $ \runInIO -> runInIO m = m

controlIO :: MonadControlIO m => (RunInBase m IO -> IO (m α)) -> m αSource

An often used composition: controlIO = join . liftControlIO

liftIOOp :: MonadControlIO m => ((α -> IO (m β)) -> IO (m γ)) -> (α -> m β) -> m γSource

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

liftIOOp f = \g -> controlIO $ runInIO -> f $ runInIO . g

liftIOOp_ :: MonadControlIO m => (IO (m α) -> IO (m β)) -> m α -> m βSource

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

liftIOOp_ f = \m -> controlIO $ runInIO -> f $ runInIO m