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

CopyrightBas van Dijk Anders Kaseorg
LicenseBSD-style
MaintainerBas van Dijk <v.dijk.bas@gmail.com>
Stabilityexperimental
Safe HaskellSafe
LanguageHaskell98

Control.Monad.Trans.Control

Contents

Description

 
Synopsis

MonadTransControl

class MonadTrans t => MonadTransControl t where #

Associated Types

type StT t a :: * #

Monadic state of t.

Methods

liftWith :: Monad m => (Run t -> m a) -> t m a #

liftWith is similar to lift in that it lifts a computation from the argument monad to the constructed monad.

Instances should satisfy similar laws as the MonadTrans laws:

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

The difference with lift is that before lifting the m computation liftWith captures the state of t. It then provides the m computation with a Run function that allows running t n computations in n (for all n) on the captured state.

restoreT :: Monad m => m (StT t a) -> t m a #

Construct a t computation from the monadic state of t that is returned from a Run function.

Instances should satisfy:

liftWith (\run -> run t) >>= restoreT . return = t
Instances
MonadTransControl MaybeT # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT MaybeT a :: Type #

Methods

liftWith :: Monad m => (Run MaybeT -> m a) -> MaybeT m a #

restoreT :: Monad m => m (StT MaybeT a) -> MaybeT m a #

MonadTransControl ListT # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT ListT a :: Type #

Methods

liftWith :: Monad m => (Run ListT -> m a) -> ListT m a #

restoreT :: Monad m => m (StT ListT a) -> ListT m a #

Monoid w => MonadTransControl (WriterT w) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (WriterT w) a :: Type #

Methods

liftWith :: Monad m => (Run (WriterT w) -> m a) -> WriterT w m a #

restoreT :: Monad m => m (StT (WriterT w) a) -> WriterT w m a #

Monoid w => MonadTransControl (WriterT w) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (WriterT w) a :: Type #

Methods

liftWith :: Monad m => (Run (WriterT w) -> m a) -> WriterT w m a #

restoreT :: Monad m => m (StT (WriterT w) a) -> WriterT w m a #

MonadTransControl (StateT s) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (StateT s) a :: Type #

Methods

liftWith :: Monad m => (Run (StateT s) -> m a) -> StateT s m a #

restoreT :: Monad m => m (StT (StateT s) a) -> StateT s m a #

MonadTransControl (StateT s) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (StateT s) a :: Type #

Methods

liftWith :: Monad m => (Run (StateT s) -> m a) -> StateT s m a #

restoreT :: Monad m => m (StT (StateT s) a) -> StateT s m a #

MonadTransControl (ReaderT r) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (ReaderT r) a :: Type #

Methods

liftWith :: Monad m => (Run (ReaderT r) -> m a) -> ReaderT r m a #

restoreT :: Monad m => m (StT (ReaderT r) a) -> ReaderT r m a #

MonadTransControl (IdentityT :: (Type -> Type) -> Type -> Type) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT IdentityT a :: Type #

Methods

liftWith :: Monad m => (Run IdentityT -> m a) -> IdentityT m a #

restoreT :: Monad m => m (StT IdentityT a) -> IdentityT m a #

MonadTransControl (ExceptT e) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (ExceptT e) a :: Type #

Methods

liftWith :: Monad m => (Run (ExceptT e) -> m a) -> ExceptT e m a #

restoreT :: Monad m => m (StT (ExceptT e) a) -> ExceptT e m a #

Error e => MonadTransControl (ErrorT e) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (ErrorT e) a :: Type #

Methods

liftWith :: Monad m => (Run (ErrorT e) -> m a) -> ErrorT e m a #

restoreT :: Monad m => m (StT (ErrorT e) a) -> ErrorT e m a #

Monoid w => MonadTransControl (RWST r w s) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (RWST r w s) a :: Type #

Methods

liftWith :: Monad m => (Run (RWST r w s) -> m a) -> RWST r w s m a #

restoreT :: Monad m => m (StT (RWST r w s) a) -> RWST r w s m a #

Monoid w => MonadTransControl (RWST r w s) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StT (RWST r w s) a :: Type #

Methods

liftWith :: Monad m => (Run (RWST r w s) -> m a) -> RWST r w s m a #

restoreT :: Monad m => m (StT (RWST r w s) a) -> RWST r w s m a #

type Run t = forall n b. Monad n => t n b -> n (StT t b) #

A function that runs a transformed monad t n on the monadic state that was captured by liftWith

A Run t function yields a computation in n that returns the monadic state of t. This state can later be used to restore a t computation using restoreT.

Defaults for MonadTransControl

The following functions can be used to define a MonadTransControl instance for a monad transformer which simply wraps another monad transformer which already has a MonadTransControl instance. For example:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

newtype CounterT m a = CounterT {unCounterT :: StateT Int m a}
  deriving (Monad, MonadTrans)

instance MonadTransControl CounterT where
    type StT CounterT a = StT (StateT Int) a
    liftWith = defaultLiftWith CounterT unCounterT
    restoreT = defaultRestoreT CounterT

type RunDefault t t' = forall n b. Monad n => t n b -> n (StT t' b) #

