| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Supermonad
Contents
Description
Representation of supermonads in Haskell.
- class (Functor m, Functor n, Functor p) => Bind m n p where
- type BindCts m n p :: Constraint
- class Functor m => Return m where
- type ReturnCts m :: Constraint
- class Fail m where
- type FailCts m :: Constraint
- type family Monad m :: Constraint where ...
Supermonads
class (Functor m, Functor n, Functor p) => Bind m n p where Source #
Representation of bind operations for supermonads.
A proper supermonad consists of an instance
for Bind, Return and optionally Fail.
The instances are required to follow a certain scheme.
If the type constructor of your supermonad is M there
may only be exactly one Bind and one Return instance
that look as follows:
instance Bind (M ...) (M ...) (M ...) where ... instance Return (M ...) where ...
This is enforced by the plugin. A compilation error will
result from either instance missing or multiple instances
for M.
For supermonads we expect the usual monad laws to hold:
Minimal complete definition
Associated Types
type BindCts m n p :: Constraint Source #
Instances
| Bind [] [] [] Source # | |
| Bind Maybe Maybe Maybe Source # | |
| Bind IO IO IO Source # | |
| Bind Identity Identity Identity Source # | |
| Bind Min Min Min Source # | |
| Bind Max Max Max Source # | |
| Bind First First First Source # | |
| Bind Last Last Last Source # | |
| Bind Option Option Option Source # | |
| Bind NonEmpty NonEmpty NonEmpty Source # | |
| Bind Complex Complex Complex Source # | |
| Bind STM STM STM Source # | |
| Bind Dual Dual Dual Source # | |
| Bind Sum Sum Sum Source # | |
| Bind Product Product Product Source # | |
| Bind First First First Source # | |
| Bind Last Last Last Source # | |
| Bind ReadPrec ReadPrec ReadPrec Source # | |
| Bind ReadP ReadP ReadP Source # | |
| Bind ((->) r) ((->) r) ((->) r) Source # | |
| Bind (Either e) (Either e) (Either e) Source # | |
| Bind (ST s) (ST s) (ST s) Source # | |
| Bind (ST s) (ST s) (ST s) Source # | |
| (Bind m m m, Monad m) => Bind (WrappedMonad m) (WrappedMonad m) (WrappedMonad m) Source # | TODO / FIXME: The wrapped monad instances for instance (Functor m) => Functor (App.WrappedMonad m) where fmap f m = App.WrapMonad $ fmap (App.unwrapMonad m) f |
| ArrowApply a => Bind (ArrowMonad a) (ArrowMonad a) (ArrowMonad a) Source # | |
| Bind (Proxy *) (Proxy *) (Proxy *) Source # | |
| (Return n, Bind m n p) => Bind (MaybeT m) (MaybeT n) (MaybeT p) Source # | |
| (Bind m n p, Bind n n n, Return n) => Bind (ListT m) (ListT n) (ListT p) Source # | |
| Bind m n p => Bind (Alt * m) (Alt * n) (Alt * p) Source # | |
| (Bind m n p, Return n) => Bind (ExceptT e m) (ExceptT e n) (ExceptT e p) Source # | |
| Bind m n p => Bind (StateT s m) (StateT s n) (StateT s p) Source # | |
| Bind m n p => Bind (StateT s m) (StateT s n) (StateT s p) Source # | |
| (Monoid w, Bind m n p) => Bind (WriterT w m) (WriterT w n) (WriterT w p) Source # | |
| (Monoid w, Bind m n p) => Bind (WriterT w m) (WriterT w n) (WriterT w p) Source # | |
| Bind m n p => Bind (IdentityT * m) (IdentityT * n) (IdentityT * p) Source # | |
| (Bind m1 n1 p1, Bind m2 n2 p2) => Bind (Product * m1 m2) (Product * n1 n2) (Product * p1 p2) Source # | |
| Bind (ContT * r m) (ContT * r m) (ContT * r m) Source # | TODO / FIXME: Still need to figure out how and if we can generalize the continuation implementation. |
| Bind m n p => Bind (ReaderT * r m) (ReaderT * r n) (ReaderT * r p) Source # | |
| (Monoid w, Bind m n p) => Bind (RWST r w s m) (RWST r w s n) (RWST r w s p) Source # | |
| (Monoid w, Bind m n p) => Bind (RWST r w s m) (RWST r w s n) (RWST r w s p) Source # | |
class Functor m => Return m where Source #
See Bind for details on laws and requirements.
Minimal complete definition
Associated Types
type ReturnCts m :: Constraint Source #
Instances
See Bind for details on laws and requirements.
Minimal complete definition
Associated Types
type FailCts m :: Constraint Source #
Instances