{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
module Algebra.Graph.Export.Dot (
Attribute (..), Quoting (..), Style (..), defaultStyle, defaultStyleViaShow,
export, exportAsIs, exportViaShow
) where
import Data.List (map, null, intersperse)
import Data.Monoid
import Data.String hiding (unlines)
import Prelude hiding (unlines)
import Algebra.Graph.ToGraph (ToGraph (..))
import Algebra.Graph.Export hiding (export)
import qualified Algebra.Graph.Export as E
data Attribute s = (:=) s s
data Quoting = DoubleQuotes | NoQuotes
data Style a s = Style
{ Style a s -> s
graphName :: s
, Style a s -> [s]
preamble :: [s]
, Style a s -> [Attribute s]
graphAttributes :: [Attribute s]
, Style a s -> [Attribute s]
defaultVertexAttributes :: [Attribute s]
, Style a s -> [Attribute s]
defaultEdgeAttributes :: [Attribute s]
, Style a s -> a -> s
vertexName :: a -> s
, Style a s -> a -> [Attribute s]
vertexAttributes :: a -> [Attribute s]
, Style a s -> a -> a -> [Attribute s]
edgeAttributes :: a -> a -> [Attribute s]
, Style a s -> Quoting
attributeQuoting :: Quoting
}
defaultStyle :: Monoid s => (a -> s) -> Style a s
defaultStyle :: (a -> s) -> Style a s
defaultStyle a -> s
v = s
-> [s]
-> [Attribute s]
-> [Attribute s]
-> [Attribute s]
-> (a -> s)
-> (a -> [Attribute s])
-> (a -> a -> [Attribute s])
-> Quoting
-> Style a s
forall a s.
s
-> [s]
-> [Attribute s]
-> [Attribute s]
-> [Attribute s]
-> (a -> s)
-> (a -> [Attribute s])
-> (a -> a -> [Attribute s])
-> Quoting
-> Style a s
Style s
forall a. Monoid a => a
mempty [] [] [] [] a -> s
v ([Attribute s] -> a -> [Attribute s]
forall a b. a -> b -> a
const []) (\a
_ a
_ -> []) Quoting
DoubleQuotes
defaultStyleViaShow :: (Show a, IsString s, Monoid s) => Style a s
defaultStyleViaShow :: Style a s
defaultStyleViaShow = (a -> s) -> Style a s
forall s a. Monoid s => (a -> s) -> Style a s
defaultStyle (String -> s
forall a. IsString a => String -> a
fromString (String -> s) -> (a -> String) -> a -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show)
export :: (IsString s, Monoid s, Ord a, ToGraph g, ToVertex g ~ a) => Style a s -> g -> s
export :: Style a s -> g -> s
export Style {s
[s]
[Attribute s]
Quoting
a -> s
a -> [Attribute s]
a -> a -> [Attribute s]
attributeQuoting :: Quoting
edgeAttributes :: a -> a -> [Attribute s]
vertexAttributes :: a -> [Attribute s]
vertexName :: a -> s
defaultEdgeAttributes :: [Attribute s]
defaultVertexAttributes :: [Attribute s]
graphAttributes :: [Attribute s]
preamble :: [s]
graphName :: s
attributeQuoting :: forall a s. Style a s -> Quoting
edgeAttributes :: forall a s. Style a s -> a -> a -> [Attribute s]
vertexAttributes :: forall a s. Style a s -> a -> [Attribute s]
vertexName :: forall a s. Style a s -> a -> s
defaultEdgeAttributes :: forall a s. Style a s -> [Attribute s]
defaultVertexAttributes :: forall a s. Style a s -> [Attribute s]
graphAttributes :: forall a s. Style a s -> [Attribute s]
preamble :: forall a s. Style a s -> [s]
graphName :: forall a s. Style a s -> s
..} g
g = Doc s -> s
forall s. Monoid s => Doc s -> s
render (Doc s -> s) -> Doc s -> s
forall a b. (a -> b) -> a -> b
$ Doc s
header Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> Doc s
body Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> Doc s
"}\n"
where
header :: Doc s
header = Doc s
"digraph" Doc s -> Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s -> Doc s
<+> s -> Doc s
forall s. s -> Doc s
literal s
graphName Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> Doc s
"\n{\n"
with :: Doc s -> [Attribute s] -> Doc s
with Doc s
x [Attribute s]
as = if [Attribute s] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Attribute s]
as then Doc s
forall a. Monoid a => a
mempty else Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s
line (Doc s
x Doc s -> Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s -> Doc s
<+> Quoting -> [Attribute s] -> Doc s
forall s. IsString s => Quoting -> [Attribute s] -> Doc s
attributes Quoting
attributeQuoting [Attribute s]
as)
line :: Doc s -> Doc s
line Doc s
s = Int -> Doc s -> Doc s
forall s. IsString s => Int -> Doc s -> Doc s
indent Int
2 Doc s
s Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> Doc s
"\n"
body :: Doc s
body = [Doc s] -> Doc s
forall s. IsString s => [Doc s] -> Doc s
unlines ((s -> Doc s) -> [s] -> [Doc s]
forall a b. (a -> b) -> [a] -> [b]
map s -> Doc s
forall s. s -> Doc s
literal [s]
preamble)
Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> (Doc s
"graph" Doc s -> [Attribute s] -> Doc s
`with` [Attribute s]
graphAttributes)
Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> (Doc s
"node" Doc s -> [Attribute s] -> Doc s
`with` [Attribute s]
defaultVertexAttributes)
Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> (Doc s
"edge" Doc s -> [Attribute s] -> Doc s
`with` [Attribute s]
defaultEdgeAttributes)
Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> (a -> Doc s) -> (a -> a -> Doc s) -> g -> Doc s
forall a g s.
(Ord a, ToGraph g, ToVertex g ~ a) =>
(a -> Doc s) -> (a -> a -> Doc s) -> g -> Doc s
E.export a -> Doc s
vDoc a -> a -> Doc s
eDoc g
g
label :: a -> Doc s
label = Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s
doubleQuotes (Doc s -> Doc s) -> (a -> Doc s) -> a -> Doc s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> Doc s
forall s. s -> Doc s
literal (s -> Doc s) -> (a -> s) -> a -> Doc s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> s
vertexName
vDoc :: a -> Doc s
vDoc a
x = Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s
line (Doc s -> Doc s) -> Doc s -> Doc s
forall a b. (a -> b) -> a -> b
$ a -> Doc s
label a
x Doc s -> Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s -> Doc s
<+> Quoting -> [Attribute s] -> Doc s
forall s. IsString s => Quoting -> [Attribute s] -> Doc s
attributes Quoting
attributeQuoting (a -> [Attribute s]
vertexAttributes a
x)
eDoc :: a -> a -> Doc s
eDoc a
x a
y = Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s
line (Doc s -> Doc s) -> Doc s -> Doc s
forall a b. (a -> b) -> a -> b
$ a -> Doc s
label a
x Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> Doc s
" -> " Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> a -> Doc s
label a
y Doc s -> Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s -> Doc s
<+> Quoting -> [Attribute s] -> Doc s
forall s. IsString s => Quoting -> [Attribute s] -> Doc s
attributes Quoting
attributeQuoting (a -> a -> [Attribute s]
edgeAttributes a
x a
y)
attributes :: IsString s => Quoting -> [Attribute s] -> Doc s
attributes :: Quoting -> [Attribute s] -> Doc s
attributes Quoting
_ [] = Doc s
forall a. Monoid a => a
mempty
attributes Quoting
q [Attribute s]
as = Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s
brackets (Doc s -> Doc s) -> ([Doc s] -> Doc s) -> [Doc s] -> Doc s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Doc s] -> Doc s
forall a. Monoid a => [a] -> a
mconcat ([Doc s] -> Doc s) -> ([Doc s] -> [Doc s]) -> [Doc s] -> Doc s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc s -> [Doc s] -> [Doc s]
forall a. a -> [a] -> [a]
intersperse Doc s
" " ([Doc s] -> Doc s) -> [Doc s] -> Doc s
forall a b. (a -> b) -> a -> b
$ (Attribute s -> Doc s) -> [Attribute s] -> [Doc s]
forall a b. (a -> b) -> [a] -> [b]
map Attribute s -> Doc s
dot [Attribute s]
as
where
dot :: Attribute s -> Doc s
dot (s
k := s
v) = s -> Doc s
forall s. s -> Doc s
literal s
k Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> Doc s
"=" Doc s -> Doc s -> Doc s
forall a. Semigroup a => a -> a -> a
<> Doc s -> Doc s
quote (s -> Doc s
forall s. s -> Doc s
literal s
v)
quote :: Doc s -> Doc s
quote = case Quoting
q of
Quoting
DoubleQuotes -> Doc s -> Doc s
forall s. IsString s => Doc s -> Doc s
doubleQuotes
Quoting
NoQuotes -> Doc s -> Doc s
forall a. a -> a
id
exportAsIs :: (IsString s, Monoid s, Ord (ToVertex g), ToGraph g, ToVertex g ~ s) => g -> s
exportAsIs :: g -> s
exportAsIs = Style s s -> g -> s
forall s a g.
(IsString s, Monoid s, Ord a, ToGraph g, ToVertex g ~ a) =>
Style a s -> g -> s
export ((s -> s) -> Style s s
forall s a. Monoid s => (a -> s) -> Style a s
defaultStyle s -> s
forall a. a -> a
id)
exportViaShow :: (IsString s, Monoid s, Ord (ToVertex g), Show (ToVertex g), ToGraph g) => g -> s
exportViaShow :: g -> s
exportViaShow = Style (ToVertex g) s -> g -> s
forall s a g.
(IsString s, Monoid s, Ord a, ToGraph g, ToVertex g ~ a) =>
Style a s -> g -> s
export Style (ToVertex g) s
forall a s. (Show a, IsString s, Monoid s) => Style a s
defaultStyleViaShow