{-| Module : FiniteCategories Description : An example of 'FullSubcategory' of __'FinGrph'__ and an example of 'Graph'. Copyright : Guillaume Sabbagh 2022 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable An example of 'FullSubcategory' of __'FinGrph'__ and an example of 'Graph'. -} module Math.FiniteCategories.FinGrph.Examples ( divisibilityGraph, exampleGraph, exampleFinGrph, exampleDiscreteDiagramToFinGrph, exampleProductGaphs, exampleParallelDiagramToFinGrph, exampleEqualizerInFinGrph, exampleDiagramHatToFinGrph, exampleColimitOfGraphs, ) where import Data.WeakSet (Set) import qualified Data.WeakSet as Set import Data.WeakSet.Safe import Data.WeakMap (Map) import qualified Data.WeakMap as Map import Data.WeakMap.Safe import Data.Text (Text, pack) import Math.Categories import Math.FiniteCategories import Math.IO.PrettyPrint import Math.FiniteCategory import Math.CompleteCategory import Math.CocompleteCategory -- | Return the divisibility graph of number lesser or equal than a given n. divisibilityGraph :: Int -> Graph Int Int divisibilityGraph n = result where Just result = graph (set [1..n]) (set [Arrow{sourceArrow = a, targetArrow = b, labelArrow = b `div` a} | a <- [1..n], b <- [1..n], b `mod` a == 0]) -- | Example of graph : divisibility graph of numbers lesser or equal than 10. exampleGraph :: Graph Int Int exampleGraph = divisibilityGraph 10 -- | Example of a 'FullSubcategory' of 'FinGrph'. exampleFinGrph :: FullSubcategory (FinGrph Int Int) (GraphHomomorphism Int Int) (Graph Int Int) exampleFinGrph = FullSubcategory FinGrph (set (divisibilityGraph <$> [1..3])) -- | Example of a discrete diagram selecting two graphs. exampleDiscreteDiagramToFinGrph :: Diagram (DiscreteCategory Int) (DiscreteMorphism Int) Int (FinGrph Text Text) (GraphHomomorphism Text Text) (Graph Text Text) exampleDiscreteDiagramToFinGrph = discreteDiagram FinGrph [g1,g2] where Right cg1 = readCGString "A -f-> B" g1 = support cg1 Right cg2 = readCGString "C -g-> D" g2 = support cg2 -- | Product of 'exampleDiscreteDiagramToFinGrph'. exampleProductGaphs :: Cone (DiscreteCategory Int) (DiscreteMorphism Int) Int (FinGrph (Limit Int Text) (Limit Int Text)) (GraphHomomorphism (Limit Int Text) (Limit Int Text)) (Graph (Limit Int Text) (Limit Int Text)) exampleProductGaphs = Math.CompleteCategory.product exampleDiscreteDiagramToFinGrph -- | Example of a parallel diagram selecting two graphs. exampleParallelDiagramToFinGrph :: Diagram Parallel ParallelAr ParallelOb (FinGrph Char Char) (GraphHomomorphism Char Char) (Graph Char Char) exampleParallelDiagramToFinGrph = parallelDiagram FinGrph gh1 gh2 where x = Arrow{sourceArrow = 'A', targetArrow = 'B', labelArrow = 'x'} y = Arrow{sourceArrow = 'C', targetArrow = 'D', labelArrow = 'y'} Just g = graph (set "ABCD") (set [x,y]) Just gh1 = graphHomomorphism (weakMap [('A','A'),('B','B'),('C','A'),('D','B')]) (weakMap [(x,x),(y,x)]) g Just gh2 = graphHomomorphism (weakMap [('A','A'),('B','B'),('C','C'),('D','D')]) (weakMap [(x,x),(y,y)]) g -- | Limit of 'exampleParallelDiagramToFinGrph'. exampleEqualizerInFinGrph :: Cone Parallel ParallelAr ParallelOb (FinGrph (Limit ParallelOb Char) (Limit ParallelOb Char)) (GraphHomomorphism (Limit ParallelOb Char) (Limit ParallelOb Char)) (Graph (Limit ParallelOb Char) (Limit ParallelOb Char)) exampleEqualizerInFinGrph = limit exampleParallelDiagramToFinGrph -- | Example of a 'Diagram' from 'Hat' to 'FinGrph'. exampleDiagramHatToFinGrph :: Diagram Hat HatAr HatOb (FinGrph Char Char) (GraphHomomorphism Char Char) (Graph Char Char) exampleDiagramHatToFinGrph = diag where f = Arrow{sourceArrow = 'A', targetArrow = 'B', labelArrow = 'f'} g = Arrow{sourceArrow = 'B', targetArrow = 'C', labelArrow = 'g'} Just g1 = graph (set "AB") (set [f]) Just g2 = graph (set "BC") (set [g]) Just g3 = graph (set "B") (set []) Just gh1 = graphHomomorphism (weakMap [('B','B')]) (weakMap []) g1 Just gh2 = graphHomomorphism (weakMap [('B','B')]) (weakMap []) g2 diag = completeDiagram Diagram{src = Hat, tgt = FinGrph, omap = weakMap [(HatA,g3),(HatB,g1),(HatC,g2)], mmap = weakMap [(HatF,gh1),(HatG,gh2)]} -- | Example of a colimit of graphs. exampleColimitOfGraphs :: Cocone Hat HatAr HatOb (FinGrph (Colimit HatOb Char) (Colimit HatOb Char)) (GraphHomomorphism (Colimit HatOb Char) (Colimit HatOb Char)) (Graph (Colimit HatOb Char) (Colimit HatOb Char)) exampleColimitOfGraphs = colimit exampleDiagramHatToFinGrph