{-| Module  : FiniteCategories
Description : Examples of random diagrams.
Copyright   : Guillaume Sabbagh 2021
License     : GPL-3
Maintainer  : guillaumesabbagh@protonmail.com
Stability   : experimental
Portability : portable

This example shows how to use `mkRandomDiagram`.
-}

module ExampleRandomDiagram.ExampleRandomDiagram
(
    main
)
where
    import CompositionGraph.CompositionGraph
    import RandomCompositionGraph.RandomCompositionGraph
    import RandomDiagram.RandomDiagram
    import System.Random
    import ExportGraphViz.ExportGraphViz
    import Diagram.Diagram
    
    generateRDiags 0 gen diags = (diags,gen)
    generateRDiags n gen diags = ((diag:end), finalGen)
        where
            (diag,newGen) = (defaultMkRandomDiagram gen)
            (end,finalGen) = generateRDiags (n-1) newGen diags

    exportDiags [] = putStrLn "End of ExampleRandomDiagram"
    exportDiags (diag:diags) = do 
        putStrLn (show (length diags)++" random diagrams remaining...")
        catToPdf (src diag) ("OutputGraphViz/Examples/RandomDiagram/RandomDefaultDiagram/src"++show (length diags))
        catToPdf (tgt diag) ("OutputGraphViz/Examples/RandomDiagram/RandomDefaultDiagram/tgt"++show (length diags))
        diagToPdf diag ("OutputGraphViz/Examples/RandomDiagram/RandomDefaultDiagram/funct"++show (length diags))
        diagToPdf2 diag ("OutputGraphViz/Examples/RandomDiagram/RandomDefaultDiagram/diag"++show (length diags))
        exportDiags diags

    -- | Exports 5 random composition graphs as pdf.
    main = do
        putStrLn "Start of ExampleRandomDiagram"
        exportDiags diags
        where
            (diags, g) = generateRDiags 5 (mkStdGen 745678765434567) []