| License | BSD-style (see the file LICENSE) |
|---|---|
| Maintainer | sjoerd@w3future.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Category.KanExtension
Description
Synopsis
- class (Functor p, Category k) => HasRightKan p k where
- type Ran p f = RanFam p (Cod f) f
- ranF :: HasRightKan p k => p -> Obj (Nat (Dom p) k) f -> Obj (Nat (Cod p) k) (RanFam p k f)
- ranF' :: Nat (Dom p) k (RanFam p k f :.: p) f -> Obj (Nat (Cod p) k) (RanFam p k f)
- newtype RanFunctor (p :: Type) (k :: Type -> Type -> Type) = RanFunctor p
- ranAdj :: forall p k. HasRightKan p k => p -> Adjunction (Nat (Dom p) k) (Nat (Cod p) k) (Precompose p k) (RanFunctor p k)
- class (Functor p, Category k) => HasLeftKan p k where
- type Lan p f = LanFam p (Cod f) f
- lanF :: HasLeftKan p k => p -> Obj (Nat (Dom p) k) f -> Obj (Nat (Cod p) k) (LanFam p k f)
- lanF' :: Nat (Dom p) k f (LanFam p k f :.: p) -> Obj (Nat (Cod p) k) (LanFam p k f)
- newtype LanFunctor (p :: Type) (k :: Type -> Type -> Type) = LanFunctor p
- lanAdj :: forall p k. HasLeftKan p k => p -> Adjunction (Nat (Cod p) k) (Nat (Dom p) k) (LanFunctor p k) (Precompose p k)
- newtype RanHask p f a = RanHask (forall c. Obj (Dom p) c -> Cod p a (p :% c) -> f :% c)
- data RanHaskF p f = RanHaskF
- data LanHask p f a where
- data LanHaskF p f = LanHaskF
Documentation
class (Functor p, Category k) => HasRightKan p k where Source #
An instance of HasRightKan p k says there are right Kan extensions for all functors with codomain k.
Associated Types
type RanFam p k (f :: Type) :: Type Source #
The right Kan extension of a functor p for functors f with codomain k.
Methods
ran :: p -> Obj (Nat (Dom p) k) f -> Nat (Dom p) k (RanFam p k f :.: p) f Source #
ran gives the defining natural transformation of the right Kan extension of f along p.
ranFactorizer :: Nat (Dom p) k (h :.: p) f -> Nat (Cod p) k h (RanFam p k f) Source #
ranFactorizer shows that this extension is universal.
Instances
| (Category j, Category k) => HasRightKan (Id j) k Source # | Ran id = id |
| Functor p => HasRightKan (Any p) (->) Source # | |
Defined in Data.Category.KanExtension | |
| (HasRightKan q k, HasRightKan p k) => HasRightKan (q :.: p) k Source # | Ran (q . p) = Ran q . Ran p |
Defined in Data.Category.KanExtension | |
| HasLimits j k => HasRightKan (Const j Unit ()) k Source # | The right Kan extension of |
Defined in Data.Category.KanExtension Methods ran :: Const j Unit () -> Obj (Nat (Dom (Const j Unit ())) k) f -> Nat (Dom (Const j Unit ())) k (RanFam (Const j Unit ()) k f :.: Const j Unit ()) f Source # ranFactorizer :: Nat (Dom (Const j Unit ())) k (h :.: Const j Unit ()) f -> Nat (Cod (Const j Unit ())) k h (RanFam (Const j Unit ()) k f) Source # | |
ranF :: HasRightKan p k => p -> Obj (Nat (Dom p) k) f -> Obj (Nat (Cod p) k) (RanFam p k f) Source #
newtype RanFunctor (p :: Type) (k :: Type -> Type -> Type) Source #
Constructors
| RanFunctor p |
Instances
| HasRightKan p k => Functor (RanFunctor p k) Source # | |
Defined in Data.Category.KanExtension Associated Types type Dom (RanFunctor p k) :: Type -> Type -> Type Source # type Cod (RanFunctor p k) :: Type -> Type -> Type Source # type (RanFunctor p k) :% a Source # Methods (%) :: RanFunctor p k -> Dom (RanFunctor p k) a b -> Cod (RanFunctor p k) (RanFunctor p k :% a) (RanFunctor p k :% b) Source # | |
| type Cod (RanFunctor p k) Source # | |
Defined in Data.Category.KanExtension | |
| type Dom (RanFunctor p k) Source # | |
Defined in Data.Category.KanExtension | |
| type (RanFunctor p k) :% f Source # | |
Defined in Data.Category.KanExtension | |
ranAdj :: forall p k. HasRightKan p k => p -> Adjunction (Nat (Dom p) k) (Nat (Cod p) k) (Precompose p k) (RanFunctor p k) Source #
The right Kan extension along p is right adjoint to precomposition with p.
class (Functor p, Category k) => HasLeftKan p k where Source #
An instance of HasLeftKan p k says there are left Kan extensions for all functors with codomain k.
Associated Types
type LanFam (p :: Type) (k :: Type -> Type -> Type) (f :: Type) :: Type Source #
The left Kan extension of a functor p for functors f with codomain k.
Methods
lan :: p -> Obj (Nat (Dom p) k) f -> Nat (Dom p) k f (LanFam p k f :.: p) Source #
lan gives the defining natural transformation of the left Kan extension of f along p.
lanFactorizer :: Nat (Dom p) k f (h :.: p) -> Nat (Cod p) k (LanFam p k f) h Source #
lanFactorizer shows that this extension is universal.
Instances
| (Category j, Category k) => HasLeftKan (Id j) k Source # | Lan id = id |
| Functor p => HasLeftKan (Any p) (->) Source # | |
Defined in Data.Category.KanExtension | |
| (HasLeftKan q k, HasLeftKan p k) => HasLeftKan (q :.: p) k Source # | Lan (q . p) = Lan q . Lan p |
Defined in Data.Category.KanExtension | |
| HasColimits j k => HasLeftKan (Const j Unit ()) k Source # | The left Kan extension of |
Defined in Data.Category.KanExtension Methods lan :: Const j Unit () -> Obj (Nat (Dom (Const j Unit ())) k) f -> Nat (Dom (Const j Unit ())) k f (LanFam (Const j Unit ()) k f :.: Const j Unit ()) Source # lanFactorizer :: Nat (Dom (Const j Unit ())) k f (h :.: Const j Unit ()) -> Nat (Cod (Const j Unit ())) k (LanFam (Const j Unit ()) k f) h Source # | |
newtype LanFunctor (p :: Type) (k :: Type -> Type -> Type) Source #
Constructors
| LanFunctor p |
Instances
| HasLeftKan p k => Functor (LanFunctor p k) Source # | |
Defined in Data.Category.KanExtension Associated Types type Dom (LanFunctor p k) :: Type -> Type -> Type Source # type Cod (LanFunctor p k) :: Type -> Type -> Type Source # type (LanFunctor p k) :% a Source # Methods (%) :: LanFunctor p k -> Dom (LanFunctor p k) a b -> Cod (LanFunctor p k) (LanFunctor p k :% a) (LanFunctor p k :% b) Source # | |
| type Cod (LanFunctor p k) Source # | |
Defined in Data.Category.KanExtension | |
| type Dom (LanFunctor p k) Source # | |
Defined in Data.Category.KanExtension | |
| type (LanFunctor p k) :% f Source # | |
Defined in Data.Category.KanExtension | |
lanAdj :: forall p k. HasLeftKan p k => p -> Adjunction (Nat (Cod p) k) (Nat (Dom p) k) (LanFunctor p k) (Precompose p k) Source #
The left Kan extension along p is left adjoint to precomposition with p.
Constructors
| RanHaskF |
Instances
| Functor p => Functor (RanHaskF p f) Source # | |
| type Cod (RanHaskF p f) Source # | |
Defined in Data.Category.KanExtension | |
| type Dom (RanHaskF p f) Source # | |
Defined in Data.Category.KanExtension | |
| type (RanHaskF p f) :% a Source # | |
Defined in Data.Category.KanExtension | |
Constructors
| LanHaskF |
Instances
| Functor p => Functor (LanHaskF p f) Source # | |
| type Cod (LanHaskF p f) Source # | |
Defined in Data.Category.KanExtension | |
| type Dom (LanHaskF p f) Source # | |
Defined in Data.Category.KanExtension | |
| type (LanHaskF p f) :% a Source # | |
Defined in Data.Category.KanExtension | |