monoidal-functors-0.2.3.0: Monoidal Functors Library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Bifunctor.Monoidal

Synopsis

Semigroupal

class (Associative cat t1, Associative cat t2, Associative cat to) => Semigroupal cat t1 t2 to f where Source #

Given monoidal categories \((\mathcal{C}, \otimes, I_{\mathcal{C}})\) and \((\mathcal{D}, \bullet, I_{\mathcal{D}})\). A bifunctor \(F : \mathcal{C_1} \times \mathcal{C_2} \to \mathcal{D}\) is Semigroupal if it supports a natural transformation \(\phi_{AB,CD} : F\ A\ B \bullet F\ C\ D \to F\ (A \otimes C)\ (B \otimes D)\), which we call combine.

Laws

Associativity:

\[ \require{AMScd} \begin{CD} (F A B \bullet F C D) \bullet F X Y @>>{\alpha_{\mathcal{D}}}> F A B \bullet (F C D \bullet F X Y) \\ @VV{\phi_{AB,CD} \bullet 1}V @VV{1 \bullet \phi_{CD,FY}}V \\ F (A \otimes C) (B \otimes D) \bullet F X Y @. F A B \bullet (F (C \otimes X) (D \otimes Y) \\ @VV{\phi_{(A \otimes C)(B \otimes D),XY}}V @VV{\phi_{AB,(C \otimes X)(D \otimes Y)}}V \\ F ((A \otimes C) \otimes X) ((B \otimes D) \otimes Y) @>>{F \alpha_{\mathcal{C_1}}} \alpha_{\mathcal{C_2}}> F (A \otimes (C \otimes X)) (B \otimes (D \otimes Y)) \\ \end{CD} \]

combine . grmap combine . bwd assocfmap (bwd assoc) . combine . glmap combine

Methods

combine :: cat (to (f x y) (f x' y')) (f (t1 x x') (t2 y y')) Source #

A natural transformation \(\phi_{AB,CD} : F\ A\ B \bullet F\ C\ D \to F\ (A \otimes C)\ (B \otimes D)\).

Examples

Expand
>>> :t combine @(->) @(,) @(,) @(,) @(,)
combine @(->) @(,) @(,) @(,) @(,) :: ((x, y), (x', y')) -> ((x, x'), (y, y'))
>>> combine @(->) @(,) @(,) @(,) @(,) ((True, "Hello"), ((), "World"))
((True,()),("Hello","World"))
>>> combine @(->) @(,) @(,) @(,) @(->) (show, (>10)) (True, 11)
("True",True)

Instances

Instances details
Semigroupal (->) Either Either Either Either Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: Either (Either x y) (Either x' y') -> Either (Either x x') (Either y y') Source #

Semigroupal (->) Either Either Either (,) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: Either (x, y) (x', y') -> (Either x x', Either y y') Source #

Semigroupal (->) Either (,) (,) Either Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Either x y, Either x' y') -> Either (Either x x') (y, y') Source #

Semigroupal (->) These (,) (,) Either Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Either x y, Either x' y') -> Either (These x x') (y, y') Source #

Profunctor p => Semigroupal (->) (,) Either Either p Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: Either (p x y) (p x' y') -> p (x, x') (Either y y') Source #

Semigroupal (->) (,) (,) (,) (,) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: ((x, y), (x', y')) -> ((x, x'), (y, y')) Source #

