simple-effects-0.9.0.1: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Runnable

Synopsis

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 (Runnable m, RunnableTrans t, Monad (t m)) => Runnable (t m) are given so users should only provide additional RunnableTrans instances instead of Runnable ones.

Minimal complete definition

currentMonadicState, restoreMonadicState, runMonad

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.

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 <- currentTransState
           res <- lift (runTransformer t st)
           restoreTransState res
  == id
  f :: (forall a. m a -> m a)
  m s -> runTransformer (lift (f m)) s == m s -> f (runTransformer (lift m) s)

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 compitation.

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 # 

Associated Types

type TransformerState (ListT :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (ListT :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

RunnableTrans MaybeT Source # 

Associated Types

type TransformerState (MaybeT :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (MaybeT :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

Monoid s => RunnableTrans (WriterT s) Source # 

Associated Types

type TransformerState (WriterT s :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (WriterT s :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

RunnableTrans (StateT s) Source # 

Associated Types

type TransformerState (StateT s :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (StateT s :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

RunnableTrans (ExceptT e) Source # 

Associated Types

type TransformerState (ExceptT e :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (ExceptT e :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

Error e => RunnableTrans (ErrorT e) Source # 

Associated Types

type TransformerState (ErrorT e :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (ErrorT e :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

RunnableTrans (IdentityT *) Source # 

Associated Types

type TransformerState (IdentityT * :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (IdentityT * :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

RunnableTrans (StateT s) Source # 

Associated Types

type TransformerState (StateT s :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (StateT s :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

Monoid s => RunnableTrans (WriterT s) Source # 

Associated Types

type TransformerState (WriterT s :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (WriterT s :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

RunnableTrans (EffectHandler effKind) Source # 

Associated Types

type TransformerState (EffectHandler effKind :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (EffectHandler effKind :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

RunnableTrans (ReaderT * s) Source # 

Associated Types

type TransformerState (ReaderT * s :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (ReaderT * s :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

Monoid w => RunnableTrans (RWST r w s) Source # 

Associated Types

type TransformerState (RWST r w s :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (RWST r w s :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

Methods

currentTransState :: Monad m => RWST r w s m (TransformerState (RWST r w s) m) Source #

restoreTransState :: Monad m => TransformerResult (RWST r w s) m a -> RWST r w s m a Source #

runTransformer :: Monad m => RWST r w s m a -> TransformerState (RWST r w s) m -> m (TransformerResult (RWST r w s) m a) Source #

Monoid w => RunnableTrans (RWST r w s) Source # 

Associated Types

type TransformerState (RWST r w s :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (RWST r w s :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

Methods

currentTransState :: Monad m => RWST r w s m (TransformerState (RWST r w s) m) Source #

restoreTransState :: Monad m => TransformerResult (RWST r w s) m a -> RWST r w s m a Source #

runTransformer :: Monad m => RWST r w s m a -> TransformerState (RWST r w s) m -> m (TransformerResult (RWST r w s) m a) Source #