boots-0.2.0.1: IoC Monad in Haskell

Copyright2019 Daniel YU
LicenseMIT
Maintainerleptonyu@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Factory

Contents

Description

IoC Monad in Haskell.

  • Motivation

Simplify to create an application in Haskell.

When we decide to create an application using Haskell. We may need using configurations, loggers as basic functions. If this application needs storages, caches, etc., then we have to weaving the management of connection of these facilities into the application. Connections need to be created before and be destroyed after using them. There is a common strategy to manage connections, that is using Cont. Then we can encapsulate the management of connections separately. For example, we can write a database plugin Factory m cxt DBConnection, which can manage the database connections in monad m with context cxt. Context cxt may be requested for getting configurations or logging functions. When all the components of application are encapsulated by plugins, then running an application will be simplified.

  • Factory

Factory has an environment env, which provides anything needs by the factory. component is the production of the factory, it will be used by other Factory. Finally to build a complete Factory m () (m ()), which can be boot.

Synopsis

Monad

class (Monad m, Monad n) => MonadFactory env n m | m -> env n where Source #

Monads which allow to produce component under env, and env can be changed by this procedure.

Methods

getEnv :: m env Source #

Return the environment of the monad.

putEnv :: env -> m () Source #

Replace the environment inside the monad.

produce Source #

Arguments

:: n component

Open resource

-> (component -> n ())

Close resource

-> m component 

Produce a resource component, with open and close.

