{-| Module  : FiniteCategories
Description : Examples of 'CommaCategory' exported with GraphViz.
Copyright   : Guillaume Sabbagh 2022
License     : GPL-3
Maintainer  : guillaumesabbagh@protonmail.com
Stability   : experimental
Portability : portable

Examples of 'CommaCategory' exported with GraphViz.

Export the category in the directory "OutputGraphViz\/Examples\/FiniteCategories\/CommaCategory".
-}
module Math.FiniteCategories.CommaCategory.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.FiniteCategories.ExportGraphViz
    import Math.IO.PrettyPrint
    
    -- | Examples of 'CommaCategory' exported with GraphViz.

    main :: IO ()
    main :: IO ()
main = do
        String -> IO ()
putStrLn String
"Start of Math.FiniteCategories.CommaCategory.Example"
        NumberCategory -> String -> IO ()
forall o m c.
(Eq o, PrettyPrint o, PrettyPrint m, Morphism m o,
 FiniteCategory c m o) =>
c -> String -> IO ()
catToPdf (Natural -> NumberCategory
numberCategory Natural
4) String
"OutputGraphViz/Examples/FiniteCategories/CommaCategory/4"
        let Just CommaCategory
  NumberCategory
  (IsSmallerThan Natural)
  Natural
  One
  One
  One
  NumberCategory
  (IsSmallerThan Natural)
  Natural
slice = NumberCategory
-> Natural
-> Maybe
     (CommaCategory
        NumberCategory
        (IsSmallerThan Natural)
        Natural
        One
        One
        One
        NumberCategory
        (IsSmallerThan Natural)
        Natural)
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq c, Eq m, Eq o) =>
c -> o -> Maybe (CommaCategory c m o One One One c m o)
sliceCategory (Natural -> NumberCategory
numberCategory Natural
4) Natural
2
        let Just CommaCategory
  One
  One
  One
  NumberCategory
  (IsSmallerThan Natural)
  Natural
  NumberCategory
  (IsSmallerThan Natural)
  Natural
coslice = NumberCategory
-> Natural
-> Maybe
     (CommaCategory
        One
        One
        One
        NumberCategory
        (IsSmallerThan Natural)
        Natural
        NumberCategory
        (IsSmallerThan Natural)
        Natural)
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq c, Eq m, Eq o) =>
c -> o -> Maybe (CommaCategory One One One c m o c m o)
cosliceCategory (Natural -> NumberCategory
numberCategory Natural
4) Natural
2
        CommaCategory
  NumberCategory
  (IsSmallerThan Natural)
  Natural
  One
  One
  One
  NumberCategory
  (IsSmallerThan Natural)
  Natural
-> String -> IO ()
forall o m c.
(Eq o, PrettyPrint o, PrettyPrint m, Morphism m o,
 FiniteCategory c m o) =>
c -> String -> IO ()
catToPdf CommaCategory
  NumberCategory
  (IsSmallerThan Natural)
  Natural
  One
  One
  One
  NumberCategory
  (IsSmallerThan Natural)
  Natural
slice String
"OutputGraphViz/Examples/FiniteCategories/CommaCategory/slice2"
        CommaCategory
  One
  One
  One
  NumberCategory
  (IsSmallerThan Natural)
  Natural
  NumberCategory
  (IsSmallerThan Natural)
  Natural
-> String -> IO ()
forall o m c.
(Eq o, PrettyPrint o, PrettyPrint m, Morphism m o,
 FiniteCategory c m o) =>
c -> String -> IO ()
catToPdf CommaCategory
  One
  One
  One
  NumberCategory
  (IsSmallerThan Natural)
  Natural
  NumberCategory
  (IsSmallerThan Natural)
  Natural
coslice String
"OutputGraphViz/Examples/FiniteCategories/CommaCategory/coslice2"
        CommaCategory
  NumberCategory
  (IsSmallerThan Natural)
  Natural
  NumberCategory
  (IsSmallerThan Natural)
  Natural
  NumberCategory
  (IsSmallerThan Natural)
  Natural
-> String -> IO ()
forall o m c.
(Eq o, PrettyPrint o, PrettyPrint m, Morphism m o,
 FiniteCategory c m o) =>
c -> String -> IO ()
catToPdf (NumberCategory
-> CommaCategory
     NumberCategory
     (IsSmallerThan Natural)
     Natural
     NumberCategory
     (IsSmallerThan Natural)
     Natural
     NumberCategory
     (IsSmallerThan Natural)
     Natural
forall c m o.
(FiniteCategory c m o, Morphism m o, Eq c, Eq m, Eq o) =>
c -> CommaCategory c m o c m o c m o
arrowCategory (Natural -> NumberCategory
numberCategory Natural
4)) String
"OutputGraphViz/Examples/FiniteCategories/CommaCategory/arrow"
        String -> IO ()
putStrLn String
"End of Math.FiniteCategories.CommaCategory.Example"