Alternative f => Semigroupal (->) Either Either Either (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: Either (Kleisli f x y) (Kleisli f x' y') -> Kleisli f (Either x x') (Either y y') Source #

Functor f => Semigroupal (->) Either Either (,) (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Kleisli f x y, Kleisli f x' y') -> Kleisli f (Either x x') (Either y y') Source #

Alternative f => Semigroupal (->) These These These (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: These (Kleisli f x y) (Kleisli f x' y') -> Kleisli f (These x x') (These y y') Source #

Applicative f => Semigroupal (->) These These (,) (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Kleisli f x y, Kleisli f x' y') -> Kleisli f (These x x') (These y y') Source #

Alternative f => Semigroupal (->) (,) Either (,) (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Kleisli f x y, Kleisli f x' y') -> Kleisli f (x, x') (Either y y') Source #

Applicative f => Semigroupal (->) (,) (,) (,) (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Kleisli f x y, Kleisli f x' y') -> Kleisli f (x, x') (y, y') Source #

Alternative f => Semigroupal (->) Either Either Either (Forget (f r) :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: Either (Forget (f r) x y) (Forget (f r) x' y') -> Forget (f r) (Either x x') (Either y y') Source #

Alternative f => Semigroupal (->) Either Either Either (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: Either (Star f x y) (Star f x' y') -> Star f (Either x x') (Either y y') Source #

Semigroupal (->) Either Either (,) (Forget (f r) :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Forget (f r) x y, Forget (f r) x' y') -> Forget (f r) (Either x x') (Either y y') Source #

Functor f => Semigroupal (->) Either Either (,) (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Star f x y, Star f x' y') -> Star f (Either x x') (Either y y') Source #

Semigroupal (->) Either Either (,) (->) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (x -> y, x' -> y') -> (Either x x' -> Either y y') Source #

Alternative f => Semigroupal (->) These These These (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: These (Star f x y) (Star f x' y') -> Star f (These x x') (These y y') Source #

Applicative f => Semigroupal (->) These These (,) (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Star f x y, Star f x' y') -> Star f (These x x') (These y y') Source #

Alternative f => Semigroupal (->) (,) Either (,) (Forget (f r) :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Forget (f r) x y, Forget (f r) x' y') -> Forget (f r) (x, x') (Either y y') Source #

Alternative f => Semigroupal (->) (,) Either (,) (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Star f x y, Star f x' y') -> Star f (x, x') (Either y y') Source #

Alternative f => Semigroupal (->) (,) (,) (,) (Forget (f r) :: Type -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Forget (f r) x y, Forget (f r) x' y') -> Forget (f r) (x, x') (y, y') Source #

Applicative f => Semigroupal (->) (,) (,) (,) (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Star f x y, Star f x' y') -> Star f (x, x') (y, y') Source #

Semigroupal (->) (,) (,) (,) (->) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (x -> y, x' -> y') -> ((x, x') -> (y, y')) Source #

Functor f => Semigroupal (->) Either Either Either (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: Either (Joker f x y) (Joker f x' y') -> Joker f (Either x x') (Either y y') Source #

Alternative f => Semigroupal (->) Either Either (,) (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Clown f x y, Clown f x' y') -> Clown f (Either x x') (Either y y') Source #

Alternative f => Semigroupal (->) Either Either (,) (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Joker f x y, Joker f x' y') -> Joker f (Either x x') (Either y y') Source #

Applicative f => Semigroupal (->) (,) (,) (,) (Clown f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Clown f x y, Clown f x' y') -> Clown f (x, x') (y, y') Source #

Applicative f => Semigroupal (->) (,) (,) (,) (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

combine :: (Joker f x y, Joker f x' y') -> Joker f (x, x') (y, y') Source #

Unital

class Unital cat i1 i2 io f where Source #

Given monoidal categories \((\mathcal{C}, \otimes, I_{\mathcal{C}})\) and \((\mathcal{D}, \bullet, I_{\mathcal{D}})\). A bifunctor \(F : \mathcal{C_1} \times \mathcal{C_2} \to \mathcal{D}\) is Unital if it supports a morphism \(\phi : I_{\mathcal{D}} \to F\ I_{\mathcal{C_1}}\ I_{\mathcal{C_2}}\), which we call introduce.

Methods

introduce :: cat io (f i1 i2) Source #

introduce maps from the identity in \(\mathcal{C_1} \times \mathcal{C_2}\) to the identity in \(\mathcal{D}\).

Examples

Expand
>>> introduce @(->) @() @() @() @(,) ()
((),())
>>> :t introduce @(->) @Void @() @() @Either
introduce @(->) @Void @() @() @Either :: () -> Either Void ()
>>> introduce @(->) @Void @() @() @Either ()
Right ()

Instances

Instances details
Unital (->) Void Void Void Either Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Unital (->) Void Void Void (,) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: Void -> (Void, Void) Source #

Unital (->) Void () () Either Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Either Void () Source #

Unital (->) () () () (,) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> ((), ()) Source #

Alternative f => Unital (->) Void Void Void (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Unital (->) Void Void () (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Kleisli f Void Void Source #

Alternative f => Unital (->) () Void () (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Kleisli f () Void Source #

Applicative f => Unital (->) () () () (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Kleisli f () () Source #

Alternative f => Unital (->) Void Void Void (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Unital (->) Void Void Void (->) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: Void -> (Void -> Void) Source #

Unital (->) Void Void () (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Star f Void Void Source #

Unital (->) Void Void () (->) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> (Void -> Void) Source #

Alternative f => Unital (->) () Void () (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Star f () Void Source #

Applicative f => Unital (->) () () () (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Star f () () Source #

Unital (->) () () () (->) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> (() -> ()) Source #

Unital (->) Void Void Void (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Alternative f => Unital (->) Void Void () (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Joker f Void Void Source #

Applicative f => Unital (->) () () () (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Methods

introduce :: () -> Joker f () () Source #

Monoidal

class (Tensor cat t1 i1, Tensor cat t2 i2, Tensor cat to io, Semigroupal cat t1 t2 to f, Unital cat i1 i2 io f) => Monoidal cat t1 i1 t2 i2 to io f Source #

Given monoidal categories \((\mathcal{C}, \otimes, I_{\mathcal{C}})\) and \((\mathcal{D}, \bullet, I_{\mathcal{D}})\). A bifunctor \(F : \mathcal{C_1} \times \mathcal{C_2} \to \mathcal{D}\) is Monoidal if it maps between \(\mathcal{C_1} \times \mathcal{C_2}\) and \(\mathcal{D}\) while preserving their monoidal structure. Eg., a homomorphism of monoidal categories.

See NCatlab for more details.

Laws

Right Unitality:

\[ \require{AMScd} \begin{CD} F A B \bullet I_{\mathcal{D}} @>{1 \bullet \phi}>> F A B \bullet F I_{\mathcal{C_{1}}} I_{\mathcal{C_{2}}}\\ @VV{\rho_{\mathcal{D}}}V @VV{\phi AB,I_{\mathcal{C_{1}}}I_{\mathcal{C_{2}}}}V \\ F A B @<<{F \rho_{\mathcal{C_{1}}} \rho_{\mathcal{C_{2}}}}< F (A \otimes I_{\mathcal{C_{1}}}) (B \otimes I_{\mathcal{C_{2}}}) \end{CD} \]

combine . grmap introducebwd unitr . fwd unitr

Left Unitality:

\[ \begin{CD} I_{\mathcal{D}} \bullet F A B @>{\phi \bullet 1}>> F I_{\mathcal{C_{1}}} I_{\mathcal{C_{2}}} \bullet F A B\\ @VV{\lambda_{\mathcal{D}}}V @VV{I_{\mathcal{C_{1}}}I_{\mathcal{C_{2}}},\phi AB}V \\ F A B @<<{F \lambda_{\mathcal{C_{1}}} \lambda_{\mathcal{C_{2}}}}< F (I_{\mathcal{C_{1}}} \otimes A) (I_{\mathcal{C_{2}}} \otimes B) \end{CD} \]

combine . glmap introducefmap (bwd unitl) . fwd unitl

Instances

Instances details
Monoidal (->) Either Void Either Void Either Void Either Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Monoidal (->) Either Void Either Void Either Void (,) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Monoidal (->) Either Void (,) () (,) () Either Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Monoidal (->) These Void (,) () (,) () Either Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Monoidal (->) (,) () (,) () (,) () (,) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Alternative f => Monoidal (->) Either Void Either Void Either Void (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Functor f => Monoidal (->) Either Void Either Void (,) () (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Alternative f => Monoidal (->) These Void These Void These Void (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Applicative f => Monoidal (->) These Void These Void (,) () (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Alternative f => Monoidal (->) (,) () Either Void (,) () (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Applicative f => Monoidal (->) (,) () (,) () (,) () (Kleisli f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Alternative f => Monoidal (->) Either Void Either Void Either Void (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Functor f => Monoidal (->) Either Void Either Void (,) () (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Monoidal (->) Either Void Either Void (,) () (->) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Alternative f => Monoidal (->) These Void These Void These Void (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Applicative f => Monoidal (->) These Void These Void (,) () (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Alternative f => Monoidal (->) (,) () Either Void (,) () (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Applicative f => Monoidal (->) (,) () (,) () (,) () (Star f) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Monoidal (->) (,) () (,) () (,) () (->) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Functor f => Monoidal (->) Either Void Either Void Either Void (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Alternative f => Monoidal (->) Either Void Either Void (,) () (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal

Applicative f => Monoidal (->) (,) () (,) () (,) () (Joker f :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Bifunctor.Monoidal