Instances
MonadMask m => MonadFactory env m (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

getEnv :: Factory m env env Source #

putEnv :: env -> Factory m env () Source #

produce :: m component -> (component -> m ()) -> Factory m env component Source #

defer :: MonadFactory env n m => n () -> m () Source #

Defer to run side effect when closeing resource.

asksEnv :: MonadFactory env n m => (env -> a) -> m a Source #

Asks sub value of env.

modifyEnv :: MonadFactory env n m => (env -> env) -> m () Source #

Modify environment env.

withEnv :: MonadFactory env n m => (env -> m env) -> m () Source #

Change environment env.

runEnv :: MonadFactory env n m => m c -> m (env, c) Source #

Run factory, return component c and updated environment env.

Monad Instance

newtype Factory m env component Source #

Factory defines how to generate a component under the environment env in monad m. It is similar to IoC container in oop, env will provide anything to be wanted to generate component.

Constructors

Factory 

Fields

Instances
MonadMask m => MonadFactory env m (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

getEnv :: Factory m env env Source #

putEnv :: env -> Factory m env () Source #

produce :: m component -> (component -> m ()) -> Factory m env component Source #

MonadState env (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

get :: Factory m env env #

put :: env -> Factory m env () #

state :: (env -> (a, env)) -> Factory m env a #

Category (Factory m :: Type -> Type -> Type) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

id :: Factory m a a #

(.) :: Factory m b c -> Factory m a b -> Factory m a c #

Monad (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

(>>=) :: Factory m env a -> (a -> Factory m env b) -> Factory m env b #

(>>) :: Factory m env a -> Factory m env b -> Factory m env b #

return :: a -> Factory m env a #

fail :: String -> Factory m env a #

Functor (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

fmap :: (a -> b) -> Factory m env a -> Factory m env b #

(<$) :: a -> Factory m env b -> Factory m env a #

Applicative (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

pure :: a -> Factory m env a #

(<*>) :: Factory m env (a -> b) -> Factory m env a -> Factory m env b #

liftA2 :: (a -> b -> c) -> Factory m env a -> Factory m env b -> Factory m env c #

(*>) :: Factory m env a -> Factory m env b -> Factory m env b #

(<*) :: Factory m env a -> Factory m env b -> Factory m env a #

MonadIO m => MonadIO (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

liftIO :: IO a -> Factory m env a #

MonadThrow m => MonadThrow (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

throwM :: Exception e => e -> Factory m env a #

Monad m => MonadCont (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

callCC :: ((a -> Factory m env b) -> Factory m env a) -> Factory m env a #

Run functions

running :: env -> Factory m env c -> (c -> m ()) -> m () Source #

Running the factory.

boot :: Monad m => Factory m () (m ()) -> m () Source #

Run the application using a specified factory.

With

within :: env -> Factory m env component -> Factory m env' component Source #

Construct factory under env, and adapt it to fit another env'.

withFactory :: (env' -> env) -> Factory m env component -> Factory m env' component Source #

Construct factory under env, and adapt it to fit another env'.

wrap :: ((c -> m ()) -> m ()) -> Factory m env c Source #

Wrap raw procedure into a Factory.

liftFT :: Monad m => m a -> Factory m env a Source #

Lift a monad m into a Factory.

natTrans :: (n () -> m ()) -> (m () -> n ()) -> Factory n env component -> Factory m env component Source #

Nature transform of one Factory with monad n into another with monad m.

Reexport Function

Category Arrow

(>>>) :: Category cat => cat a b -> cat b c -> cat a c infixr 1 #

Left-to-right composition

(<<<) :: Category cat => cat b c -> cat a b -> cat a c infixr 1 #

Right-to-left composition

Monoid Join

(<>) :: Semigroup a => a -> a -> a infixr 6 #

An associative operation.

Other

class Monad m => MonadThrow (m :: Type -> Type) where #

A class for monads in which exceptions may be thrown.

Instances should obey the following law:

throwM e >> x = throwM e

In other words, throwing an exception short-circuits the rest of the monadic computation.

Methods

throwM :: Exception e => e -> m a #

Throw an exception. Note that this throws when this action is run in the monad m, not when it is applied. It is a generalization of Control.Exception's throwIO.

Should satisfy the law:

throwM e >> f = throwM e
Instances
MonadThrow [] 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> [a] #

MonadThrow Maybe 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Maybe a #

MonadThrow IO 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IO a #

MonadThrow Q 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> Q a #

MonadThrow STM 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> STM a #

e ~ SomeException => MonadThrow (Either e) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> Either e a #

MonadThrow (ST s) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ST s a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> MaybeT m a #

MonadThrow m => MonadThrow (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ListT m a #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ExceptT e m a #

MonadThrow m => MonadThrow (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> IdentityT m a #

(Error e, MonadThrow m) => MonadThrow (ErrorT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e0 => e0 -> ErrorT e m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

MonadThrow m => MonadThrow (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> StateT s m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> WriterT w m a #

MonadThrow m => MonadThrow (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

throwM :: Exception e => e -> Factory m env a #

MonadThrow m => MonadThrow (ContT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ContT r m a #

MonadThrow m => MonadThrow (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> ReaderT r m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

throwM :: Exception e => e -> RWST r w s m a #

class MonadThrow m => MonadCatch (m :: Type -> Type) #

A class for monads which allow exceptions to be caught, in particular exceptions which were thrown by throwM.

Instances should obey the following law:

catch (throwM e) f = f e

Note that the ability to catch an exception does not guarantee that we can deal with all possible exit points from a computation. Some monads, such as continuation-based stacks, allow for more than just a success/failure strategy, and therefore catch cannot be used by those monads to properly implement a function such as finally. For more information, see MonadMask.

Minimal complete definition

catch

Instances
MonadCatch IO 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a #

MonadCatch STM 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => STM a -> (e -> STM a) -> STM a #

e ~ SomeException => MonadCatch (Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => Either e a -> (e0 -> Either e a) -> Either e a #

MonadCatch m => MonadCatch (MaybeT m)

Catches exceptions from the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a #

MonadCatch m => MonadCatch (ListT m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => ListT m a -> (e -> ListT m a) -> ListT m a #

MonadCatch m => MonadCatch (ExceptT e m)

Catches exceptions from the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => ExceptT e m a -> (e0 -> ExceptT e m a) -> ExceptT e m a #

MonadCatch m => MonadCatch (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a #

(Error e, MonadCatch m) => MonadCatch (ErrorT e m)

Catches exceptions from the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e0 => ErrorT e m a -> (e0 -> ErrorT e m a) -> ErrorT e m a #

MonadCatch m => MonadCatch (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

MonadCatch m => MonadCatch (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a #

MonadCatch m => MonadCatch (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

catch :: Exception e => RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a #

class MonadCatch m => MonadMask (m :: Type -> Type) #

A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads are invalid instances of this class.

Instances should ensure that, in the following code:

fg = f `finally` g

The action g is called regardless of what occurs within f, including async exceptions. Some monads allow f to abort the computation via other effects than throwing an exception. For simplicity, we will consider aborting and throwing an exception to be two forms of "throwing an error".

If f and g both throw an error, the error thrown by fg depends on which errors we're talking about. In a monad transformer stack, the deeper layers override the effects of the inner layers; for example, ExceptT e1 (Except e2) a represents a value of type Either e2 (Either e1 a), so throwing both an e1 and an e2 will result in Left e2. If f and g both throw an error from the same layer, instances should ensure that the error from g wins.

Effects other than throwing an error are also overriden by the deeper layers. For example, StateT s Maybe a represents a value of type s -> Maybe (a, s), so if an error thrown from f causes this function to return Nothing, any changes to the state which f also performed will be erased. As a result, g will see the state as it was before f. Once g completes, f's error will be rethrown, so g' state changes will be erased as well. This is the normal interaction between effects in a monad transformer stack.

By contrast, lifted-base's version of finally always discards all of g's non-IO effects, and g never sees any of f's non-IO effects, regardless of the layer ordering and regardless of whether f throws an error. This is not the result of interacting effects, but a consequence of MonadBaseControl's approach.

Minimal complete definition

mask, uninterruptibleMask, generalBracket

Instances
MonadMask IO 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

generalBracket :: IO a -> (a -> ExitCase b -> IO c) -> (a -> IO b) -> IO (b, c) #

e ~ SomeException => MonadMask (Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

generalBracket :: Either e a -> (a -> ExitCase b -> Either e c) -> (a -> Either e b) -> Either e (b, c) #

MonadMask m => MonadMask (MaybeT m)

Since: exceptions-0.10.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

uninterruptibleMask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

generalBracket :: MaybeT m a -> (a -> ExitCase b -> MaybeT m c) -> (a -> MaybeT m b) -> MaybeT m (b, c) #

MonadMask m => MonadMask (ExceptT e m)

Since: exceptions-0.9.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

uninterruptibleMask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

generalBracket :: ExceptT e m a -> (a -> ExitCase b -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m (b, c) #

MonadMask m => MonadMask (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

uninterruptibleMask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

generalBracket :: IdentityT m a -> (a -> ExitCase b -> IdentityT m c) -> (a -> IdentityT m b) -> IdentityT m (b, c) #

(Error e, MonadMask m) => MonadMask (ErrorT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b) -> ErrorT e m b #

uninterruptibleMask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b) -> ErrorT e m b #

generalBracket :: ErrorT e m a -> (a -> ExitCase b -> ErrorT e m c) -> (a -> ErrorT e m b) -> ErrorT e m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

MonadMask m => MonadMask (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

uninterruptibleMask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

generalBracket :: ReaderT r m a -> (a -> ExitCase b -> ReaderT r m c) -> (a -> ReaderT r m b) -> ReaderT r m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

class Monad m => MonadIO (m :: Type -> Type) where #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Methods

liftIO :: IO a -> m a #

Lift a computation from the IO monad.

Instances
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (Factory m env) Source # 
Instance details

Defined in Control.Monad.Factory

Methods

liftIO :: IO a -> Factory m env a #

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

liftIO :: IO a -> RWST r w s m a #

lift :: (MonadTrans t, Monad m) => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.