Copyright | Guillaume Sabbagh 2022 |
---|---|
License | GPL-3 |
Maintainer | [email protected] |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Math.CocompleteCategory
Description
Typeclasses for Category
with special properties such as being cocomplete.
A Category
might have coproducts meaning that any discreteDiagram
on it has a colimit.
A Category
might have coequalizers meaning that any parallelDiagram
on it has a colimit.
If a Category
have both coproducts and coequalizers, it is cocomplete meaning that it has all small colimits.
To compute colimits in a custom FiniteCategory
, see colimits
in Math.ConeCategory.
Synopsis
- data Colimit i t
- = Coprojection t
- | CoproductElement i t
- uncoproject :: Colimit oIndex t -> t
- class (Category c m o, Morphism m o, Category cLim mLim oLim, Morphism mLim oLim) => HasCoproducts c m o cLim mLim oLim oIndex | c -> m, m -> o, cLim -> mLim, mLim -> oLim, c oIndex -> cLim where
- coproduct :: Diagram (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex c m o -> Cocone (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex cLim mLim oLim
- class (Category c m o, Morphism m o) => HasCoequalizers c m o | c -> m, m -> o where
- coequalize :: Diagram Parallel ParallelAr ParallelOb c m o -> Cocone Parallel ParallelAr ParallelOb c m o
- colimitFromCoproductsAndCoequalizers :: (Category c m o, Morphism m o, Category cLim mLim oLim, Morphism mLim oLim, HasCoproducts c m o cLim mLim oLim oIndex, HasCoequalizers cLim mLim oLim, FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq oIndex, Eq mIndex, Eq cIndex) => (m -> mLim) -> Diagram cIndex mIndex oIndex c m o -> Cocone cIndex mIndex oIndex cLim mLim oLim
- class (Category c m o, Morphism m o, Category cLim mLim oLim, Morphism mLim oLim) => CocompleteCategory c m o cLim mLim oLim cIndex mIndex oIndex | c -> m, m -> o, cLim -> mLim, mLim -> oLim, c cIndex mIndex oIndex -> cLim where
- colimit :: (FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq cIndex, Eq mIndex, Eq oIndex) => Diagram cIndex mIndex oIndex c m o -> Cocone cIndex mIndex oIndex cLim mLim oLim
- coprojectBase :: Diagram cIndex mIndex oIndex c m o -> Diagram c m o cLim mLim oLim
- uncoprojectBase :: CocompleteCategory c m o cLim mLim oLim cIndex mIndex oIndex => Diagram cIndex mIndex oIndex c m o -> Diagram cLim mLim oLim c m o
Colimit type
For a Category
parametrized over a type t, the apex of the colimit of a diagram indexed by a category parametrized over a type i will contain Coproduct
constructions. A given distinguished element can be constructed from a Coprojection
at a given index.
For example, in FinSet
, let's consider a discrete diagram from DiscreteTwo
to (FinSet
Int) which selects {1,2} and {3,4}. The nadir of the colimit is obviously {(A
,1),(A
,2),(B
,3),(B
,4)}, note that it is not an object of (Finset
Int) but an object of (FinSet
(DiscreteTwoOb,Int)). The Colimit
type allows to construct type (FinSet
(Colimit
DiscreteTwo
Int)) in which we can consider the original objects with Coprojection
and the new distinguished elements with Coproduct
. Thus, the colimit will be {Coproduct A
1,Coproduct A
2,Coproduct B
3,Coproduct B
4}. We can construct coprojections in the same category, for example along A
, which will map (Coprojection
1) to Coproduct
A
1.
Constructors
Coprojection t | A |
CoproductElement i t | A |
Instances
(Eq a, Eq oIndex) => HasCoproducts (FinSet a) (Function a) (Set a) (FinSet (Colimit oIndex a)) (Function (Colimit oIndex a)) (Set (Colimit oIndex a)) oIndex Source # | |
Defined in Math.Categories.FinSet Methods coproduct :: Diagram (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinSet a) (Function a) (Set a) -> Cocone (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinSet (Colimit oIndex a)) (Function (Colimit oIndex a)) (Set (Colimit oIndex a)) Source # | |
(Eq a, Eq mIndex, Eq oIndex) => CocompleteCategory (FinSet a) (Function a) (Set a) (FinSet (Colimit oIndex a)) (Function (Colimit oIndex a)) (Set (Colimit oIndex a)) cIndex mIndex oIndex Source # | |
Defined in Math.Categories.FinSet Methods colimit :: Diagram cIndex mIndex oIndex (FinSet a) (Function a) (Set a) -> Cocone cIndex mIndex oIndex (FinSet (Colimit oIndex a)) (Function (Colimit oIndex a)) (Set (Colimit oIndex a)) Source # coprojectBase :: Diagram cIndex mIndex oIndex (FinSet a) (Function a) (Set a) -> Diagram (FinSet a) (Function a) (Set a) (FinSet (Colimit oIndex a)) (Function (Colimit oIndex a)) (Set (Colimit oIndex a)) Source # | |
(PrettyPrint i, PrettyPrint t, Eq i) => PrettyPrint (Colimit i t) Source # | |
Defined in Math.CocompleteCategory | |
(Simplifiable t, Simplifiable i) => Simplifiable (Colimit i t) Source # | |
Defined in Math.CocompleteCategory | |
Generic (Colimit i t) Source # | |
(Show i, Show t) => Show (Colimit i t) Source # | |
(Eq i, Eq t) => Eq (Colimit i t) Source # | |
(Eq n, Eq e, Eq oIndex) => HasCoproducts (FinGrph n e) (GraphHomomorphism n e) (Graph n e) (FinGrph (Colimit oIndex n) (Colimit oIndex e)) (GraphHomomorphism (Colimit oIndex n) (Colimit oIndex e)) (Graph (Colimit oIndex n) (Colimit oIndex e)) oIndex Source # | |
Defined in Math.Categories.FinGrph Methods coproduct :: Diagram (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinGrph n e) (GraphHomomorphism n e) (Graph n e) -> Cocone (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinGrph (Colimit oIndex n) (Colimit oIndex e)) (GraphHomomorphism (Colimit oIndex n) (Colimit oIndex e)) (Graph (Colimit oIndex n) (Colimit oIndex e)) Source # | |
(Eq e, Eq n, Eq mIndex, Eq oIndex) => CocompleteCategory (FinGrph n e) (GraphHomomorphism n e) (Graph n e) (FinGrph (Colimit oIndex n) (Colimit oIndex e)) (GraphHomomorphism (Colimit oIndex n) (Colimit oIndex e)) (Graph (Colimit oIndex n) (Colimit oIndex e)) cIndex mIndex oIndex Source # | |
Defined in Math.Categories.FinGrph Methods colimit :: Diagram cIndex mIndex oIndex (FinGrph n e) (GraphHomomorphism n e) (Graph n e) -> Cocone cIndex mIndex oIndex (FinGrph (Colimit oIndex n) (Colimit oIndex e)) (GraphHomomorphism (Colimit oIndex n) (Colimit oIndex e)) (Graph (Colimit oIndex n) (Colimit oIndex e)) Source # coprojectBase :: Diagram cIndex mIndex oIndex (FinGrph n e) (GraphHomomorphism n e) (Graph n e) -> Diagram (FinGrph n e) (GraphHomomorphism n e) (Graph n e) (FinGrph (Colimit oIndex n) (Colimit oIndex e)) (GraphHomomorphism (Colimit oIndex n) (Colimit oIndex e)) (Graph (Colimit oIndex n) (Colimit oIndex e)) Source # | |
(Eq e, Eq n, Eq oIndex, Eq mIndex, Morphism mIndex oIndex, FiniteCategory cIndex mIndex oIndex) => CocompleteCategory (FinSketch n e) (SketchMorphism n e) (Sketch n e) (FinSketch (Colimit oIndex n) (Colimit oIndex e)) (SketchMorphism (Colimit oIndex n) (Colimit oIndex e)) (Sketch (Colimit oIndex n) (Colimit oIndex e)) cIndex mIndex oIndex Source # | |
Defined in Math.Categories.FinSketch Methods colimit :: Diagram cIndex mIndex oIndex (FinSketch n e) (SketchMorphism n e) (Sketch n e) -> Cocone cIndex mIndex oIndex (FinSketch (Colimit oIndex n) (Colimit oIndex e)) (SketchMorphism (Colimit oIndex n) (Colimit oIndex e)) (Sketch (Colimit oIndex n) (Colimit oIndex e)) Source # coprojectBase :: Diagram cIndex mIndex oIndex (FinSketch n e) (SketchMorphism n e) (Sketch n e) -> Diagram (FinSketch n e) (SketchMorphism n e) (Sketch n e) (FinSketch (Colimit oIndex n) (Colimit oIndex e)) (SketchMorphism (Colimit oIndex n) (Colimit oIndex e)) (Sketch (Colimit oIndex n) (Colimit oIndex e)) Source # | |
(FiniteCategory c m o, Morphism m o, Eq c, Eq m, Eq o, FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq oIndex, Eq mIndex) => CocompleteCategory (FinCat c m o) (FinFunctor c m o) c (FinCat (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (FinFunctor (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) cIndex mIndex oIndex Source # | Note that computing a |
Defined in Math.FiniteCategories.ColimitCategory Methods colimit :: Diagram cIndex mIndex oIndex (FinCat c m o) (FinFunctor c m o) c -> Cocone cIndex mIndex oIndex (FinCat (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (FinFunctor (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) Source # coprojectBase :: Diagram cIndex mIndex oIndex (FinCat c m o) (FinFunctor c m o) c -> Diagram (FinCat c m o) (FinFunctor c m o) c (FinCat (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (FinFunctor (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) Source # | |
(Eq e, Eq n, Eq oIndex) => HasCoproducts (FinCat (CompositionGraph n e) (CGMorphism n e) n) (FinFunctor (CompositionGraph n e) (CGMorphism n e) n) (CompositionGraph n e) (FinCat (CompositionGraph (Colimit oIndex n) (Colimit oIndex e)) (CGMorphism (Colimit oIndex n) (Colimit oIndex e)) (Colimit oIndex n)) (FinFunctor (CompositionGraph (Colimit oIndex n) (Colimit oIndex e)) (CGMorphism (Colimit oIndex n) (Colimit oIndex e)) (Colimit oIndex n)) (CompositionGraph (Colimit oIndex n) (Colimit oIndex e)) oIndex Source # | |
Defined in Math.FiniteCategories.ColimitCategory Methods coproduct :: Diagram (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinCat (CompositionGraph n e) (CGMorphism n e) n) (FinFunctor (CompositionGraph n e) (CGMorphism n e) n) (CompositionGraph n e) -> Cocone (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinCat (CompositionGraph (Colimit oIndex n) (Colimit oIndex e)) (CGMorphism (Colimit oIndex n) (Colimit oIndex e)) (Colimit oIndex n)) (FinFunctor (CompositionGraph (Colimit oIndex n) (Colimit oIndex e)) (CGMorphism (Colimit oIndex n) (Colimit oIndex e)) (Colimit oIndex n)) (CompositionGraph (Colimit oIndex n) (Colimit oIndex e)) Source # | |
type Rep (Colimit i t) Source # | |
Defined in Math.CocompleteCategory type Rep (Colimit i t) = D1 ('MetaData "Colimit" "Math.CocompleteCategory" "FiniteCategories-0.6.5.1-inplace" 'False) (C1 ('MetaCons "Coprojection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 t)) :+: C1 ('MetaCons "CoproductElement" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 i) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 t))) |
uncoproject :: Colimit oIndex t -> t Source #
Remove the constructor Coprojection
from an original object t, throws an error if a CoproductElement
is given.
Helper typeclasses to define a CocompleteCategory
class (Category c m o, Morphism m o, Category cLim mLim oLim, Morphism mLim oLim) => HasCoproducts c m o cLim mLim oLim oIndex | c -> m, m -> o, cLim -> mLim, mLim -> oLim, c oIndex -> cLim where Source #
The typeclass of categories which have all coproducts.
Methods
coproduct :: Diagram (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex c m o -> Cocone (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex cLim mLim oLim Source #
Given a discreteDiagram
selecting objects, return the coproduct of the selected objects as a Cocone
.
Instances
class (Category c m o, Morphism m o) => HasCoequalizers c m o | c -> m, m -> o where Source #
The typeclass of categories which have all coequalizers.
Methods
coequalize :: Diagram Parallel ParallelAr ParallelOb c m o -> Cocone Parallel ParallelAr ParallelOb c m o Source #
Given a parallelDiagram
selecting arrows, return the coequalizer of the selected arrows as a Cocone
.
Instances
colimitFromCoproductsAndCoequalizers :: (Category c m o, Morphism m o, Category cLim mLim oLim, Morphism mLim oLim, HasCoproducts c m o cLim mLim oLim oIndex, HasCoequalizers cLim mLim oLim, FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq oIndex, Eq mIndex, Eq cIndex) => (m -> mLim) -> Diagram cIndex mIndex oIndex c m o -> Cocone cIndex mIndex oIndex cLim mLim oLim Source #
Computes efficiently colimits thanks to coproducts and coequalizers. Can be used to instantiate CocompleteCategory
.
The first argument is a function to transform an object of the original category into a colimit object.
Most of the time, the original category takes one type parameter and the function uses Coprojection
, when the category does not take any type parameter it is id
.
For example, for FinSet
, the function has to transform a function {1 -> 2} to the function {Coprojection 1 -> Coprojection 2}.
Cocomplete Category
class (Category c m o, Morphism m o, Category cLim mLim oLim, Morphism mLim oLim) => CocompleteCategory c m o cLim mLim oLim cIndex mIndex oIndex | c -> m, m -> o, cLim -> mLim, mLim -> oLim, c cIndex mIndex oIndex -> cLim where Source #
The typeclass of categories which have all colimits.
Methods
colimit :: (FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq cIndex, Eq mIndex, Eq oIndex) => Diagram cIndex mIndex oIndex c m o -> Cocone cIndex mIndex oIndex cLim mLim oLim Source #
Return the colimit of a Diagram
.
coprojectBase :: Diagram cIndex mIndex oIndex c m o -> Diagram c m o cLim mLim oLim Source #
Instances
(Enum a, Ord a, Eq mIndex, Eq oIndex) => CocompleteCategory (OrdinalCategory a) (IsSmallerThan a) a (OrdinalCategory a) (IsSmallerThan a) a cIndex mIndex oIndex Source # | |
Defined in Math.Categories.OrdinalCategory Methods colimit :: Diagram cIndex mIndex oIndex (OrdinalCategory a) (IsSmallerThan a) a -> Cocone cIndex mIndex oIndex (OrdinalCategory a) (IsSmallerThan a) a Source # coprojectBase :: Diagram cIndex mIndex oIndex (OrdinalCategory a) (IsSmallerThan a) a -> Diagram (OrdinalCategory a) (IsSmallerThan a) a (OrdinalCategory a) (IsSmallerThan a) a Source # | |
(Ord a, Eq mIndex, Eq oIndex) => CocompleteCategory (TotalOrder a) (IsSmallerThan a) a (TotalOrder a) (IsSmallerThan a) a cIndex mIndex oIndex Source # | |
Defined in Math.Categories.TotalOrder Methods colimit :: Diagram cIndex mIndex oIndex (TotalOrder a) (IsSmallerThan a) a -> Cocone cIndex mIndex oIndex (TotalOrder a) (IsSmallerThan a) a Source # coprojectBase :: Diagram cIndex mIndex oIndex (TotalOrder a) (IsSmallerThan a) a -> Diagram (TotalOrder a) (IsSmallerThan a) a (TotalOrder a) (IsSmallerThan a) a Source # | |
(Eq a, Eq mIndex, Eq oIndex) => CocompleteCategory (FinSet a) (Function a) (Set a) (FinSet (Colimit oIndex a)) (Function (Colimit oIndex a)) (Set (Colimit oIndex a)) cIndex mIndex oIndex Source # | |
Defined in Math.Categories.FinSet Methods colimit :: Diagram cIndex mIndex oIndex (FinSet a) (Function a) (Set a) -> Cocone cIndex mIndex oIndex (FinSet (Colimit oIndex a)) (Function (Colimit oIndex a)) (Set (Colimit oIndex a)) Source # coprojectBase :: Diagram cIndex mIndex oIndex (FinSet a) (Function a) (Set a) -> Diagram (FinSet a) (Function a) (Set a) (FinSet (Colimit oIndex a)) (Function (Colimit oIndex a)) (Set (Colimit oIndex a)) Source # | |
(Eq e, Eq n, Eq mIndex, Eq oIndex) => CocompleteCategory (FinGrph n e) (GraphHomomorphism n e) (Graph n e) (FinGrph (Colimit oIndex n) (Colimit oIndex e)) (GraphHomomorphism (Colimit oIndex n) (Colimit oIndex e)) (Graph (Colimit oIndex n) (Colimit oIndex e)) cIndex mIndex oIndex Source # | |
Defined in Math.Categories.FinGrph Methods colimit :: Diagram cIndex mIndex oIndex (FinGrph n e) (GraphHomomorphism n e) (Graph n e) -> Cocone cIndex mIndex oIndex (FinGrph (Colimit oIndex n) (Colimit oIndex e)) (GraphHomomorphism (Colimit oIndex n) (Colimit oIndex e)) (Graph (Colimit oIndex n) (Colimit oIndex e)) Source # coprojectBase :: Diagram cIndex mIndex oIndex (FinGrph n e) (GraphHomomorphism n e) (Graph n e) -> Diagram (FinGrph n e) (GraphHomomorphism n e) (Graph n e) (FinGrph (Colimit oIndex n) (Colimit oIndex e)) (GraphHomomorphism (Colimit oIndex n) (Colimit oIndex e)) (Graph (Colimit oIndex n) (Colimit oIndex e)) Source # | |
(Eq e, Eq n, Eq oIndex, Eq mIndex, Morphism mIndex oIndex, FiniteCategory cIndex mIndex oIndex) => CocompleteCategory (FinSketch n e) (SketchMorphism n e) (Sketch n e) (FinSketch (Colimit oIndex n) (Colimit oIndex e)) (SketchMorphism (Colimit oIndex n) (Colimit oIndex e)) (Sketch (Colimit oIndex n) (Colimit oIndex e)) cIndex mIndex oIndex Source # | |
Defined in Math.Categories.FinSketch Methods colimit :: Diagram cIndex mIndex oIndex (FinSketch n e) (SketchMorphism n e) (Sketch n e) -> Cocone cIndex mIndex oIndex (FinSketch (Colimit oIndex n) (Colimit oIndex e)) (SketchMorphism (Colimit oIndex n) (Colimit oIndex e)) (Sketch (Colimit oIndex n) (Colimit oIndex e)) Source # coprojectBase :: Diagram cIndex mIndex oIndex (FinSketch n e) (SketchMorphism n e) (Sketch n e) -> Diagram (FinSketch n e) (SketchMorphism n e) (Sketch n e) (FinSketch (Colimit oIndex n) (Colimit oIndex e)) (SketchMorphism (Colimit oIndex n) (Colimit oIndex e)) (Sketch (Colimit oIndex n) (Colimit oIndex e)) Source # | |
(FiniteCategory c m o, Morphism m o, Eq c, Eq m, Eq o, FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq oIndex, Eq mIndex) => CocompleteCategory (FinCat c m o) (FinFunctor c m o) c (FinCat (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (FinFunctor (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) cIndex mIndex oIndex Source # | Note that computing a |
Defined in Math.FiniteCategories.ColimitCategory Methods colimit :: Diagram cIndex mIndex oIndex (FinCat c m o) (FinFunctor c m o) c -> Cocone cIndex mIndex oIndex (FinCat (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (FinFunctor (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) Source # coprojectBase :: Diagram cIndex mIndex oIndex (FinCat c m o) (FinFunctor c m o) c -> Diagram (FinCat c m o) (FinFunctor c m o) c (FinCat (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (FinFunctor (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) (CGMorphism (Colimit oIndex o) (Colimit oIndex m)) (Colimit oIndex o)) (CompositionGraph (Colimit oIndex o) (Colimit oIndex m)) Source # |
uncoprojectBase :: CocompleteCategory c m o cLim mLim oLim cIndex mIndex oIndex => Diagram cIndex mIndex oIndex c m o -> Diagram cLim mLim oLim c m o Source #