data-category-0.3.1.1: Restricted categories

Portabilitynon-portable
Stabilityexperimental
Maintainersjoerd@w3future.com

Data.Category.Adjunction

Contents

Description

 

Synopsis

Adjunctions

data Adjunction c d f g Source

Constructors

(Functor f, Functor g, Category c, Category d, Dom f ~ d, Cod f ~ c, Dom g ~ c, Cod g ~ d) => Adjunction 

Fields

leftAdjoint :: f
 
rightAdjoint :: g
 
unit :: Nat d d (Id d) (g :.: f)
 
counit :: Nat c c (f :.: g) (Id c)
 

mkAdjunction :: (Functor f, Functor g, Category c, Category d, Dom f ~ d, Cod f ~ c, Dom g ~ c, Cod g ~ d) => f -> g -> (forall a. Obj d a -> Component (Id d) (g :.: f) a) -> (forall a. Obj c a -> Component (f :.: g) (Id c) a) -> Adjunction c d f gSource

leftAdjunct :: Adjunction c d f g -> Obj d a -> c (f :% a) b -> d a (g :% b)Source

rightAdjunct :: Adjunction c d f g -> Obj c b -> d a (g :% b) -> c (f :% a) bSource

Adjunctions from universal morphisms

initialPropAdjunction :: forall f g c d. (Functor f, Functor g, Category c, Category d, Dom f ~ d, Cod f ~ c, Dom g ~ c, Cod g ~ d) => f -> g -> (forall y. Obj d y -> InitialUniversal y g (f :% y)) -> Adjunction c d f gSource

terminalPropAdjunction :: forall f g c d. (Functor f, Functor g, Category c, Category d, Dom f ~ d, Cod f ~ c, Dom g ~ c, Cod g ~ d) => f -> g -> (forall x. Obj c x -> TerminalUniversal x f (g :% x)) -> Adjunction c d f gSource

Adjunctions to universal morphisms

Adjunctions as a category

data AdjArrow c d whereSource

Constructors

AdjArrow :: (Category c, Category d) => Adjunction c d f g -> AdjArrow (CatW c) (CatW d) 

Instances

Category AdjArrow

The category with categories as objects and adjunctions as arrows.

(Co)limitfunctor adjunction

limitAdj :: forall j (~>). HasLimits j ~> => LimitFunctor j ~> -> Adjunction (Nat j ~>) ~> (Diag j ~>) (LimitFunctor j ~>)Source

The limit functor is right adjoint to the diagonal functor.

colimitAdj :: forall j (~>). HasColimits j ~> => ColimitFunctor j ~> -> Adjunction ~> (Nat j ~>) (ColimitFunctor j ~>) (Diag j ~>)Source

The colimit functor is left adjoint to the diagonal functor.

(Co)monad of an adjunction

Examples

contAdj :: Adjunction (Op (->)) (->) (Cont1 r) (Cont2 r)Source