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

Six examples of 'NumberCategory' exported with GraphViz.

Export categories __0__ up to __5__ in the directory "OutputGraphViz\/Examples\/FiniteCategories\/NumberCategory".
-}
module Math.FiniteCategories.NumberCategory.Example
(
    main
)
where
    import Math.FiniteCategories.NumberCategory
    import Math.IO.FiniteCategories.ExportGraphViz
    
    -- | Six examples of 'NumberCategory' exported with GraphViz.

    main :: IO ()
    main :: IO ()
main = do
        String -> IO ()
putStrLn String
"Start of Math.FiniteCategories.NumberCategory.Example"
        let cats :: [NumberCategory]
cats = Natural -> NumberCategory
numberCategory (Natural -> NumberCategory) -> [Natural] -> [NumberCategory]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Natural
0..Natural
5]
        let exports :: [IO ()]
exports = (NumberCategory -> String -> IO ())
-> (NumberCategory, String) -> IO ()
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry NumberCategory -> String -> IO ()
forall o m c.
(Eq o, PrettyPrint o, PrettyPrint m, Morphism m o,
 FiniteCategory c m o) =>
c -> String -> IO ()
catToPdf ((NumberCategory, String) -> IO ())
-> [(NumberCategory, String)] -> [IO ()]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [NumberCategory] -> [String] -> [(NumberCategory, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [NumberCategory]
cats ((String
"OutputGraphViz/Examples/FiniteCategories/NumberCategory/"String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> (Integer -> String) -> Integer -> String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Integer -> String
forall a. Show a => a -> String
show (Integer -> String) -> [Integer] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Integer
0..Integer
5])
        [IO ()] -> IO [()]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [IO ()]
exports
        String -> IO ()
putStrLn String
"End of Math.FiniteCategories.NumberCategory.Example"