| Copyright | (C) 2008 Edward Kmett (C) 2024 Koji Miyazato |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Koji Miyazato <viercc@gmail.com> |
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Control.Monad.Coproduct
Description
Synopsis
- newtype (m0 :+ n0) a = Coproduct {}
- inject1 :: Functor m0 => m0 a -> (m0 :+ n0) a
- inject2 :: Functor n0 => n0 a -> (m0 :+ n0) a
- (||||) :: MonadIdeal t => (forall a. m0 a -> t a) -> (forall a. n0 a -> t a) -> (m0 :+ n0) b -> t b
- eitherMonad :: (Isolated m0, Isolated n0, Monad t) => (forall a. m0 a -> t a) -> (forall a. n0 a -> t a) -> (m0 :+ n0) b -> t b
- newtype Mutual p m n a = Mutual {}
Ideal Monad Coproduct
Coproduct of impure parts of two Monads.
As the coproduct of Isolated
Given and Isolated m0Isolated n0, the functor m0 :+ n0 is Isolated too. In other words,
given two Monads Unite m0 and Unite n0, this type constructs a new Monad (Unite (m0 :+ n0)).
Furthermore, as the name suggests,
Unite (m0 :+ n0) is the coproduct of Unite m0 and Unite n0 as a Monad.
is a monad morphismhoistUniteinject1:: Unite m0 ~> Unite (m0 :+ n0)is a monad morphismhoistUniteinject2:: Unite n0 ~> Unite (m0 :+ n0)is an impure monad morphism, giveneitherMonadmt nt :: (m0 :+ n0) ~> t(mt :: m0 ~> t)and(nt :: n0 ~> t)are impure monad morphisms.- Any impure monad morphisms
(m0 :+ n0) ~> tcan be uniquely rewritten as(eitherMonad mt nt).
Here, a natural transformation nat :: f ~> g is an impure monad morphism means
f is an Isolated, g is a Monad, and nat becomes a monad morphism when combined with pure as below.
either pure nat . runUnite :: Unite f ~> g
As the coproduct of MonadIdeal
Given and MonadIdeal m0MonadIdeal n0, the functor m0 :+ n0 is MonadIdeal too.
It is the coproduct of m0 and n0 as a MonadIdeal.
inject1 :: m0 ~> (m0 :+ n0)is aMonadIdealmorphisminject2 :: n0 ~> (m0 :+ n0)is aMonadIdealmorphism(mt |||| nt) :: (m0 :+ n0) ~> t0is aMonadIdealmorphism, givenmt, ntareMonadIdealmorphisms.- Any
MonadIdealmorphism(m0 :+ n0) ~> t0can be uniquely rewritten as(mt |||| nt).
Here, a MonadIdeal morphism is a natural transformation nat between MonadIdeal such that
preserves idealBind.
nat (idealBind ma k) = idealBind (nat ma) (hoistIdeal nat . k)
Instances
| (Functor m0, Functor n0) => Functor (m0 :+ n0) Source # | |
| (MonadIdeal m0, MonadIdeal n0) => MonadIdeal (m0 :+ n0) Source # | |
| (Isolated m0, Isolated n0) => Isolated (m0 :+ n0) Source # | |
Defined in Control.Monad.Coproduct | |
| (MonadIdeal m0, MonadIdeal n0) => Apply (m0 :+ n0) Source # | |
| (MonadIdeal m0, MonadIdeal n0) => Bind (m0 :+ n0) Source # | |
| (Show (m0 (Either a (Mutual Either n0 m0 a))), Show (n0 (Either a (Mutual Either m0 n0 a)))) => Show ((m0 :+ n0) a) Source # | |
| (Eq (m0 (Either a (Mutual Either n0 m0 a))), Eq (n0 (Either a (Mutual Either m0 n0 a)))) => Eq ((m0 :+ n0) a) Source # | |
(||||) :: MonadIdeal t => (forall a. m0 a -> t a) -> (forall a. n0 a -> t a) -> (m0 :+ n0) b -> t b Source #
eitherMonad :: (Isolated m0, Isolated n0, Monad t) => (forall a. m0 a -> t a) -> (forall a. n0 a -> t a) -> (m0 :+ n0) b -> t b Source #