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

Diagram.Diagram

Description

A diagram is a heterogeneous FinFunctor, it is a shift of perspective : we view the functor not as a morphism of categories but as a selection in a category.

By heterogeneous, we mean that the type of the source category may be different from the target category.

To convert a Diagram into any other kind of functor, see Diagram.Conversion.

To enumerate all diagrams between two categories, see the ob function of FunctorCategory.

Synopsis

Diagram typeclass and useful functions

data Diagram c1 m1 o1 c2 m2 o2 Source #

A diagram is a heterogeneous FinFunctor F, it is a shift of perspective : we view the FinFunctor not as a morphism of categories but as a selection in a category. It must obey the following rules :

F (src f) = src (F f)
F (tgt f) = tgt (F f)
F (f @ g) = F(f) @ F(g)
F (identity a) = identity (F a)

Unlike FinFunctor, a Diagram can have a source category and a target category with different types.

Using constructor functions mkDiagram, mkConstantDiagram, mkDiscreteDiagram, mkSelect0, mkSelect1, mkSelect2, mkSelect3, mkTriangle and mkParallel is the safe way to instantiate a Diagram (FinFunctoriality is checked during construction).

Therefore, if you want to construct an arbitrary diagram, use the constructor function mkDiagram unless it is too long to check FinFunctoriality in which case you should use the Diagram constructor. It is then your responsability to ensure the FinFunctoriality property is verified.

Constructors

Diagram 

Fields

Instances

