Stability | experimental |
---|---|
Maintainer | Bas van Dijk <v.dijk.bas@gmail.com> |
Safe Haskell | Trustworthy |
(TODO: It would be nicer if the associated data types StT
and StM
were
associated type synonyms instead. This would simplify a lot of code and could
make some definitions more efficient because there'll be no need to wrap the
monadic state in a data type. Unfortunately GHC has a bug which prevents this:
http://hackage.haskell.org/trac/ghc/ticket/5595. I will switch to associated
type synonyms when that bug is fixed.)
- class MonadTrans t => MonadTransControl t where
- type Run t = forall n b. Monad n => t n b -> n (StT t b)
- defaultLiftWith :: (Monad m, MonadTransControl n) => (forall b. n m b -> t m b) -> (forall o b. t o b -> n o b) -> (forall b. StT n b -> StT t b) -> (Run t -> m a) -> t m a
- defaultRestoreT :: (Monad m, MonadTransControl n) => (n m a -> t m a) -> (StT t a -> StT n a) -> m (StT t a) -> t m a
- class MonadBase b m => MonadBaseControl b m | m -> b where
- data StM m :: * -> *
- liftBaseWith :: (RunInBase m b -> b a) -> m a
- restoreM :: StM m a -> m a
- type RunInBase m b = forall a. m a -> b (StM m a)
- type ComposeSt t m a = StM m (StT t a)
- defaultLiftBaseWith :: (MonadTransControl t, MonadBaseControl b m) => (forall c. ComposeSt t m c -> StM (t m) c) -> (RunInBase (t m) b -> b a) -> t m a
- defaultRestoreM :: (MonadTransControl t, MonadBaseControl b m) => (StM (t m) a -> ComposeSt t m a) -> StM (t m) a -> t m a
- control :: MonadBaseControl b m => (RunInBase m b -> b (StM m a)) -> m a
- liftBaseOp :: MonadBaseControl b m => ((a -> b (StM m c)) -> b (StM m d)) -> (a -> m c) -> m d
- liftBaseOp_ :: MonadBaseControl b m => (b (StM m a) -> b (StM m c)) -> m a -> m c
- liftBaseDiscard :: MonadBaseControl b m => (b () -> b a) -> m () -> m a
MonadTransControl
class MonadTrans t => MonadTransControl t whereSource
liftWith :: Monad m => (Run t -> m a) -> t m aSource
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 aSource
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
MonadTransControl MaybeT | |
MonadTransControl ListT | |
MonadTransControl IdentityT | |
Monoid w => MonadTransControl (WriterT w) | |
Monoid w => MonadTransControl (WriterT w) | |
MonadTransControl (StateT s) | |
MonadTransControl (StateT s) | |
MonadTransControl (ReaderT r) | |
Error e => MonadTransControl (ErrorT e) | |
Monoid w => MonadTransControl (RWST r w s) | |
Monoid w => MonadTransControl (RWST r w s) |
Defaults for MonadTransControl
Following functions can be used to define MonadTransControl
instances for
newtypes.
{-# LANGUAGE GeneralizedNewtypeDeriving #-} newtype CounterT m a = CounterT {unCounterT :: StateT Int m a} deriving (Monad, MonadTrans) instance MonadTransControl CounterT where newtype StT CounterT a = StCounter {unStCounter :: StT (StateT Int) a} liftWith =defaultLiftWith
CounterT unCounterT StCounter restoreT =defaultRestoreT
CounterT unStCounter
:: (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 |
-> (forall b. StT n b -> StT t b) |
|
-> (Run t -> m a) | |
-> t m a |
Default definition for the liftWith
method.
MonadBaseControl
class MonadBase b m => MonadBaseControl b m | m -> b whereSource
liftBaseWith :: (RunInBase m b -> b a) -> m aSource
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 aSource
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
MonadBaseControl [] [] | |
MonadBaseControl IO IO | |
MonadBaseControl STM STM | |
MonadBaseControl Maybe Maybe | |
MonadBaseControl Identity Identity | |
MonadBaseControl b m => MonadBaseControl b (ListT m) | |
MonadBaseControl b m => MonadBaseControl b (MaybeT m) | |
MonadBaseControl b m => MonadBaseControl b (IdentityT m) | |
(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) | |
(Monoid w, MonadBaseControl b m) => MonadBaseControl b (WriterT w m) | |
(Error e, MonadBaseControl b m) => MonadBaseControl b (ErrorT e m) | |
MonadBaseControl b m => MonadBaseControl b (StateT s m) | |
MonadBaseControl b m => MonadBaseControl b (StateT s m) | |
MonadBaseControl b m => MonadBaseControl b (ReaderT r m) | |
(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) | |
(Monoid w, MonadBaseControl b m) => MonadBaseControl b (RWST r w s m) | |
MonadBaseControl ((->) r) ((->) r) | |
MonadBaseControl (Either e) (Either e) | |
MonadBaseControl (ST s) (ST s) | |
MonadBaseControl (ST s) (ST s) |
type RunInBase m b = forall a. m a -> b (StM m a)Source
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 newtype StM (T m) a = StMT {unStMT ::ComposeSt
T m a} liftBaseWith =defaultLiftBaseWith
StMT restoreM =defaultRestoreM
unStMT
Defining an instance for a base monad B
is equally straightforward:
instance MonadBaseControl B B where newtype StM B a = StMB {unStMB :: a} liftBaseWith f = f $ liftM StMB restoreM = return . unStMB
type ComposeSt t m a = StM m (StT t a)Source
Handy type synonym that composes the monadic states of t
and m
.
It can be used to define the StM
for new MonadBaseControl
instances.
:: (MonadTransControl t, MonadBaseControl b m) | |
=> (forall c. ComposeSt t m c -> StM (t m) c) |
|
-> (RunInBase (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 stM = \f ->liftWith
$ \run ->liftBaseWith
$ \runInBase -> f $ liftM stM . runInBase . run
:: (MonadTransControl t, MonadBaseControl b m) | |
=> (StM (t m) a -> ComposeSt t m a) |
|
-> StM (t m) a -> t m a |
Utility functions
control :: MonadBaseControl b m => (RunInBase m b -> b (StM m a)) -> m aSource
An often used composition: control f =
liftBaseWith
f >>= restoreM
liftBaseOp :: MonadBaseControl b m => ((a -> b (StM m c)) -> b (StM m d)) -> (a -> m c) -> m dSource
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 cSource
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 aSource
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