Copyright | 2019 Daniel YU |
---|---|
License | MIT |
Maintainer | leptonyu@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
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
- class (Monad m, Monad n) => MonadFactory env n m | m -> env n where
- defer :: MonadFactory env n m => n () -> m ()
- asksEnv :: MonadFactory env n m => (env -> a) -> m a
- modifyEnv :: MonadFactory env n m => (env -> env) -> m ()
- withEnv :: MonadFactory env n m => (env -> m env) -> m ()
- runEnv :: MonadFactory env n m => m c -> m (env, c)
- newtype Factory m env component = Factory {}
- running :: env -> Factory m env c -> (c -> m ()) -> m ()
- boot :: Monad m => Factory m () (m ()) -> m ()
- within :: env -> Factory m env component -> Factory m env' component
- withFactory :: (env' -> env) -> Factory m env component -> Factory m env' component
- wrap :: ((c -> m ()) -> m ()) -> Factory m env c
- liftFT :: Monad m => m a -> Factory m env a
- natTrans :: (n () -> m ()) -> (m () -> n ()) -> Factory n env component -> Factory m env component
- (>>>) :: Category cat => cat a b -> cat b c -> cat a c
- (<<<) :: Category cat => cat b c -> cat a b -> cat a c
- (<>) :: Semigroup a => a -> a -> a
- class Monad m => MonadThrow (m :: Type -> Type) where
- class MonadThrow m => MonadCatch (m :: Type -> Type)
- class MonadCatch m => MonadMask (m :: Type -> Type)
- class Monad m => MonadIO (m :: Type -> Type) where
- lift :: (MonadTrans t, Monad m) => m a -> t m a
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.
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
.
Instances
MonadMask m => MonadFactory env m (Factory m env) Source # | |
MonadState env (Factory m env) Source # | |
Category (Factory m :: Type -> Type -> Type) Source # | |
Monad (Factory m env) Source # | |
Functor (Factory m env) Source # | |
Applicative (Factory m env) Source # | |
Defined in Control.Monad.Factory 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 # | |
Defined in Control.Monad.Factory | |
MonadThrow m => MonadThrow (Factory m env) Source # | |
Defined in Control.Monad.Factory | |
Monad m => MonadCont (Factory m env) Source # | |
Run functions
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'
.
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
Monoid Join
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.
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
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
.
Instances
MonadCatch IO | |
MonadCatch STM | |
e ~ SomeException => MonadCatch (Either e) | Since: exceptions-0.8.3 |
MonadCatch m => MonadCatch (MaybeT m) | Catches exceptions from the base monad. |
MonadCatch m => MonadCatch (ListT m) | |
MonadCatch m => MonadCatch (ExceptT e m) | Catches exceptions from the base monad. |
MonadCatch m => MonadCatch (IdentityT m) | |
(Error e, MonadCatch m) => MonadCatch (ErrorT e m) | Catches exceptions from the base monad. |
MonadCatch m => MonadCatch (StateT s m) | |
MonadCatch m => MonadCatch (StateT s m) | |
(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) | |
(MonadCatch m, Monoid w) => MonadCatch (WriterT w m) | |
MonadCatch m => MonadCatch (ReaderT r m) | |
(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) | |
(MonadCatch m, Monoid w) => MonadCatch (RWST r w s m) | |
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.
Instances
MonadMask IO | |
e ~ SomeException => MonadMask (Either e) | Since: exceptions-0.8.3 |
Defined in Control.Monad.Catch | |
MonadMask m => MonadMask (MaybeT m) | Since: exceptions-0.10.0 |
Defined in Control.Monad.Catch | |
MonadMask m => MonadMask (ExceptT e m) | Since: exceptions-0.9.0 |
Defined in Control.Monad.Catch 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) | |
Defined in Control.Monad.Catch 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) | |
Defined in Control.Monad.Catch | |
MonadMask m => MonadMask (StateT s m) | |
Defined in Control.Monad.Catch | |
MonadMask m => MonadMask (StateT s m) | |
Defined in Control.Monad.Catch | |
(MonadMask m, Monoid w) => MonadMask (WriterT w m) | |
Defined in Control.Monad.Catch 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) | |
Defined in Control.Monad.Catch 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) | |
Defined in Control.Monad.Catch 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) | |
Defined in Control.Monad.Catch 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) | |
Defined in Control.Monad.Catch 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:
Instances
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.