module Data.Tree.Class
( module Data.Tree.Class )
where
class Tree t where
mkTree :: a -> [t a] -> t a
mkLeaf :: a -> t a
mkLeaf n = mkTree n []
isLeaf :: t a -> Bool
isLeaf = null . getChildren
isInner :: t a -> Bool
isInner = not . isLeaf
getNode :: t a -> a
getChildren :: t a -> [t a]
changeNode :: (a -> a) -> t a -> t a
changeChildren :: ([t a] -> [t a]) -> t a -> t a
setNode :: a -> t a -> t a
setNode n = changeNode (const n)
setChildren :: [t a] -> t a -> t a
setChildren cl = changeChildren (const cl)
foldTree :: (a -> [b] -> b) -> t a -> b
nodesTree :: t a -> [a]
nodesTree = foldTree (\ n rs -> n : concat rs)
depthTree :: t a -> Int
depthTree = foldTree (\ _ rs -> 1 + maximum (0 : rs))
cardTree :: t a -> Int
cardTree = foldTree (\ _ rs -> 1 + sum rs)
formatTree :: (a -> String) -> t a -> String
formatTree nf n = formatNTree' nf (showString "---") (showString " ") n ""
formatNTree' :: Tree t => (a -> String) -> (String -> String) -> (String -> String) -> t a -> String -> String
formatNTree' node2String pf1 pf2 tree
= formatNode
. formatChildren pf2 l
where
n = getNode tree
l = getChildren tree
formatNode = pf1 . foldr (.) id (map trNL (node2String n)) . showNL
trNL '\n' = showNL . pf2
trNL c = showChar c
showNL = showChar '\n'
formatChildren _ []
= id
formatChildren pf (t:ts)
| null ts
= pfl'
. formatTr pf2' t
| otherwise
= pfl'
. formatTr pf1' t
. formatChildren pf ts
where
pf0' = pf . showString indent1
pf1' = pf . showString indent2
pf2' = pf . showString indent3
pfl' = pf . showString indent4
formatTr = formatNTree' node2String pf0'
indent1 = "+---"
indent2 = "| "
indent3 = " "
indent4 = "|\n"