module RBST.Pretty (
pretty
, prettyPrint
, compact
, compactPrint
) where
import Data.Char (isSpace)
import Data.List (dropWhileEnd, intercalate)
import RBST.Internal (RBST (..), Size (..), Tree (..), withTree)
pretty :: (Show k, Show a) => RBST k a -> String
pretty = withTree drawPretty
prettyPrint :: (Show k, Show a) => RBST k a -> IO ()
prettyPrint = putStrLn . pretty
compact :: (Show k, Show a) => RBST k a -> String
compact = withTree drawComptact
compactPrint :: (Show k, Show a) => RBST k a -> IO ()
compactPrint = putStrLn . compact
showNode :: (Show k, Show a) => Size -> k -> a -> String
showNode s k x = "(" ++ show k ++ "," ++ show x ++ ") [" ++ (show (unSize s)) ++ "]"
drawComptact, drawPretty :: (Show k, Show a) => Tree k a -> String
drawComptact = unlines . comptactWith showNode
drawPretty = prettyWith showNode
comptactWith
:: forall k a .
(Size -> k -> a -> String)
-> Tree k a
-> [String]
comptactWith _ Empty = []
comptactWith display (Node s k Empty x Empty) = [display s k x]
comptactWith display (Node s k l x r) = [nodeASCII] ++ drawSubTrees
where
nodeASCII = display s k x
drawSubTrees =
let drawR = ws "|" : shift (ws "|-- ") (ws "| ") (comptactWith display r)
drawL = ws "|" : shift (ws "\\__ ") (ws " ") (comptactWith display l)
in drawR ++ drawL
ws = (++) (spaces (length nodeASCII `div` 2))
shift first other = zipWith (++) (first : repeat other)
prettyWith
:: forall k a.
(Size -> k -> a -> String)
-> Tree k a
-> String
prettyWith display = showTree . toBinTree
where
toBinTree :: Tree k a -> BinTree
toBinTree Empty = Leaf
toBinTree (Node s k l x r) = Branch (display s k x) (toBinTree l) (toBinTree r)
data BinTree
= Leaf
| Branch String BinTree BinTree
showTree :: BinTree -> String
showTree Leaf = ""
showTree (Branch label left right) = case (left, right) of
(Leaf, Leaf) -> label
(_, Leaf) -> toLines $
[ spaces rootShiftOnlyLeft ++ label
, spaces branchShiftOnlyLeft ++ "╱"
] ++ map (spaces leftShiftOnlyLeft ++) leftLines
(Leaf, _) -> toLines $
[ spaces rootShiftOnlyRight ++ label
, spaces branchShiftOnlyRight ++ "╲"
] ++ map (spaces rightShiftOnlyRight ++) rightLines
(_, _) -> toLines $
[ spaces rootOffset ++ label
]
++ map (spaces rootOffset ++ ) (branchLines branchHeight)
++ map (spaces childrenOffset ++) (zipChildren leftLines rightLines)
where
leftStr, rightStr :: String
leftStr = showTree left
rightStr = showTree right
leftLines :: [String]
leftLines = lines leftStr
rightLines = lines rightStr
rootLabelMiddle, leftLabelMiddle, rightLabelMiddle :: Int
rootLabelMiddle = middleLabelPos label
leftLabelMiddle = middleLabelPos $ head leftLines
rightLabelMiddle = middleLabelPos $ head rightLines
rootShiftOnlyLeft, leftShiftOnlyLeft, branchShiftOnlyLeft :: Int
(rootShiftOnlyLeft, leftShiftOnlyLeft) = case compare rootLabelMiddle leftLabelMiddle of
EQ -> (1, 0)
GT -> (0, rootLabelMiddle - leftLabelMiddle - 1)
LT -> (leftLabelMiddle - rootLabelMiddle + 1, 0)
branchShiftOnlyLeft = rootLabelMiddle + rootShiftOnlyLeft - 1
rootShiftOnlyRight, rightShiftOnlyRight, branchShiftOnlyRight :: Int
(rootShiftOnlyRight, rightShiftOnlyRight) = case compare rootLabelMiddle rightLabelMiddle of
EQ -> (0, 1)
GT -> (0, rootLabelMiddle - rightLabelMiddle + 1)
LT -> (rightLabelMiddle - rootLabelMiddle - 1, 0)
branchShiftOnlyRight = rootLabelMiddle + rootShiftOnlyRight + 1
leftWidth, rightOffMiddle, childDistance, branchHeight, rootMustMiddle :: Int
leftWidth = 1 + maximum (map length leftLines)
rightOffMiddle = leftWidth + rightLabelMiddle
childDistance = rightOffMiddle - leftLabelMiddle
branchHeight = childDistance `div` 2
rootMustMiddle = (leftLabelMiddle + rightOffMiddle) `div` 2
rootOffset, childrenOffset :: Int
(rootOffset, childrenOffset) = case compare rootLabelMiddle rootMustMiddle of
EQ -> (0, 0)
LT -> (rootMustMiddle - rootLabelMiddle, 0)
GT -> (0, rootLabelMiddle - rootMustMiddle)
zipChildren :: [String] -> [String] -> [String]
zipChildren l [] = l
zipChildren [] r = map (spaces leftWidth ++ ) r
zipChildren (x:xs) (y:ys) =
let xLen = length x
newX = x ++ spaces (leftWidth - xLen)
in (newX ++ y) : zipChildren xs ys
spaces :: Int -> String
spaces n = replicate n ' '
middleLabelPos :: String -> Int
middleLabelPos s =
let (spacePrefix, rest) = span isSpace s
in length spacePrefix + (length (dropWhileEnd isSpace rest) `div` 2)
toLines :: [String] -> String
toLines = intercalate "\n"
branchLines :: Int -> [String]
branchLines n = go 0
where
go :: Int -> [String]
go i
| i == n = []
| otherwise = line : go (i + 1)
where
line :: String
line = spaces (n - i - 1) ++ "╱" ++ spaces (2 * i) ++ "╲"