{-# LANGUAGE OverloadedStrings #-}
module Algebra.Graph.Export (
Doc, isEmpty, literal, render,
(<+>), brackets, doubleQuotes, indent, unlines,
export
) where
import Data.Foldable (fold)
import Data.String hiding (unlines)
import Prelude hiding (unlines)
import Algebra.Graph.ToGraph (ToGraph, ToVertex, toAdjacencyMap)
import Algebra.Graph.AdjacencyMap (vertexList, edgeList)
import Algebra.Graph.Internal
newtype Doc s = Doc (List s) deriving (Doc s
[Doc s] -> Doc s
Doc s -> Doc s -> Doc s
forall {s}. Semigroup (Doc s)
forall s. Doc s
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall s. [Doc s] -> Doc s
forall s. Doc s -> Doc s -> Doc s
mconcat :: [Doc s] -> Doc s
$cmconcat :: forall s. [Doc s] -> Doc s
mappend :: Doc s -> Doc s -> Doc s
$cmappend :: forall s. Doc s -> Doc s -> Doc s
mempty :: Doc s
$cmempty :: forall s. Doc s
Monoid, NonEmpty (Doc s) -> Doc s
Doc s -> Doc s -> Doc s
forall b. Integral b => b -> Doc s -> Doc s
forall s. NonEmpty (Doc s) -> Doc s
forall s. Doc s -> Doc s -> Doc s
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall s b. Integral b => b -> Doc s -> Doc s
stimes :: forall b. Integral b => b -> Doc s -> Doc s
$cstimes :: forall s b. Integral b => b -> Doc s -> Doc s
sconcat :: NonEmpty (Doc s) -> Doc s
$csconcat :: forall s. NonEmpty (Doc s) -> Doc s
<> :: Doc s -> Doc s -> Doc s
$c<> :: forall s. Doc s -> Doc s -> Doc s
Semigroup)
instance (Monoid s, Show s) => Show (Doc s) where
show :: Doc s -> String
show = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Monoid s => Doc s -> s
render
instance (Monoid s, Eq s) => Eq (Doc s) where
Doc s
x == :: Doc s -> Doc s -> Bool
== Doc s
y | forall s. Doc s -> Bool
isEmpty Doc s
x = forall s. Doc s -> Bool
isEmpty Doc s
y
| forall s. Doc s -> Bool
isEmpty Doc s
y = Bool
False
| Bool
otherwise = forall s. Monoid s => Doc s -> s
render Doc s
x forall a. Eq a => a -> a -> Bool
== forall s. Monoid s => Doc s -> s
render Doc s
y
instance (Monoid s, Ord s) => Ord (Doc s) where
compare :: Doc s -> Doc s -> Ordering
compare Doc s
x Doc s
y | forall s. Doc s -> Bool
isEmpty Doc s
x = if forall s. Doc s -> Bool
isEmpty Doc s
y then Ordering
EQ else Ordering
LT
| forall s. Doc s -> Bool
isEmpty Doc s
y = Ordering
GT
| Bool
otherwise = forall a. Ord a => a -> a -> Ordering
compare (forall s. Monoid s => Doc s -> s
render Doc s
x) (forall s. Monoid s => Doc s -> s
render Doc s
y)
instance IsString s => IsString (Doc s) where
fromString :: String -> Doc s
fromString = forall s. s -> Doc s
literal forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. IsString a => String -> a
fromString
isEmpty :: Doc s -> Bool
isEmpty :: forall s. Doc s -> Bool
isEmpty (Doc List s
xs) = forall (t :: * -> *) a. Foldable t => t a -> Bool
null List s
xs
literal :: s -> Doc s
literal :: forall s. s -> Doc s
literal = forall s. List s -> Doc s
Doc forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Applicative f => a -> f a
pure
render :: Monoid s => Doc s -> s
render :: forall s. Monoid s => Doc s -> s
render (Doc List s
x) = forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold List s
x
(<+>) :: IsString s => Doc s -> Doc s -> Doc s
Doc s
x <+> :: forall s. IsString s => Doc s -> Doc s -> Doc s
<+> Doc s
y | forall s. Doc s -> Bool
isEmpty Doc s
x = Doc s
y
| forall s. Doc s -> Bool
isEmpty Doc s
y = Doc s
x
| Bool
otherwise = Doc s
x forall a. Semigroup a => a -> a -> a
<> Doc s
" " forall a. Semigroup a => a -> a -> a
<> Doc s
y
infixl 7 <+>
brackets :: IsString s => Doc s -> Doc s
brackets :: forall s. IsString s => Doc s -> Doc s
brackets Doc s
x = Doc s
"[" forall a. Semigroup a => a -> a -> a
<> Doc s
x forall a. Semigroup a => a -> a -> a
<> Doc s
"]"
doubleQuotes :: IsString s => Doc s -> Doc s
doubleQuotes :: forall s. IsString s => Doc s -> Doc s
doubleQuotes Doc s
x = Doc s
"\"" forall a. Semigroup a => a -> a -> a
<> Doc s
x forall a. Semigroup a => a -> a -> a
<> Doc s
"\""
indent :: IsString s => Int -> Doc s -> Doc s
indent :: forall s. IsString s => Int -> Doc s -> Doc s
indent Int
spaces Doc s
x = forall a. IsString a => String -> a
fromString (forall a. Int -> a -> [a]
replicate Int
spaces Char
' ') forall a. Semigroup a => a -> a -> a
<> Doc s
x
unlines :: IsString s => [Doc s] -> Doc s
unlines :: forall s. IsString s => [Doc s] -> Doc s
unlines [] = forall a. Monoid a => a
mempty
unlines (Doc s
x:[Doc s]
xs) = Doc s
x forall a. Semigroup a => a -> a -> a
<> Doc s
"\n" forall a. Semigroup a => a -> a -> a
<> forall s. IsString s => [Doc s] -> Doc s
unlines [Doc s]
xs
export :: (Ord a, ToGraph g, ToVertex g ~ a) => (a -> Doc s) -> (a -> a -> Doc s) -> g -> Doc s
export :: forall a g s.
(Ord a, ToGraph g, ToVertex g ~ a) =>
(a -> Doc s) -> (a -> a -> Doc s) -> g -> Doc s
export a -> Doc s
v a -> a -> Doc s
e g
g = Doc s
vDoc forall a. Semigroup a => a -> a -> a
<> Doc s
eDoc
where
vDoc :: Doc s
vDoc = forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map a -> Doc s
v (forall a. AdjacencyMap a -> [a]
vertexList AdjacencyMap (ToVertex g)
adjMap)
eDoc :: Doc s
eDoc = forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> a -> Doc s
e) (forall a. AdjacencyMap a -> [(a, a)]
edgeList AdjacencyMap (ToVertex g)
adjMap)
adjMap :: AdjacencyMap (ToVertex g)
adjMap = forall t.
(ToGraph t, Ord (ToVertex t)) =>
t -> AdjacencyMap (ToVertex t)
toAdjacencyMap g
g