{-| Module  : FiniteCategories
Description : An example of `CompositionGraph` construction with insertion, modification and deletion.
Copyright   : Guillaume Sabbagh 2021
License     : GPL-3
Maintainer  : guillaumesabbagh@protonmail.com
Stability   : experimental
Portability : portable

An example of `CompositionGraph` construction with insertion, modification and deletion.
-}
module ExampleCompositionGraph.ExampleCompositionGraphConstruction
(
    main
)
where
    import              CompositionGraph.CompositionGraph
    import              ExportGraphViz.ExportGraphViz
    import              Diagram.Diagram
    import              FiniteCategory.FiniteCategory
    import              Data.Text                               (Text, pack)
    import              Data.List                               ((\\))
    import              Diagram.Conversion
    
    cg1 = mkEmptyCompositionGraph :: CompositionGraph Text Text
    (cg2,funct2) = insertObject cg1 (pack "1")
    (cg3,funct3) = insertObject cg2 (pack "2")
    Right (cg4,funct4) = insertMorphism cg3 ((pack "1")) ((pack "2")) (pack "f")
    Right (cg5,funct5) = insertMorphism cg4 ((pack "1")) ((pack "1")) (pack "g")
    Right (cg6,funct6) = identifyMorphisms cg5 ((head [f | f <- genAr cg5 ((pack "1")) ((pack "1")), isNotIdentity cg5 f]) @ (head [f | f <- genAr cg5 ((pack "1")) ((pack "1")), isNotIdentity cg5 f])) (head [f | f <- genAr cg5 ((pack "1")) ((pack "1")), isNotIdentity cg5 f])
    Right (cg7,funct7) = replaceObject cg6 (pack "2") (pack "3")
    Right (cg8,funct8) = replaceMorphism cg7 (head (ar cg7 (pack "1") (pack "3"))) (pack "h")
    (cg9,funct9) = insertObject cg8 (pack "4")
    Right (cg10,funct10) = insertMorphism cg9 ((pack "3")) ((pack "4")) (pack "i")
    Right (cg11,funct11) = insertMorphism cg10 ((pack "1")) ((pack "4")) (pack "j")
    Right (cg12,funct12) = identifyMorphisms cg11 (((ar cg11 (pack "1") (pack "4")) \\ (genAr cg11 (pack "1") (pack "4")))!!1) (head (genAr cg11 (pack "1") (pack "4")))
    Right (cg13,funct13) = deleteMorphism cg12 (head (genAr cg12 (pack "1") (pack "4")))
    Right (cg14,funct14) = deleteObject cg13 (pack "4")
    Right (cg15,funct15) = identifyMorphisms cg14 ((ar cg14 (pack "1") (pack "3"))!!1) ((ar cg14 (pack "1") (pack "3"))!!0)
    Right (cg16,funct16) = unidentifyMorphism cg15 ((ar cg15 (pack "1") (pack "3"))!!0)
            
    Just diag2 = partialFunctorToDiagram funct2
    Just diag3 = partialFunctorToDiagram funct3
    Just diag4 = partialFunctorToDiagram funct4
    -- we don't create diag5 and diag6 because their are not showable as categories are infinite.
    Just diag7 = partialFunctorToDiagram funct7
    Just diag8 = partialFunctorToDiagram funct8
    Just diag9 = partialFunctorToDiagram funct9
    Just diag10 = partialFunctorToDiagram funct10
    Just diag11 = partialFunctorToDiagram funct11
    -- we don't create diag12, diag13, diag14 and diag15 because they are not total.
    Just diag16 = partialFunctorToDiagram funct16
            
    -- | Exports the composition graphs and insertion functors as pdf file with GraphViz.
    main = do
            putStrLn "Start of ExampleCompositionGraphConstruction"
            catToPdf cg1 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat1"
            catToPdf cg2 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat2"
            catToPdf cg3 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat3"
            catToPdf cg4 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat4"
            catToPdf cg6 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat6"
            catToPdf cg7 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat7"
            catToPdf cg8 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat8"
            catToPdf cg9 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat9"
            catToPdf cg10 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat10"
            catToPdf cg11 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat11"
            catToPdf cg12 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat12"
            catToPdf cg13 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat13"
            catToPdf cg14 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat14"
            catToPdf cg15 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat15"
            catToPdf cg16 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/cat16"
            diagToPdf diag2 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct2"
            diagToPdf diag3 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct3"
            diagToPdf diag4 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct4"
            diagToPdf diag7 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct7"
            diagToPdf diag8 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct8"
            diagToPdf diag9 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct9"
            diagToPdf diag10 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct10"
            diagToPdf diag11 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct11"
            diagToPdf diag16 "OutputGraphViz/Examples/CompositionGraph/CompositionGraphConstruction/funct16"
            putStrLn "End of ExampleCompositionGraphConstruction"