Copyright | Bas van Dijk, Anders Kaseorg |
---|---|
License | BSD-style |
Maintainer | Bas van Dijk <v.dijk.bas@gmail.com> |
Stability | experimental |
Safe Haskell | Safe |
Language | Haskell98 |
- class MonadTrans t => MonadTransControl t where
- type Run t = forall n b. Monad n => t n b -> n (StT t b)
- type RunDefault t 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) -> (RunDefault t n -> m a) -> t m a
- defaultRestoreT :: (Monad m, MonadTransControl n) => (n m a -> t m a) -> m (StT n a) -> t m a
- class MonadBase b m => MonadBaseControl b m | m -> b where
- type StM m a :: *
- 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)
- type RunInBaseDefault t m b = forall a. t m a -> b (ComposeSt t m a)
- defaultLiftBaseWith :: (MonadTransControl t, MonadBaseControl b m) => (RunInBaseDefault t m b -> b a) -> t m a
- defaultRestoreM :: (MonadTransControl t, MonadBaseControl b m) => ComposeSt t m a -> t m a
- control :: MonadBaseControl b m => (RunInBase m b -> b (StM m a)) -> m a
- embed :: MonadBaseControl b m => (a -> m c) -> m (a -> b (StM m c))
- embed_ :: MonadBaseControl b m => (a -> m ()) -> m (a -> b ())
- 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
- liftBaseOpDiscard :: MonadBaseControl b m => ((a -> b ()) -> b c) -> (a -> m ()) -> m c
MonadTransControl
class MonadTrans t => MonadTransControl t where Source
liftWith :: Monad m => (Run t -> m a) -> t m a Source
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 Source
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) | |
Error e => MonadTransControl (ErrorT e) | |
MonadTransControl (ExceptT e) | |
MonadTransControl (StateT s) | |
MonadTransControl (StateT s) | |
MonadTransControl (ReaderT r) | |
Monoid w => MonadTransControl (RWST r w s) | |
Monoid w => MonadTransControl (RWST r w s) |
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) Source
A function like Run
that runs a monad transformer t
which wraps the
monad transformer t'
. This is used in defaultLiftWith
.
:: (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.
:: (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 Source
liftBaseWith :: (RunInBase m b -> b a) -> m a Source
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 Source
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
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 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 = fid
restoreM =return
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.
type RunInBaseDefault t m b = forall a. t m a -> b (ComposeSt t m a) Source
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 Source
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 Source
Utility functions
control :: MonadBaseControl b m => (RunInBase m b -> b (StM m a)) -> m a Source
An often used composition: control f =
liftBaseWith
f >>= restoreM
embed :: MonadBaseControl b m => (a -> m c) -> m (a -> b (StM m c)) Source
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 ()) Source
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 Source
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 Source
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 Source
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 Source
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 ()