Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class (Functor m, Functor n, Functor p) => Applicative m n p where
- type ApplicativeCts m n p :: Constraint
- pure :: (Return f, ReturnCts f) => a -> f a
- class Functor (f :: * -> *) where
- 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:
type BindCts m n p :: Constraint Source #
(>>=) :: BindCts m n p => m a -> (a -> n b) -> p b infixl 1 Source #
(>>) :: BindCts m n p => m a -> n b -> p b infixl 1 Source #
Bind [] [] [] Source # | |
Bind Maybe Maybe Maybe Source # | |
Bind IO IO IO Source # | |
Bind Complex Complex Complex 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 Identity Identity Identity 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 (Either e) (Either e) (Either e) Source # | |
Bind (U1 *) (U1 *) (U1 *) 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 (Rec1 * m) (Rec1 * n) (Rec1 * 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 ((->) LiftedRep LiftedRep r) ((->) LiftedRep LiftedRep r) ((->) LiftedRep LiftedRep r) Source # | |
(Bind f g h, Bind f' g' h') => Bind ((:*:) * f f') ((:*:) * g g') ((:*:) * h h') 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 # | |
Bind f g h => Bind (M1 * i c f) (M1 * i c g) (M1 * i c h) 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
or Ap
for details on laws and requirements.
type ReturnCts m :: Constraint Source #
See Bind
for details on laws and requirements.
type FailCts m :: Constraint Source #
Super-Applicatives
class (Functor m, Functor n, Functor p) => Applicative m n p where Source #
TODO
type ApplicativeCts m n p :: Constraint Source #
(<*>) :: ApplicativeCts m n p => m (a -> b) -> n a -> p b infixl 4 Source #
(*>) :: ApplicativeCts m n p => m a -> n b -> p b infixl 4 Source #
(<*) :: ApplicativeCts m n p => m a -> n b -> p a infixl 4 Source #
class Functor (f :: * -> *) where #
The Functor
class is used for types that can be mapped over.
Instances of Functor
should satisfy the following laws:
fmap id == id fmap (f . g) == fmap f . fmap g
The instances of Functor
for lists, Maybe
and IO
satisfy these laws.