A function like Run that runs a monad transformer t which wraps the monad transformer t'. This is used in defaultLiftWith.

defaultLiftWith #

Arguments

:: (Monad m, MonadTransControl n) 
=> (forall b. n m b -> t m b)

Monad constructor

-> (forall o b. t o b -> n o b)

Monad deconstructor

-> (RunDefault t n -> m a) 
-> t m a 

Default definition for the liftWith method.

defaultRestoreT #

Arguments

:: (Monad m, MonadTransControl n) 
=> (n m a -> t m a)

Monad constructor

-> m (StT n a) 
-> t m a 

Default definition for the restoreT method.

MonadBaseControl

class MonadBase b m => MonadBaseControl b m | m -> b where #

Associated Types

type StM m a :: * #

Monadic state of m.

Methods

liftBaseWith :: (RunInBase m b -> b a) -> m a #

liftBaseWith is similar to liftIO and liftBase in that it lifts a base computation to the constructed monad.

Instances should satisfy similar laws as the MonadIO and MonadBase laws:

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

The difference with liftBase is that before lifting the base computation liftBaseWith captures the state of m. It then provides the base computation with a RunInBase function that allows running m computations in the base monad on the captured state.

restoreM :: StM m a -> m a #

Construct a m computation from the monadic state of m that is returned from a RunInBase function.

Instances should satisfy:

liftBaseWith (\runInBase -> runInBase m) >>= restoreM = m
Instances
MonadBaseControl [] [] # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM [] a :: Type #

Methods

liftBaseWith :: (RunInBase [] [] -> [a]) -> [a] #

restoreM :: StM [] a -> [a] #

MonadBaseControl Maybe Maybe # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Maybe a :: Type #

MonadBaseControl IO IO # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM IO a :: Type #

Methods

liftBaseWith :: (RunInBase IO IO -> IO a) -> IO a #

restoreM :: StM IO a -> IO a #

MonadBaseControl Identity Identity # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM Identity a :: Type #

MonadBaseControl STM STM # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM STM a :: Type #

Methods

liftBaseWith :: (RunInBase STM STM -> STM a) -> STM a #

restoreM :: StM STM a -> STM a #

MonadBaseControl b m => MonadBaseControl b (ListT m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ListT m) a :: Type #

Methods

liftBaseWith :: (RunInBase (ListT m) b -> b a) -> ListT m a #

restoreM :: StM (ListT m) a -> ListT m a #

