module Math.FiniteCategories.DiscreteCategory.Example
(
main
)
where
import Data.WeakSet.Safe
import Math.FiniteCategories.DiscreteCategory
import Math.IO.FiniteCategories.ExportGraphViz
main :: IO ()
main :: IO ()
main = do
String -> IO ()
putStrLn String
"Start of Math.FiniteCategories.DiscreteCategory.Example"
let cats :: [DiscreteCategory Char]
cats = Set Char -> DiscreteCategory Char
forall a. Set a -> DiscreteCategory a
discreteCategory (Set Char -> DiscreteCategory Char)
-> (Int -> Set Char) -> Int -> DiscreteCategory Char
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Int
n -> String -> Set Char
forall a. [a] -> Set a
set (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
n [Char
'A'..])) (Int -> DiscreteCategory Char) -> [Int] -> [DiscreteCategory Char]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Int
0..Int
5]
let exports :: [IO ()]
exports = (DiscreteCategory Char -> String -> IO ())
-> (DiscreteCategory Char, String) -> IO ()
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry DiscreteCategory Char -> String -> IO ()
forall o m c.
(Eq o, PrettyPrint o, PrettyPrint m, Morphism m o,
FiniteCategory c m o) =>
c -> String -> IO ()
catToPdf ((DiscreteCategory Char, String) -> IO ())
-> [(DiscreteCategory Char, String)] -> [IO ()]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [DiscreteCategory Char]
-> [String] -> [(DiscreteCategory Char, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [DiscreteCategory Char]
cats ((String
"OutputGraphViz/Examples/FiniteCategories/DiscreteCategory/"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.DiscreteCategory.Example"