| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Control.Monad.Module
Description
Synopsis
- class (Functor f, Monad m) => Module f m where
- (>>==) :: f a -> (a -> m b) -> f b
 
 - mjoin :: Module f m => f (m a) -> f a
 - transAction :: (MonadTrans t, Monad m, Monad (t m)) => t m a -> (a -> m b) -> t m b
 - composeAction :: (Functor f, Monad m) => Compose f m a -> (a -> m b) -> Compose f m b
 - class Module f m => LiftedModule f m where
- mlift :: m a -> f a
 
 
Documentation
class (Functor f, Monad m) => Module f m where Source #
f is right m-module. (according to https://ncatlab.org/nlab/show/module+over+a+monad#modules definitions).
 We have  natural transformation.Compose f m ~> f
Laws
fma>>==return = fma fma>>==(f>=>g) = (fma>>==f)>>==g
Properties
For all  we can write associated Monad minstance .Module m m where (>>==) = (>>=)
mjoin and >>== are equivalent in power:
fa>>==amb =mjoin(fmapamb fa)
transAction :: (MonadTrans t, Monad m, Monad (t m)) => t m a -> (a -> m b) -> t m b Source #
 action's implementation.Module m (t m)
class Module f m => LiftedModule f m where Source #
An extension of Module allowing to lift m a info f a.
 As we have , this allows to have a pseudo-return for Monad mf:
 point . return :: a -> f a
Note: for f = t m for some MonadTrans t.mlift = lift
Since: 0.0.2
Instances
| LiftedModule f m => LiftedModule (ScopeH b f m) m Source # | |
Defined in Bound.ScopeH  | |
| (Monad f, Monad (t f)) => LiftedModule (ScopeT b t f) f Source # | |
Defined in Bound.ScopeT  | |