{-| Module : FiniteCategories Description : An example of 'CompositionGraph' pretty printed. Copyright : Guillaume Sabbagh 2022 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable An example of 'CompositionGraph' pretty printed. Examples of other categories transformed into 'CompositionGraph's are also pretty printed. A random example of 'CompositionGraph' is also pretty printed. A 'CompositionGraph' created from a string is also pretty printed. -} module Math.FiniteCategories.CompositionGraph.Example ( main ) where import qualified Data.WeakSet as Set import Data.WeakSet.Safe import Data.WeakMap.Safe import Math.FiniteCategory import Math.Categories import Math.FiniteCategories import Math.IO.PrettyPrint import Math.FiniteCategories.FunctorCategory import Math.Categories.FinCat import Data.Text (pack) import System.Random import Numeric.Natural -- | An example of 'CompositionGraph' pretty printed. main :: IO () main = do putStrLn "Start of Math.FiniteCategories.CompositionGraph.Example" putStrLn $ pprintFiniteCategory (unsafeCompositionGraph (unsafeGraph (set [1 :: Int,2,3]) (set [Arrow{sourceArrow=1,targetArrow=1,labelArrow='a'},Arrow{sourceArrow=1,targetArrow=2,labelArrow='b'},Arrow{sourceArrow=2,targetArrow=3,labelArrow='c'}])) (weakMap [([Arrow{sourceArrow=1,targetArrow=1,labelArrow='a'},Arrow{sourceArrow=1,targetArrow=1,labelArrow='a'}],[Arrow{sourceArrow=1,targetArrow=1,labelArrow='a'}])])) putStrLn $ pprint (finiteCategoryToCompositionGraph (ens.(Set.powerSet).set $ "AB")) putStrLn $ pprint (finiteCategoryToCompositionGraph (numberCategory 4)) putStrLn $ pprintFiniteCategory (fst.defaultConstructRandomCompositionGraph $ (mkStdGen 123456)) putStrLn $ pprint (fst.defaultConstructRandomDiagram $ (mkStdGen 12345678)) let (Right cg) = readCGString "A -f-> B -g-> C = A -h-> C" putStrLn $ pprintFiniteCategory cg let (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" putStrLn $ pprintFiniteCategory cg putStrLn (take 30 (repeat '\n')) -- let (Right cg1) = readCGString "A -f-> B" -- let (Right cg2) = readCGString "A -g-> C" -- let diag = discreteDiagram FinCat [cg1,cg2] -- let colimit = colimitOfCompositionGraphs diag (\x o -> (pack.show $ x) <> (pack ".")<>o) (\x m -> (pack.show$ x) <>(pack ".")<>m) -- putStrLn $ show $ nadir colimit -- putStrLn "\n\n\n" -- putStrLn $ show $ colimit let (Right cg1) = readCGString "A -f-> B\nB -g-> C" let (Right cg2) = readCGString "1 -a-> 2\n 2 -b-> 3" let (Right cg3) = readCGString "A1 -(gof)a-> C2" let 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"))]} let 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"))]} let diag = completeDiagram Diagram{src = Hat, tgt = FinCat, omap = weakMap [(HatA,cg3) , (HatB,cg2), (HatC, cg1)], mmap = weakMap [(HatF, g), (HatG, f)]} let coproduct = coproductOfTextCompositionGraphs diag putStrLn $ pprintFiniteCategory $ nadir coproduct putStrLn $ "\n\n" putStrLn $ show $ coproduct putStrLn $ "\n\n" -- let Just f_ = ((legsCocone coproduct) =>$ HatB) @? f -- let Just g_ = ((legsCocone coproduct) =>$ HatC) @? g -- let coequalizer = coequalizeCompositionGraphs f_ g_ -- putStrLn $ pprintFiniteCategory $ tgt coequalizer -- putStrLn $ "\n\n" -- putStrLn $ show $ coequalizer -- putStrLn $ "\n\n" let colimit = colimitOfCompositionGraphs diag (\x o -> (pack.show $ x) <> (pack ".")<>o) (\x m -> (pack.show$ x) <>(pack ".")<>m) putStrLn $ pprintFiniteCategory $ nadir colimit putStrLn $ "\n\n" putStrLn $ show $ colimit putStrLn "End of Math.FiniteCategories.CompositionGraph.Example"