data-category-0.2.0: Restricted categories

Portabilitynon-portable
Stabilityexperimental
Maintainersjoerd@w3future.com

Data.Category.Adjunction

Description

 

Synopsis

Documentation

data Adjunction c d f g whereSource

Constructors

Adjunction :: (Functor f, Functor g, Category c, Category d, Dom f ~ d, Cod f ~ c, Dom g ~ c, Cod g ~ d) => f -> g -> Nat d d (Id d) (g :.: f) -> Nat c c (f :.: g) (Id c) -> Adjunction c d f g 

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

unit :: Adjunction c d f g -> Id d :~> (g :.: f)Source

counit :: Adjunction c d f g -> (f :.: g) :~> Id cSource

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

initialPropAdjunction :: (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 :: (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

data AdjArrow c d whereSource

Constructors

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

Instances

wrap :: (Functor g, Functor f, Dom g ~ Dom f', Dom g ~ Cod f) => g -> f -> Nat (Dom f') (Dom f') (Id (Dom f')) (g' :.: f') -> (g :.: f) :~> ((g :.: g') :.: (f' :.: f))Source

cowrap :: (Functor f', Functor g', Dom f' ~ Dom g, Dom f' ~ Cod g') => f' -> g' -> Nat (Dom g) (Dom g) (f :.: g) (Id (Dom g)) -> ((f' :.: f) :.: (g :.: g')) :~> (f' :.: g')Source

curryAdj :: Adjunction (->) (->) (EndoHask ((,) e)) (EndoHask ((->) e))Source

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.