{-| Module : FiniteCategories Description : Examples of 'CompositionGraph's. Copyright : Guillaume Sabbagh 2023 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable Examples of 'CompositionGraph's, other categories transformed into 'CompositionGraph's, a random example of 'CompositionGraph', a 'CompositionGraph' created from a string and a colimit of 'CompositionGraph's. See also 'exampleCgdString' in Math.FiniteCategories.FunctorCategory.Examples for constructing diagrams of 'CompositionGraph's. -} module Math.FiniteCategories.CompositionGraph.Examples ( exampleCompositionGraph, exampleCompositionGraph2, exampleSetTransformedIntoACompositionGraph, example4TransformedIntoACompositionGraph, exampleRandomCompositionGraph, exampleCgString, exampleCgString2, exampleDiagramToCompositionGraphs, exampleColimitOfCompositionGraphs, ) where import qualified Data.WeakSet as Set import Data.WeakSet.Safe import Data.WeakMap.Safe import Math.FiniteCategory import Math.Categories import Math.CocompleteCategory import Math.FiniteCategories import Math.FiniteCategories.FunctorCategory import Math.Categories.FinCat import Data.Text (pack , Text) import System.Random import Numeric.Natural -- | An example of 'CompositionGraph' constructed with the smart constructor 'compositionGraph'. exampleCompositionGraph :: CompositionGraph Int Char exampleCompositionGraph = result where Just underlyingGraph = graph (set [1,2,3]) (set [Arrow{sourceArrow=1,targetArrow=1,labelArrow='a'},Arrow{sourceArrow=1,targetArrow=2,labelArrow='b'},Arrow{sourceArrow=2,targetArrow=3,labelArrow='c'}]) compositionLaw = weakMap [([Arrow{sourceArrow=1,targetArrow=1,labelArrow='a'},Arrow{sourceArrow=1,targetArrow=1,labelArrow='a'}],[Arrow{sourceArrow=1,targetArrow=1,labelArrow='a'}])] Right result = compositionGraph underlyingGraph compositionLaw -- | An example of 'CompositionGraph' constructed with the smart constructor 'unsafeCompositionGraph'. exampleCompositionGraph2 :: CompositionGraph Int Char exampleCompositionGraph2 = result where underlyingGraph = unsafeGraph (set [1,2]) (set [Arrow{sourceArrow=1,targetArrow=2,labelArrow='f'}]) compositionLaw = weakMap [] result = unsafeCompositionGraph underlyingGraph compositionLaw -- | The insertion diagram from S (the subcategory of Set containing all subsets of the set {'A','B'} as objects) to the same category transformed into a 'CompositionGraph'. exampleSetTransformedIntoACompositionGraph :: Diagram (Ens Char) (Function Char) (Set.Set Char) (CompositionGraph (Set.Set Char) (Function Char)) (CGMorphism (Set.Set Char) (Function Char)) (Set.Set Char) exampleSetTransformedIntoACompositionGraph = finiteCategoryToCompositionGraph2 s where s = ens.(Set.powerSet).set $ "AB" -- | The insertion diagram from 4 to the same category transformed into a 'CompositionGraph'. example4TransformedIntoACompositionGraph :: Diagram NumberCategory NumberCategoryMorphism NumberCategoryObject (CompositionGraph NumberCategoryObject NumberCategoryMorphism) (CGMorphism NumberCategoryObject NumberCategoryMorphism) NumberCategoryObject example4TransformedIntoACompositionGraph = finiteCategoryToCompositionGraph2 (numberCategory 4) -- | An example of random 'CompositionGraph'. exampleRandomCompositionGraph :: CompositionGraph Int Int exampleRandomCompositionGraph = result where randomGen = mkStdGen 123456 (result,newRandomGen) = defaultConstructRandomCompositionGraph randomGen -- | An example of 'CompositionGraph' read from a .cg string. exampleCgString :: CompositionGraph Text Text exampleCgString = cg where Right cg = readCGString "A -f-> B -g-> C = A -h-> C" -- | A second example of 'CompositionGraph' read from a .cg string. exampleCgString2 :: CompositionGraph Text Text exampleCgString2 = cg where Right cg = readCGString "A -f-> B\nB -g-> C\nC -h-> B\nB -g-> C -h-> B = \nC -h-> B -g-> C -h-> B -g-> C = C -h-> B -g-> C" -- | An example of 'Diagram' from 'Hat' to 'FinCat' of 'CompositionGraph's. exampleDiagramToCompositionGraphs :: Diagram Hat HatAr HatOb (FinCat (CompositionGraph Text Text) (CGMorphism Text Text) Text) (FinFunctor (CompositionGraph Text Text) (CGMorphism Text Text) Text) (CompositionGraph Text Text) exampleDiagramToCompositionGraphs = completeDiagram diag where (Right cg1) = readCGString "A" (Right cg2) = readCGString "A\nB" (Right cg3) = readCGString "A\nC" f = completeDiagram Diagram{src = cg1, tgt = cg2, omap = weakMap [(pack "A", pack "A")], mmap = weakMap []} g = completeDiagram Diagram{src = cg1, tgt = cg3, omap = weakMap [(pack "A", pack "A")], mmap = weakMap []} diag = Diagram{src = Hat, tgt = FinCat, omap = weakMap [(HatA,cg1) , (HatB,cg2), (HatC, cg3)], mmap = weakMap [(HatF, f), (HatG, g)]} -- | An example of colimit of 'CompositionGraph's. exampleColimitOfCompositionGraphs = result where (Right cg1) = readCGString "A -f-> B\nB -g-> C" (Right cg2) = readCGString "1 -a-> 2\n 2 -b-> 3" (Right cg3) = readCGString "A1 -(gof)a-> C2" f = completeDiagram Diagram{src = cg3, tgt = cg1, omap = weakMap [(pack "A1", pack "A"),(pack "C2", pack "C")], mmap = weakMap [(anElement $ genAr cg3 (pack "A1") (pack "C2"), anElement $ ar cg1 (pack "A") (pack "C"))]} g = completeDiagram Diagram{src = cg3, tgt = cg2, omap = weakMap [(pack "A1", pack "1"),(pack "C2", pack "2")], mmap = weakMap [(anElement $ genAr cg3 (pack "A1") (pack "C2"), anElement $ ar cg2 (pack "1") (pack "2"))]} diag = completeDiagram Diagram{src = Hat, tgt = FinCat, omap = weakMap [(HatA,cg3) , (HatB,cg2), (HatC, cg1)], mmap = weakMap [(HatF, g), (HatG, f)]} result = colimitOfCompositionGraphs diag