| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Runnable
- class Monad m => Runnable m where
- type MonadicState m :: *
- type MonadicResult m a :: *
- class Runnable m => PureRunnable m where
- class MonadTrans t => RunnableTrans t where
- type TransformerState t (m :: * -> *) :: *
- type TransformerResult t (m :: * -> *) a :: *
Documentation
class Monad m => Runnable m where Source #
A class of monads that have a run function.
The runMonad function gives the result inside of IO. The only reason for this is to allow
an instance for IO to be written. Other instances do not perform any aditional IO.
Instances for Identity, IO and
( are given so users
should only provide additional Runnable m, RunnableTrans t, Monad (t m)) => Runnable (t m)RunnableTrans instances instead of Runnable ones.
Minimal complete definition
Associated Types
type MonadicState m :: * Source #
The type of value that needs to be provided to run this monad.
type MonadicResult m a :: * Source #
The type of the result you get when you run this monad.
Methods
currentMonadicState :: m (MonadicState m) Source #
Get the current state value.
restoreMonadicState :: MonadicResult m a -> m a Source #
If given a result, reconstruct a monadic compitation.
runMonad :: MonadicState m -> m a -> IO (MonadicResult m a) Source #
Given the required state value and a computation, run the computation up to the IO effect.
This should effectively run each layer in the transformer stack. The MonadicState should
hold all the needed information to do so.
A more formal description of what it means to run a transformer is given for the
runTransformer function.
runMonad :: PureRunnable m => MonadicState m -> m a -> IO (MonadicResult m a) Source #
Given the required state value and a computation, run the computation up to the IO effect.
This should effectively run each layer in the transformer stack. The MonadicState should
hold all the needed information to do so.
A more formal description of what it means to run a transformer is given for the
runTransformer function.
class Runnable m => PureRunnable m where Source #
Minimal complete definition
Methods
runPureMonad :: MonadicState m -> m a -> MonadicResult m a Source #
Instances
| PureRunnable Identity Source # | |
| (PureRunnable m, RunnableTrans t, Monad (t m)) => PureRunnable (t m) Source # | |
class MonadTrans t => RunnableTrans t where Source #
A class of transformers that can run their effects in the underlying monad.
The following laws need to hold.
\t -> do st <-currentTransStateres <-lift(runTransformert st)restoreTransStateres ==id
f :: (forall a. m a -> m a) \m s -> runTransformer (lift (f m)) s == \m s -> f (runTransformer (lift m) s)
Minimal complete definition
Associated Types
type TransformerState t (m :: * -> *) :: * Source #
The type of value that needs to be provided to run this transformer.
type TransformerResult t (m :: * -> *) a :: * Source #
The type of the result you get when you run this transformer.
Methods
currentTransState :: Monad m => t m (TransformerState t m) Source #
Get the current state value.
restoreTransState :: Monad m => TransformerResult t m a -> t m a Source #
If given a result, reconstruct the computation.
runTransformer :: Monad m => t m a -> TransformerState t m -> m (TransformerResult t m a) Source #
Given the required state value and a computation, run the effects of the transformer in the underlying monad.
Instances
| RunnableTrans ListT Source # | |
| RunnableTrans MaybeT Source # | |
| RunnableTrans (ExceptT e) Source # | |
| Monoid s => RunnableTrans (WriterT s) Source # | |
| RunnableTrans (StateT s) Source # | |
| Error e => RunnableTrans (ErrorT e) Source # | |
| RunnableTrans (IdentityT *) Source # | |
| RunnableTrans (StateT s) Source # | |
| Monoid s => RunnableTrans (WriterT s) Source # | |
| RunnableTrans (RuntimeImplemented e) Source # | |
| RunnableTrans (ReaderT * s) Source # | |
| Monoid w => RunnableTrans (RWST r w s) Source # | |
| Monoid w => RunnableTrans (RWST r w s) Source # | |