FiniteCategories-0.6.4.0: Finite categories and usual categorical constructions on them.
CopyrightGuillaume Sabbagh 2022
LicenseGPL-3
Maintainerguillaumesabbagh@protonmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.FiniteCategories.LimitCategory

Description

A LimitCategory is the category in which the limit of a diagram in FinCat lives. To compute limits in a usual category, see Math.CompleteCategory. To compute limits in a custom FiniteCategory, see limits in Math.ConeCategory.

Synopsis

Limit category

data LimitCategory cIndex mIndex oIndex c m o Source #

A LimitCategory is either a ProjectedCategory (an original category) or a LimitCategory.

Constructors

ProjectedCategory c

An original category in FinCat with the indexing object of the category.

LimitCategory (Diagram cIndex mIndex oIndex (FinCat c m o) (FinFunctor c m o) c)

The limit category of a given Diagram.

Instances

Instances details
(FiniteCategory c m o, Morphism m o, Eq c, Eq m, Eq o, FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq cIndex, Eq mIndex, Eq oIndex) => CompleteCategory (FinCat c m o) (FinFunctor c m o) c (FinCat (LimitCategory cIndex mIndex oIndex c m o) (Limit oIndex m) (Limit oIndex o)) (FinFunctor (LimitCategory cIndex mIndex oIndex c m o) (Limit oIndex m) (Limit oIndex o)) (LimitCategory cIndex mIndex oIndex c m o) cIndex mIndex oIndex Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Methods

limit :: Diagram cIndex mIndex oIndex (FinCat c m o) (FinFunctor c m o) c -> Cone cIndex mIndex oIndex (FinCat (LimitCategory cIndex mIndex oIndex c m o) (Limit oIndex m) (Limit oIndex o)) (FinFunctor (LimitCategory cIndex mIndex oIndex c m o) (Limit oIndex m) (Limit oIndex o)) (LimitCategory cIndex mIndex oIndex c m o) Source #

projectBase :: Diagram cIndex mIndex oIndex (FinCat c m o) (FinFunctor c m o) c -> Diagram (FinCat c m o) (FinFunctor c m o) c (FinCat (LimitCategory cIndex mIndex oIndex c m o) (Limit oIndex m) (Limit oIndex o)) (FinFunctor (LimitCategory cIndex mIndex oIndex c m o) (Limit oIndex m) (Limit oIndex o)) (LimitCategory cIndex mIndex oIndex c m o) Source #

(PrettyPrint c, PrettyPrint cIndex, PrettyPrint oIndex, PrettyPrint mIndex, PrettyPrint o, PrettyPrint m, Eq o, Eq m, Eq oIndex, Eq c, Eq mIndex, FiniteCategory c m o, Morphism m o) => PrettyPrint (LimitCategory cIndex mIndex oIndex c m o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Methods

pprint :: Int -> LimitCategory cIndex mIndex oIndex c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> LimitCategory cIndex mIndex oIndex c m o -> String Source #

pprintIndent :: Int -> LimitCategory cIndex mIndex oIndex c m o -> String Source #

(Simplifiable c, Simplifiable cIndex, Simplifiable oIndex, Simplifiable mIndex, Simplifiable o, Simplifiable m, Eq o, Eq m, Eq oIndex, Eq mIndex) => Simplifiable (LimitCategory cIndex mIndex oIndex c m o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Methods

simplify :: LimitCategory cIndex mIndex oIndex c m o -> LimitCategory cIndex mIndex oIndex c m o #

Generic (LimitCategory cIndex mIndex oIndex c m o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Associated Types

type Rep (LimitCategory cIndex mIndex oIndex c m o) :: Type -> Type

Methods

from :: LimitCategory cIndex mIndex oIndex c m o -> Rep (LimitCategory cIndex mIndex oIndex c m o) x

to :: Rep (LimitCategory cIndex mIndex oIndex c m o) x -> LimitCategory cIndex mIndex oIndex c m o

(Show c, Show cIndex, Show oIndex, Show mIndex, Show o, Show m) => Show (LimitCategory cIndex mIndex oIndex c m o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Methods

showsPrec :: Int -> LimitCategory cIndex mIndex oIndex c m o -> ShowS

show :: LimitCategory cIndex mIndex oIndex c m o -> String

showList :: [LimitCategory cIndex mIndex oIndex c m o] -> ShowS

(Eq c, Eq cIndex, Eq mIndex, Eq oIndex, Eq m, Eq o, FiniteCategory c m o, FiniteCategory cIndex mIndex oIndex, Morphism m o, Morphism mIndex oIndex) => Eq (LimitCategory cIndex mIndex oIndex c m o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Methods

(==) :: LimitCategory cIndex mIndex oIndex c m o -> LimitCategory cIndex mIndex oIndex c m o -> Bool

(/=) :: LimitCategory cIndex mIndex oIndex c m o -> LimitCategory cIndex mIndex oIndex c m o -> Bool

(FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq mIndex, Eq oIndex, Category c m o, Morphism m o, Eq m, Eq o) => Category (LimitCategory cIndex mIndex oIndex c m o) (Limit oIndex m) (Limit oIndex o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Methods

identity :: LimitCategory cIndex mIndex oIndex c m o -> Limit oIndex o -> Limit oIndex m Source #

ar :: LimitCategory cIndex mIndex oIndex c m o -> Limit oIndex o -> Limit oIndex o -> Set (Limit oIndex m) Source #

genAr :: LimitCategory cIndex mIndex oIndex c m o -> Limit oIndex o -> Limit oIndex o -> Set (Limit oIndex m) Source #

decompose :: LimitCategory cIndex mIndex oIndex c m o -> Limit oIndex m -> [Limit oIndex m] Source #

(FiniteCategory cIndex mIndex oIndex, Morphism mIndex oIndex, Eq mIndex, Eq oIndex, FiniteCategory c m o, Morphism m o, Eq m, Eq o) => FiniteCategory (LimitCategory cIndex mIndex oIndex c m o) (Limit oIndex m) (Limit oIndex o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

Methods

ob :: LimitCategory cIndex mIndex oIndex c m o -> Set (Limit oIndex o) Source #

type Rep (LimitCategory cIndex mIndex oIndex c m o) Source # 
Instance details

Defined in Math.FiniteCategories.LimitCategory

type Rep (LimitCategory cIndex mIndex oIndex c m o) = D1 ('MetaData "LimitCategory" "Math.FiniteCategories.LimitCategory" "FiniteCategories-0.6.4.0-inplace" 'False) (C1 ('MetaCons "ProjectedCategory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c)) :+: C1 ('MetaCons "LimitCategory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Diagram cIndex mIndex oIndex (FinCat c m o) (FinFunctor c m o) c))))

Orphan instances

(Morphism m o, Eq m, Eq oIndex) => Morphism (Limit oIndex m) (Limit oIndex o) Source # 
Instance details

Methods

(@) :: Limit oIndex m -> Limit oIndex m -> Limit oIndex m Source #

(@?) :: Limit oIndex m -> Limit oIndex m -> Maybe (Limit oIndex m) Source #

source :: Limit oIndex m -> Limit oIndex o Source #

target :: Limit oIndex m -> Limit oIndex o Source #