MonadBaseControl b m => MonadBaseControl b (MaybeT m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (MaybeT m) a :: Type #

Methods

liftBaseWith :: (RunInBase (MaybeT m) b -> b a) -> MaybeT m a #

restoreM :: StM (MaybeT m) a -> MaybeT m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (WriterT w m) a :: Type #

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (WriterT w m) a :: Type #

Methods

liftBaseWith :: (RunInBase (WriterT w m) b -> b a) -> WriterT w m a #

restoreM :: StM (WriterT w m) a -> WriterT w m a #

(Error e, MonadBaseControl b m) => MonadBaseControl b (ErrorT e m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ErrorT e m) a :: Type #

Methods

liftBaseWith :: (RunInBase (ErrorT e m) b -> b a) -> ErrorT e m a #

restoreM :: StM (ErrorT e m) a -> ErrorT e m a #

MonadBaseControl b m => MonadBaseControl b (ExceptT e m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ExceptT e m) a :: Type #

Methods

liftBaseWith :: (RunInBase (ExceptT e m) b -> b a) -> ExceptT e m a #

restoreM :: StM (ExceptT e m) a -> ExceptT e m a #

MonadBaseControl b m => MonadBaseControl b (StateT s m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (StateT s m) a :: Type #

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

MonadBaseControl b m => MonadBaseControl b (StateT s m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (StateT s m) a :: Type #

Methods

liftBaseWith :: (RunInBase (StateT s m) b -> b a) -> StateT s m a #

restoreM :: StM (StateT s m) a -> StateT s m a #

MonadBaseControl b m => MonadBaseControl b (ReaderT r m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ReaderT r m) a :: Type #

Methods

liftBaseWith :: (RunInBase (ReaderT r m) b -> b a) -> ReaderT r m a #

restoreM :: StM (ReaderT r m) a -> ReaderT r m a #

MonadBaseControl b m => MonadBaseControl b (IdentityT m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (IdentityT m) a :: Type #

Methods

liftBaseWith :: (RunInBase (IdentityT m) b -> b a) -> IdentityT m a #

restoreM :: StM (IdentityT m) a -> IdentityT m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (RWST r w s m) a :: Type #

Methods

liftBaseWith :: (RunInBase (RWST r w s m) b -> b a) -> RWST r w s m a #

restoreM :: StM (RWST r w s m) a -> RWST r w s m a #

(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (RWST r w s m) a :: Type #

Methods

liftBaseWith :: (RunInBase (RWST r w s m) b -> b a) -> RWST r w s m a #

restoreM :: StM (RWST r w s m) a -> RWST r w s m a #

MonadBaseControl (Either e) (Either e) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (Either e) a :: Type #

Methods

liftBaseWith :: (RunInBase (Either e) (Either e) -> Either e a) -> Either e a #

restoreM :: StM (Either e) a -> Either e a #

MonadBaseControl (ST s) (ST s) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ST s) a :: Type #

Methods

liftBaseWith :: (RunInBase (ST s) (ST s) -> ST s a) -> ST s a #

restoreM :: StM (ST s) a -> ST s a #

MonadBaseControl (ST s) (ST s) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (ST s) a :: Type #

Methods

liftBaseWith :: (RunInBase (ST s) (ST s) -> ST s a) -> ST s a #

restoreM :: StM (ST s) a -> ST s a #

MonadBaseControl ((->) r :: Type -> Type) ((->) r :: Type -> Type) # 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM ((->) r) a :: Type #

Methods

liftBaseWith :: (RunInBase ((->) r) ((->) r) -> r -> a) -> r -> a #

restoreM :: StM ((->) r) a -> r -> a #

type RunInBase m b = forall a. m a -> b (StM m a) #

A function that runs a m computation on the monadic state that was captured by liftBaseWith

A RunInBase m function yields a computation in the base monad of m that returns the monadic state of m. This state can later be used to restore the m computation using restoreM.

Defaults for MonadBaseControl

Note that by using the following default definitions it's easy to make a monad transformer T an instance of MonadBaseControl:

instance MonadBaseControl b m => MonadBaseControl b (T m) where
    type StM (T m) a = ComposeSt T m a
    liftBaseWith     = defaultLiftBaseWith
    restoreM         = defaultRestoreM

Defining an instance for a base monad B is equally straightforward:

instance MonadBaseControl B B where
    type StM B a   = a
    liftBaseWith f = f id
    restoreM       = return

type ComposeSt t m a = StM m (StT t a) #

Handy type synonym that composes the monadic states of t and m.

It can be used to define the StM for new MonadBaseControl instances.

type RunInBaseDefault t m b = forall a. t m a -> b (ComposeSt t m a) #

A function like RunInBase that runs a monad transformer t in its base monad b. It is used in defaultLiftBaseWith.

defaultLiftBaseWith :: (MonadTransControl t, MonadBaseControl b m) => (RunInBaseDefault t m b -> b a) -> t m a #

Default defintion for the liftBaseWith method.

Note that it composes a liftWith of t with a liftBaseWith of m to give a liftBaseWith of t m:

defaultLiftBaseWith = \f -> liftWith $ \run ->
                              liftBaseWith $ \runInBase ->
                                f $ runInBase . run

defaultRestoreM :: (MonadTransControl t, MonadBaseControl b m) => ComposeSt t m a -> t m a #

Default definition for the restoreM method.

Note that: defaultRestoreM = restoreT . restoreM

Utility functions

control :: MonadBaseControl b m => (RunInBase m b -> b (StM m a)) -> m a #

An often used composition: control f = liftBaseWith f >>= restoreM

embed :: MonadBaseControl b m => (a -> m c) -> m (a -> b (StM m c)) #

Embed a transformer function as an function in the base monad returning a mutated transformer state.

embed_ :: MonadBaseControl b m => (a -> m ()) -> m (a -> b ()) #

Performs the same function as embed, but discards transformer state from the embedded function.

liftBaseOp :: MonadBaseControl b m => ((a -> b (StM m c)) -> b (StM m d)) -> (a -> m c) -> m d #

liftBaseOp is a particular application of liftBaseWith that allows lifting control operations of type:

((a -> b c) -> b c) to: (MonadBaseControl b m => (a -> m c) -> m c).

For example:

liftBaseOp alloca :: MonadBaseControl IO m => (Ptr a -> m c) -> m c

liftBaseOp_ :: MonadBaseControl b m => (b (StM m a) -> b (StM m c)) -> m a -> m c #

liftBaseOp_ is a particular application of liftBaseWith that allows lifting control operations of type:

(b a -> b a) to: (MonadBaseControl b m => m a -> m a).

For example:

liftBaseOp_ mask_ :: MonadBaseControl IO m => m a -> m a

liftBaseDiscard :: MonadBaseControl b m => (b () -> b a) -> m () -> m a #

liftBaseDiscard is a particular application of liftBaseWith that allows lifting control operations of type:

(b () -> b a) to: (MonadBaseControl b m => m () -> m a).

Note that, while the argument computation m () has access to the captured state, all its side-effects in m are discarded. It is run only for its side-effects in the base monad b.

For example:

liftBaseDiscard forkIO :: MonadBaseControl IO m => m () -> m ThreadId

liftBaseOpDiscard :: MonadBaseControl b m => ((a -> b ()) -> b c) -> (a -> m ()) -> m c #

liftBaseOpDiscard is a particular application of liftBaseWith that allows lifting control operations of type:

((a -> b ()) -> b c) to: (MonadBaseControl b m => (a -> m ()) -> m c).

Note that, while the argument computation m () has access to the captured state, all its side-effects in m are discarded. It is run only for its side-effects in the base monad b.

For example:

liftBaseDiscard (runServer addr port) :: MonadBaseControl IO m => m () -> m ()