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.FullSubcategory

Description

Selecting a FullSubcategory in a Category yields a FiniteCategory.

We have to forget the generating set of morphisms of the original Category as the generators are not always inheritable (see for example the full subcategory of Square containing the objects A and D).

If the generators are inheritable, you can use the constructor InheritedFullSubcategory to inherit the generators of the original Category.

Synopsis

Documentation

data FullSubcategory c m o Source #

A FullSubcategory needs an original category and a set of objects to select in the category.

The generators are forgotten, use InheritedFullSubcategory if the generators are inheritable.

Constructors

FullSubcategory c (Set o) 

Instances

Instances details
(PrettyPrint c, PrettyPrint o, Eq o) => PrettyPrint (FullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

pprint :: Int -> FullSubcategory c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FullSubcategory c m o -> String Source #

pprintIndent :: Int -> FullSubcategory c m o -> String Source #

(Simplifiable c, Simplifiable o, Eq o) => Simplifiable (FullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

simplify :: FullSubcategory c m o -> FullSubcategory c m o #

Generic (FullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Associated Types

type Rep (FullSubcategory c m o) :: Type -> Type

Methods

from :: FullSubcategory c m o -> Rep (FullSubcategory c m o) x

to :: Rep (FullSubcategory c m o) x -> FullSubcategory c m o

(Show c, Show o) => Show (FullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

showsPrec :: Int -> FullSubcategory c m o -> ShowS

show :: FullSubcategory c m o -> String

showList :: [FullSubcategory c m o] -> ShowS

(Eq c, Eq o) => Eq (FullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

(==) :: FullSubcategory c m o -> FullSubcategory c m o -> Bool

(/=) :: FullSubcategory c m o -> FullSubcategory c m o -> Bool

(Category c m o, Eq o) => Category (FullSubcategory c m o) m o Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

identity :: FullSubcategory c m o -> o -> m Source #

ar :: FullSubcategory c m o -> o -> o -> Set m Source #

genAr :: FullSubcategory c m o -> o -> o -> Set m Source #

decompose :: FullSubcategory c m o -> m -> [m] Source #

(Category c m o, Eq o) => FiniteCategory (FullSubcategory c m o) m o Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

ob :: FullSubcategory c m o -> Set o Source #

type Rep (FullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

type Rep (FullSubcategory c m o) = D1 ('MetaData "FullSubcategory" "Math.FiniteCategories.FullSubcategory" "FiniteCategories-0.6.4.0-inplace" 'False) (C1 ('MetaCons "FullSubcategory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set o))))

data InheritedFullSubcategory c m o Source #

An InheritedFullSubcategory is a FullSubcategory where the generators are the same as in the original Category.

Constructors

InheritedFullSubcategory c (Set o) 

Instances

Instances details
(PrettyPrint c, PrettyPrint o, Eq o) => PrettyPrint (InheritedFullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

pprint :: Int -> InheritedFullSubcategory c m o -> String Source #

pprintWithIndentations :: Int -> Int -> String -> InheritedFullSubcategory c m o -> String Source #

pprintIndent :: Int -> InheritedFullSubcategory c m o -> String Source #

(Simplifiable c, Simplifiable o, Eq o) => Simplifiable (InheritedFullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Generic (InheritedFullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Associated Types

type Rep (InheritedFullSubcategory c m o) :: Type -> Type

(Show c, Show o) => Show (InheritedFullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

showsPrec :: Int -> InheritedFullSubcategory c m o -> ShowS

show :: InheritedFullSubcategory c m o -> String

showList :: [InheritedFullSubcategory c m o] -> ShowS

(Eq c, Eq o) => Eq (InheritedFullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

(Category c m o, Eq o) => Category (InheritedFullSubcategory c m o) m o Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

identity :: InheritedFullSubcategory c m o -> o -> m Source #

ar :: InheritedFullSubcategory c m o -> o -> o -> Set m Source #

genAr :: InheritedFullSubcategory c m o -> o -> o -> Set m Source #

decompose :: InheritedFullSubcategory c m o -> m -> [m] Source #

(Category c m o, Eq o) => FiniteCategory (InheritedFullSubcategory c m o) m o Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

Methods

ob :: InheritedFullSubcategory c m o -> Set o Source #

type Rep (InheritedFullSubcategory c m o) Source # 
Instance details

Defined in Math.FiniteCategories.FullSubcategory

type Rep (InheritedFullSubcategory c m o) = D1 ('MetaData "InheritedFullSubcategory" "Math.FiniteCategories.FullSubcategory" "FiniteCategories-0.6.4.0-inplace" 'False) (C1 ('MetaCons "InheritedFullSubcategory" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 c) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set o))))