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.Categories.FinSet

Description

The FinSet category has finite sets as objects and functions as morphisms.

Finite sets are represented by weak sets from Data.WeakSet and functions by enriched weak maps from Data.WeakMap.

These structures are homogeneous, meaning you can only have sets containing one type of objects in a given FinSet category.

See the category PureSet for the category of sets which can be arbitrarily nested.

Synopsis

Function

data Function a Source #

A Function (finite function) is a weak map enriched with a codomain.

We have to store the codomain to retrieve the target set of a morphism in FinSet.

Constructors

Function 

Fields

Instances

Instances details
(PrettyPrint a, Eq a) => PrettyPrint (Function a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

pprint :: Int -> Function a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> Function a -> String Source #

pprintIndent :: Int -> Function a -> String Source #

(Simplifiable a, Eq a) => Simplifiable (Function a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

simplify :: Function a -> Function a #

Generic (Function a) Source # 
Instance details

Defined in Math.Categories.FinSet

Associated Types

type Rep (Function a) :: Type -> Type

Methods

from :: Function a -> Rep (Function a) x

to :: Rep (Function a) x -> Function a

Show a => Show (Function a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

showsPrec :: Int -> Function a -> ShowS

show :: Function a -> String

showList :: [Function a] -> ShowS

Eq a => Eq (Function a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

(==) :: Function a -> Function a -> Bool

(/=) :: Function a -> Function a -> Bool

Eq a => Morphism (Function a) (Set a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

(@) :: Function a -> Function a -> Function a Source #

(@?) :: Function a -> Function a -> Maybe (Function a) Source #

source :: Function a -> Set a Source #

target :: Function a -> Set a Source #

Eq a => Category (FinSet a) (Function a) (Set a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

identity :: FinSet a -> Set a -> Function a Source #

ar :: FinSet a -> Set a -> Set a -> Set (Function a) Source #

genAr :: FinSet a -> Set a -> Set a -> Set (Function a) Source #

decompose :: FinSet a -> Function a -> [Function a] Source #

Eq a => HasCoequalizers (FinSet a) (Function a) (Set a) Source # 
Instance details

Defined in Math.Categories.FinSet

Eq a => HasEqualizers (FinSet a) (Function a) (Set a) Source # 
Instance details

Defined in Math.Categories.FinSet

(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 # 
Instance details

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 oIndex) => HasProducts (FinSet a) (Function a) (Set a) (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit oIndex a)) oIndex Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

product :: Diagram (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinSet a) (Function a) (Set a) -> Cone (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit 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 # 
Instance details

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 a, Eq mIndex, Eq oIndex) => CompleteCategory (FinSet a) (Function a) (Set a) (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit oIndex a)) cIndex mIndex oIndex Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

limit :: Diagram cIndex mIndex oIndex (FinSet a) (Function a) (Set a) -> Cone cIndex mIndex oIndex (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit oIndex a)) Source #

projectBase :: Diagram cIndex mIndex oIndex (FinSet a) (Function a) (Set a) -> Diagram (FinSet a) (Function a) (Set a) (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit oIndex a)) Source #

Eq a => CartesianClosedCategory (FinSet a) (Function a) (Set a) (FinSet (TwoProduct a)) (Function (TwoProduct a)) (Set (TwoProduct a)) (FinSet (Cartesian a)) (Function (Cartesian a)) (Set (Cartesian a)) Source # 
Instance details

Defined in Math.Categories.FinSet

type Rep (Function a) Source # 
Instance details

Defined in Math.Categories.FinSet

type Rep (Function a) = D1 ('MetaData "Function" "Math.Categories.FinSet" "FiniteCategories-0.6.4.0-inplace" 'False) (C1 ('MetaCons "Function" 'PrefixI 'True) (S1 ('MetaSel ('Just "function") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map a a)) :*: S1 ('MetaSel ('Just "codomain") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set a))))

(||!||) :: Eq a => Function a -> a -> a Source #

A function to apply a Function to an object in the domain of the Function.

FinSet

data FinSet a Source #

FinSet is the category of finite sets.

Constructors

FinSet 

Instances

Instances details
PrettyPrint (FinSet a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

pprint :: Int -> FinSet a -> String Source #

pprintWithIndentations :: Int -> Int -> String -> FinSet a -> String Source #

pprintIndent :: Int -> FinSet a -> String Source #

Simplifiable (FinSet a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

simplify :: FinSet a -> FinSet a #

Generic (FinSet a) Source # 
Instance details

Defined in Math.Categories.FinSet

Associated Types

type Rep (FinSet a) :: Type -> Type

Methods

from :: FinSet a -> Rep (FinSet a) x

to :: Rep (FinSet a) x -> FinSet a

Show (FinSet a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

showsPrec :: Int -> FinSet a -> ShowS

show :: FinSet a -> String

showList :: [FinSet a] -> ShowS

Eq (FinSet a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

(==) :: FinSet a -> FinSet a -> Bool

(/=) :: FinSet a -> FinSet a -> Bool

Eq a => Category (FinSet a) (Function a) (Set a) Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

identity :: FinSet a -> Set a -> Function a Source #

ar :: FinSet a -> Set a -> Set a -> Set (Function a) Source #

genAr :: FinSet a -> Set a -> Set a -> Set (Function a) Source #

decompose :: FinSet a -> Function a -> [Function a] Source #

Eq a => HasCoequalizers (FinSet a) (Function a) (Set a) Source # 
Instance details

Defined in Math.Categories.FinSet

Eq a => HasEqualizers (FinSet a) (Function a) (Set a) Source # 
Instance details

Defined in Math.Categories.FinSet

(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 # 
Instance details

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 oIndex) => HasProducts (FinSet a) (Function a) (Set a) (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit oIndex a)) oIndex Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

product :: Diagram (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinSet a) (Function a) (Set a) -> Cone (DiscreteCategory oIndex) (DiscreteMorphism oIndex) oIndex (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit 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 # 
Instance details

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 a, Eq mIndex, Eq oIndex) => CompleteCategory (FinSet a) (Function a) (Set a) (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit oIndex a)) cIndex mIndex oIndex Source # 
Instance details

Defined in Math.Categories.FinSet

Methods

limit :: Diagram cIndex mIndex oIndex (FinSet a) (Function a) (Set a) -> Cone cIndex mIndex oIndex (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit oIndex a)) Source #

projectBase :: Diagram cIndex mIndex oIndex (FinSet a) (Function a) (Set a) -> Diagram (FinSet a) (Function a) (Set a) (FinSet (Limit oIndex a)) (Function (Limit oIndex a)) (Set (Limit oIndex a)) Source #

Eq a => CartesianClosedCategory (FinSet a) (Function a) (Set a) (FinSet (TwoProduct a)) (Function (TwoProduct a)) (Set (TwoProduct a)) (FinSet (Cartesian a)) (Function (Cartesian a)) (Set (Cartesian a)) Source # 
Instance details

Defined in Math.Categories.FinSet

type Rep (FinSet a) Source # 
Instance details

Defined in Math.Categories.FinSet

type Rep (FinSet a) = D1 ('MetaData "FinSet" "Math.Categories.FinSet" "FiniteCategories-0.6.4.0-inplace" 'False) (C1 ('MetaCons "FinSet" 'PrefixI 'False) (U1 :: Type -> Type))