Instances details
(Eq c1, Eq c2, Eq o1, Eq o2, Eq m1, Eq m2) => Eq (Diagram c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in Diagram.Diagram

Methods

(==) :: Diagram c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 -> Bool

(/=) :: Diagram c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 -> Bool

(Show c1, Show c2, Show o1, Show o2, Show m1, Show m2) => Show (Diagram c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in Diagram.Diagram

Methods

showsPrec :: Int -> Diagram c1 m1 o1 c2 m2 o2 -> ShowS

show :: Diagram c1 m1 o1 c2 m2 o2 -> String

showList :: [Diagram c1 m1 o1 c2 m2 o2] -> ShowS

(FiniteCategory c1 m1 o1, Morphism m1 o1, PrettyPrintable m1, PrettyPrintable o1, Eq m1, Eq o1, PrettyPrintable c1, FiniteCategory c2 m2 o2, Morphism m2 o2, PrettyPrintable m2, PrettyPrintable o2, PrettyPrintable c2) => PrettyPrintable (Diagram c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in Diagram.Diagram

Methods

pprint :: Diagram c1 m1 o1 c2 m2 o2 -> String Source #

(FiniteCategory c1 m1 o1, Morphism m1 o1, Eq c1, Eq m1, Eq o1, FiniteCategory c2 m2 o2, Morphism m2 o2, Eq c2, Eq m2, Eq o2) => Morphism (NaturalTransformation c1 m1 o1 c2 m2 o2) (Diagram c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in FunctorCategory.FunctorCategory

Methods

(@) :: NaturalTransformation c1 m1 o1 c2 m2 o2 -> NaturalTransformation c1 m1 o1 c2 m2 o2 -> NaturalTransformation c1 m1 o1 c2 m2 o2 Source #

source :: NaturalTransformation c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 Source #

target :: NaturalTransformation c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 Source #

(FiniteCategory c1 m1 o1, Morphism m1 o1, Eq m1, Eq o1, FiniteCategory c2 m2 o2, Morphism m2 o2, Eq m2, Eq o2) => GeneratedFiniteCategory (FunctorCategory c1 m1 o1 c2 m2 o2) (NaturalTransformation c1 m1 o1 c2 m2 o2) (Diagram c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in FunctorCategory.FunctorCategory

Methods

genAr :: FunctorCategory c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 -> [NaturalTransformation c1 m1 o1 c2 m2 o2] Source #

decompose :: FunctorCategory c1 m1 o1 c2 m2 o2 -> NaturalTransformation c1 m1 o1 c2 m2 o2 -> [NaturalTransformation c1 m1 o1 c2 m2 o2] Source #

genArrows :: FunctorCategory c1 m1 o1 c2 m2 o2 -> [NaturalTransformation c1 m1 o1 c2 m2 o2] Source #

(FiniteCategory c1 m1 o1, Morphism m1 o1, Eq m1, Eq o1, FiniteCategory c2 m2 o2, Morphism m2 o2, Eq m2, Eq o2) => FiniteCategory (FunctorCategory c1 m1 o1 c2 m2 o2) (NaturalTransformation c1 m1 o1 c2 m2 o2) (Diagram c1 m1 o1 c2 m2 o2) Source # 
Instance details

Defined in FunctorCategory.FunctorCategory

Methods

ob :: FunctorCategory c1 m1 o1 c2 m2 o2 -> [Diagram c1 m1 o1 c2 m2 o2] Source #

identity :: FunctorCategory c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 -> NaturalTransformation c1 m1 o1 c2 m2 o2 Source #

ar :: FunctorCategory c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c2 m2 o2 -> [NaturalTransformation c1 m1 o1 c2 m2 o2] Source #

arrows :: FunctorCategory c1 m1 o1 c2 m2 o2 -> [NaturalTransformation c1 m1 o1 c2 m2 o2] Source #

checkFunctoriality :: (FiniteCategory c1 m1 o1, Morphism m1 o1, Eq m1, Eq o1, FiniteCategory c2 m2 o2, Morphism m2 o2, Eq m2, Eq o2) => Diagram c1 m1 o1 c2 m2 o2 -> Bool Source #

Checks wether the properties of a Diagram are respected. Returns True if the diagram is well formed, else False.

completeMmap Source #

Arguments

:: (GeneratedFiniteCategory c1 m1 o1, Morphism m1 o1, Eq o1, Eq m1, FiniteCategory c2 m2 o2, Morphism m2 o2, Eq o2, Eq m2) 
=> c1

The source category, it must be a generated category.

-> c2

The target category.

-> AssociationList o1 o2

The omap.

-> AssociationList m1 m2

The mmap to complete.

-> AssociationList m1 m2

The completed mmap.

Completes the function map mmap of a diagram so that you do not have to specify images of identites and composite arrows.

composeDiag :: (FiniteCategory c1 m1 o1, Morphism m1 o1, FiniteCategory c2 m2 o2, Morphism m2 o2, FiniteCategory c3 m3 o3, Morphism m3 o3, Eq m1, Eq o1, Eq m2, Eq o2) => Diagram c2 m2 o2 c3 m3 o3 -> Diagram c1 m1 o1 c2 m2 o2 -> Diagram c1 m1 o1 c3 m3 o3 Source #

Compose two diagrams.

objectImage :: (FiniteCategory c1 m1 o1, Morphism m1 o1, FiniteCategory c2 m2 o2, Morphism m2 o2) => Diagram c1 m1 o1 c2 m2 o2 -> [o2] Source #

Returns the objects image of the diagram.

Constructors of diagrams

mkDiagram Source #

Arguments

:: (FiniteCategory c1 m1 o1, Morphism m1 o1, Eq m1, Eq o1, FiniteCategory c2 m2 o2, Morphism m2 o2, Eq m2, Eq o2) 
=> c1

The source category of the diagram.

-> c2

The target category of the diagram.

-> AssociationList o1 o2

The object map of the diagram.

-> AssociationList m1 m2

The morphism map of the diagram.

-> Maybe (Diagram c1 m1 o1 c2 m2 o2)

The constructor returns Nothing if the FinFunctoriality check failed.

Constructor of an arbitrary Diagram that checks functoriality.

Use the Diagram constructor if the functoriality check is too slow. It is then your responsability to ensure the functoriality property is verified.

mkIdentityDiagram :: (FiniteCategory c m o, Morphism m o) => c -> Diagram c m o c m o Source #

Constructs a diagram which maps a category to itself to that each object is mapped to itself and each morphism is mapped to itself too.

mkConstantDiagram :: (FiniteCategory c1 m1 o1, Morphism m1 o1, FiniteCategory c2 m2 o2, Morphism m2 o2, Eq o2) => c1 -> c2 -> o2 -> Maybe (Diagram c1 m1 o1 c2 m2 o2) Source #

Constructs a diagram where every object is mapped to a single object and every morphism is mapped to the identity of this single object.

mkDiscreteDiagram :: (FiniteCategory c m o, Morphism m o, Eq o) => c -> [o] -> Maybe (Diagram (DiscreteCategory o) (DiscreteIdentity o) (DiscreteObject o) c m o) Source #

Constructs a diagram that selects a list of objects of a category.

mkSelect0 :: (FiniteCategory c m o, Morphism m o) => c -> Diagram Zero Zero Zero c m o Source #

Constructs a diagram that selects no object and no morphism.

mkSelect1 :: (FiniteCategory c m o, Morphism m o, Eq o) => c -> o -> Maybe (Diagram One One One c m o) Source #

Constructs a diagram that selects a single object and its identity.

mkSelect2 :: (FiniteCategory c m o, Morphism m o, Eq m, Eq o) => c -> m -> Maybe (Diagram Two TwoAr TwoOb c m o) Source #

Constructs a diagram that selects a single arrow.

mkSelect3 Source #

Arguments

:: (FiniteCategory c m o, Morphism m o, Eq o, Eq m) 
=> c

The target category.

-> m

f

-> m

g

-> Maybe (Diagram Three ThreeAr ThreeOb c m o) 

Constructs a diagram that selects a triangle.

B <-f- A
|     /
g   g\@f
|  /
v v 
C

mkTriangle :: (FiniteCategory c m o, Morphism m o, Eq o, Eq m) => c -> m -> m -> Maybe (Diagram Three ThreeAr ThreeOb c m o) Source #

Constructs a diagram that selects a triangle. (Alias for mkSelect3).

mkParallel :: (FiniteCategory c m o, Morphism m o, Eq o, Eq m) => c -> m -> m -> Maybe (Diagram Parallel ParallelAr ParallelOb c m o) Source #

Constructs a diagram that selects two parallel arrows.

mkV :: (FiniteCategory c m o, Morphism m o, Eq o, Eq m) => c -> m -> m -> Maybe (Diagram V VAr VOb c m o) Source #

Constructs a diagram that selects a V.

mkHat :: (FiniteCategory c m o, Morphism m o, Eq o, Eq m) => c -> m -> m -> Maybe (Diagram Hat HatAr HatOb c m o) Source #

Constructs a diagram that selects a Hat.