{-# LANGUAGE RecordWildCards #-}
module Data.Monoid.TreeDiagram
( TreeDiagram
, showTreeDiagram
, printTreeDiagram
, singleton
, subtree
, width
, height
) where
import Data.List (intersperse)
import Data.Semigroup (Semigroup(..))
concatShowS :: [ShowS] -> ShowS
concatShowS = foldr (.) id
replicateChar :: Int -> Char -> ShowS
replicateChar n = concatShowS . replicate n . showChar
data TreeDiagram = Empty | NonEmpty
{ graph :: GraphEnvironment -> ShowS
, graphWidth :: Int
, graphIndent :: Int
, graphDedent :: Int
, rows :: [(Int,ShowS)]
, leftLimit :: (Int,Int)
, rightLimit :: (Int,Int)
}
data GraphEnvironment = GraphEnvironment
{ isLeftmost :: !Bool
, isRightmost :: !Bool
, uptickIndex :: !Int
}
showTreeDiagram :: TreeDiagram -> ShowS
showTreeDiagram Empty = id
showTreeDiagram NonEmpty{..} =
let graphLine =
replicateChar graphIndent ' ' .
graph GraphEnvironment
{ isLeftmost = True
, isRightmost = True
, uptickIndex = graphWidth
}
rowLines = snd <$> rows
in concatShowS . intersperse (showChar '\n') $ graphLine : rowLines
printTreeDiagram :: TreeDiagram -> IO ()
printTreeDiagram = putStrLn . ($[]) . showTreeDiagram
singleton :: Show a => a -> TreeDiagram
singleton a = NonEmpty
{ graph = const $ shows a
, graphWidth = length $ show a
, graphIndent = 0
, graphDedent = 0
, rows = []
, leftLimit = (0,0)
, rightLimit = (0,0)
}
instance Semigroup TreeDiagram where
(<>) = mappend
instance Monoid TreeDiagram where
mempty = Empty
Empty `mappend` d = d
d `mappend` Empty = d
a `mappend` b = NonEmpty
{ graph = \o ->
let uptickIndex' = uptickIndex o - graphWidth a
midline = if 0 <= uptickIndex' && uptickIndex' < graphPadding
then replicateChar uptickIndex' '─' .
showChar '┴' .
replicateChar (graphPadding - 1 - uptickIndex') '─'
else replicateChar graphPadding '─'
in
graph a o{ isRightmost = False } .
midline .
graph b o{ isLeftmost = False, uptickIndex = uptickIndex' - graphPadding }
, graphWidth = graphWidth a + graphPadding + graphWidth b
, graphIndent = graphIndent a
, graphDedent = graphDedent b
, rows = alongside (width a + padding) (rows a) (rows b)
, leftLimit = leftLimit a
, rightLimit = rightLimit b
}
where graphPadding = graphDedent a + padding + graphIndent b
padding = fromEnum (blo <= ahi && alo <= bhi)
(alo,ahi) = rightLimit a
(blo,bhi) = leftLimit b
width :: TreeDiagram -> Int
width Empty = 0
width d = graphIndent d + graphWidth d + graphDedent d
height :: TreeDiagram -> Int
height Empty = 0
height d = 1 + length (rows d)
alongside :: Int -> [(Int,ShowS)] -> [(Int,ShowS)] -> [(Int,ShowS)]
alongside n ((mx,dx):xs) ((my,dy):ys) = (n + my, dx . replicateChar (n - mx) ' ' . dy) : alongside n xs ys
alongside _ xs [] = xs
alongside n [] ys = [(n + my, replicateChar n ' '. dy) | (my,dy) <- ys]
downtick :: GraphEnvironment -> ShowS
downtick GraphEnvironment{..} = case (isLeftmost, isRightmost, uptickIndex == 0) of
(False, False, False) -> showChar '┬'
(False, False, True) -> showChar '┼'
(False, True, False) -> showChar '┐'
(False, True, True) -> showChar '┤'
(True, False, False) -> showChar '┌'
(True, False, True) -> showChar '├'
(True, True, False) -> showChar '╷'
(True, True, True) -> showChar '│'
subtree :: TreeDiagram -> TreeDiagram
subtree Empty = NonEmpty
{ graph = downtick
, graphWidth = 1
, graphIndent = 0
, graphDedent = 0
, rows = [(1, showChar '│'),(1, showChar '╵')]
, leftLimit = (1,2)
, rightLimit = (1,2)
}
subtree NonEmpty{..} = NonEmpty
{ graph = downtick
, graphWidth = 1
, graphIndent = uptickIndent
, graphDedent = graphIndent + graphWidth + graphDedent - 1 - uptickIndent
, rows = (uptickIndent + 1, replicateChar uptickIndent ' ' . showChar '│')
: (graphIndent + graphWidth, replicateChar graphIndent ' ' . graphLine)
: rows
, leftLimit = (if llo > 1 then llo + 2 else if graphWidth > 1 then 2 else 1, lhi + 2)
, rightLimit = (if rlo > 1 then rlo + 2 else if graphWidth > 2 then 2 else 1, rhi + 2)
}
where uptickIndent = graphIndent + uptickIndex
uptickIndex = graphWidth `div` 2
(llo,lhi) = leftLimit
(rlo,rhi) = rightLimit
graphLine = graph GraphEnvironment
{ isLeftmost = True
, isRightmost = True
, uptickIndex = uptickIndex
}