module Data.Generics.Fixplate.Draw
(
drawTree
, showTree
, graphvizTree
, drawTreeWith
, showTreeWith
, graphvizTreeWith
)
where
import Data.Foldable
import Data.Traversable ()
import Data.Generics.Fixplate.Base
import Data.Generics.Fixplate.Open
import Data.Generics.Fixplate.Attributes ( enumerateNodes_ )
import Data.Generics.Fixplate.Traversals ( universe )
drawTree :: (Functor f, Foldable f, ShowF f) => Mu f -> IO ()
drawTree = putStrLn . showTree
drawTreeWith :: (Functor f, Foldable f) => (f Hole -> String) -> Mu f -> IO ()
drawTreeWith pp = putStrLn . showTreeWith pp
data Void = Void ; instance Show Void where show _ = "_"
showTree :: (Functor f, Foldable f, ShowF f) => Mu f -> String
showTree = showTreeWith pp where
pp t = showF (fmap (const Void) t)
showTreeWith :: (Functor f, Foldable f) => (f Hole -> String) -> Mu f -> String
showTreeWith pprint = unlines . map mkLine . go [False] where
go bars (Fix s) = ( bars , this ) : rest where
this = pprint $ fmap (const Hole) s
rest = Prelude.concat $ reverse $ zipWith worker theBars (toRevList s)
worker b t = go (b:bars) t
theBars = False : repeat True
mkLine (b:bs, str) = Prelude.concatMap (_branch style) (reverse bs) ++ (_twig style b) ++ str
mkLine ([] , _ ) = error "showTreeWith/mkLine: shouldn't happen"
style = defaultStyle
defaultStyle :: Style
defaultStyle = Style
{ _twigNorm = " |-- "
, _twigLast = " \\-- "
, _branchNorm = " | "
, _branchLast = " "
}
data Style = Style
{ _twigNorm :: !String
, _twigLast :: !String
, _branchNorm :: !String
, _branchLast :: !String
}
_twig :: Style -> Bool -> String
_twig style b = if b then _twigNorm style else _twigLast style
_branch :: Style -> Bool -> String
_branch style b = if b then _branchNorm style else _branchLast style
graphvizTree :: (Traversable f, ShowF f) => Mu f -> String
graphvizTree = graphvizTreeWith pp where
pp t = showF (fmap (const Void) t)
graphvizTreeWith :: (Traversable f) => (f Hole -> String) -> Mu f -> String
graphvizTreeWith pp tree = unlines dot where
dot = header : viznodes ++ vizedges ++ [footer]
header = "digraph tree {"
footer = "}"
enum = enumerateNodes_ tree
node i = "node" ++ show i
only = fmap (const Hole)
viznodes =
[ node i ++ " [ label=\"" ++ escape (pp (only s)) ++ "\" ] ;"
| Fix (Ann i s) <- universe enum
]
vizedges = Prelude.concat
[ [ node i ++ " -> " ++ node j ++ " ;"
| Fix (Ann j _) <- toList s
]
| Fix (Ann i s) <- universe enum
]
escape :: String -> String
escape = Prelude.concatMap f where
f c = if Prelude.elem c stuff then '\\':c:[] else c:[]
stuff = "\\\""