{-| Module : FiniteCategories Description : A simple typeclass for things to be pretty printed. Copyright : Guillaume Sabbagh 2022 License : GPL-3 Maintainer : guillaumesabbagh@protonmail.com Stability : experimental Portability : portable A simple typeclass for things to be pretty printed. Things should be pretty printable to be exported with graphviz. Different objects should be pretty printed into different strings or the graphviz export might be wrong. -} module Math.IO.PrettyPrint ( PrettyPrint(..), pprintFunction ) where import Data.List (intercalate) import qualified Data.Set as Set import qualified Data.WeakSet as WSet import qualified Data.WeakMap as WMap import qualified Math.PureSet as PSet import qualified Data.Text as Text import Numeric.Natural -- | The typeclass of things that can be pretty printed. class PrettyPrint a where pprint :: a -> String instance (PrettyPrint a) => PrettyPrint [a] where pprint xs = "[" ++ intercalate "," (pprint <$> xs) ++ "]" instance (PrettyPrint a, PrettyPrint b) => PrettyPrint (a,b) where pprint (a,b) = "(" ++ pprint a ++ "," ++ pprint b ++ ")" instance (PrettyPrint a, PrettyPrint b, PrettyPrint c) => PrettyPrint (a,b,c) where pprint (a,b,c) = "(" ++ pprint a ++ "," ++ pprint b ++ "," ++ pprint c ++ ")" instance (PrettyPrint a) => PrettyPrint (Set.Set a) where pprint xs = "{" ++ intercalate "," (pprint <$> (Set.toList xs)) ++ "}" instance (PrettyPrint a, Eq a) => PrettyPrint (WSet.Set a) where pprint xs = "{" ++ intercalate "," (pprint <$> (WSet.setToList xs)) ++ "}" instance (PrettyPrint a, Eq a, PrettyPrint b, Eq b) => PrettyPrint (WMap.Map a b) where pprint m = "{" ++ intercalate "," ((\(k,v) -> (pprint k) ++ "->" ++ (pprint v)) <$> (WMap.mapToList m)) ++ "}" instance PrettyPrint PSet.PureSet where pprint = PSet.formatPureSet instance PrettyPrint Int where pprint = show instance PrettyPrint Double where pprint = show instance PrettyPrint Natural where pprint = show instance PrettyPrint Char where pprint = (:[]) instance PrettyPrint Text.Text where pprint = Text.unpack -- | Pretty print a function on a specific domain. pprintFunction :: (PrettyPrint a, PrettyPrint b) => (a -> b) -> [a] -> String pprintFunction f xs = intercalate "\n" [pprint x ++" -> " ++ pprint (f x) | x <- xs]