{-# LANGUAGE FlexibleInstances, TypeSynonymInstances #-}
module Math.Combinat.Trees.Nary
(
module Data.Tree
, Tree(..)
, ternaryTrees
, regularNaryTrees
, semiRegularTrees
, countTernaryTrees
, countRegularNaryTrees
, derivTrees
, asciiTreeVertical_
, asciiTreeVertical
, asciiTreeVerticalLeavesOnly
, Dot
, graphvizDotTree
, graphvizDotForest
, classifyTreeNode
, isTreeLeaf , isTreeNode
, isTreeLeaf_ , isTreeNode_
, treeNodeNumberOfChildren
, countTreeNodes
, countTreeLeaves
, countTreeLabelsWith
, countTreeNodesWith
, leftSpine , leftSpine_
, rightSpine , rightSpine_
, leftSpineLength , rightSpineLength
, addUniqueLabelsTree
, addUniqueLabelsForest
, addUniqueLabelsTree_
, addUniqueLabelsForest_
, labelDepthTree
, labelDepthForest
, labelDepthTree_
, labelDepthForest_
, labelNChildrenTree
, labelNChildrenForest
, labelNChildrenTree_
, labelNChildrenForest_
) where
import Data.Tree
import Data.List
import Control.Applicative
import Control.Monad.Trans.State
import Data.Traversable (traverse)
import Math.Combinat.Sets ( listTensor )
import Math.Combinat.Partitions.Multiset ( partitionMultiset )
import Math.Combinat.Compositions ( compositions )
import Math.Combinat.Numbers ( factorial, binomial )
import Math.Combinat.Trees.Graphviz ( Dot , graphvizDotForest , graphvizDotTree )
import Math.Combinat.Classes
import Math.Combinat.ASCII as ASCII
import Math.Combinat.Helper
instance HasNumberOfNodes (Tree a) where
numberOfNodes = go where
go (Node label subforest) = if null subforest
then 0
else 1 + sum' (map go subforest)
instance HasNumberOfLeaves (Tree a) where
numberOfLeaves = go where
go (Node label subforest) = if null subforest
then 1
else sum' (map go subforest)
regularNaryTrees
:: Int
-> Int
-> [Tree ()]
regularNaryTrees d = go where
go 0 = [ Node () [] ]
go n = [ Node () cs
| is <- compositions d (n-1)
, cs <- listTensor [ go i | i<-is ]
]
ternaryTrees :: Int -> [Tree ()]
ternaryTrees = regularNaryTrees 3
countRegularNaryTrees :: (Integral a, Integral b) => a -> b -> Integer
countRegularNaryTrees d n = binomial (dd*nn) nn `div` ((dd-1)*nn+1) where
dd = fromIntegral d :: Integer
nn = fromIntegral n :: Integer
countTernaryTrees :: Integral a => a -> Integer
countTernaryTrees = countRegularNaryTrees (3::Int)
semiRegularTrees
:: [Int]
-> Int
-> [Tree ()]
semiRegularTrees [] n = if n==0 then [Node () []] else []
semiRegularTrees dset_ n =
if head dset >=1
then go n
else error "semiRegularTrees: expecting a list of positive integers"
where
dset = map head $ group $ sort $ dset_
go 0 = [ Node () [] ]
go n = [ Node () cs
| d <- dset
, is <- compositions d (n-1)
, cs <- listTensor [ go i | i<-is ]
]
asciiTreeVertical_ :: Tree a -> ASCII
asciiTreeVertical_ tree = ASCII.asciiFromLines (go tree) where
go :: Tree b -> [String]
go (Node _ cs) = case cs of
[] -> ["-*"]
_ -> concat $ mapWithFirstLast f $ map go cs
f :: Bool -> Bool -> [String] -> [String]
f bf bl (l:ls) = let indent = if bl then " " else "| "
gap = if bl then [] else ["| "]
branch = if bl && not bf
then "\\-"
else if bf then "@-"
else "+-"
in (branch++l) : map (indent++) ls ++ gap
instance DrawASCII (Tree ()) where
ascii = asciiTreeVertical_
asciiTreeVertical :: Show a => Tree a -> ASCII
asciiTreeVertical tree = ASCII.asciiFromLines (go tree) where
go :: Show b => Tree b -> [String]
go (Node x cs) = case cs of
[] -> ["-- " ++ show x]
_ -> concat $ mapWithFirstLast (f (show x)) $ map go cs
f :: String -> Bool -> Bool -> [String] -> [String]
f label bf bl (l:ls) =
let spaces = (map (const ' ') label )
dashes = (map (const '-') spaces )
indent = if bl then " " ++spaces++" " else " |" ++ spaces ++ " "
gap = if bl then [] else [" |" ++ spaces ++ " "]
branch = if bl && not bf
then " \\"++dashes++"--"
else if bf
then "-(" ++ label ++ ")-"
else " +" ++ dashes ++ "--"
in (branch++l) : map (indent++) ls ++ gap
asciiTreeVerticalLeavesOnly :: Show a => Tree a -> ASCII
asciiTreeVerticalLeavesOnly tree = ASCII.asciiFromLines (go tree) where
go :: Show b => Tree b -> [String]
go (Node x cs) = case cs of
[] -> ["- " ++ show x]
_ -> concat $ mapWithFirstLast f $ map go cs
f :: Bool -> Bool -> [String] -> [String]
f bf bl (l:ls) = let indent = if bl then " " else "| "
gap = if bl then [] else ["| "]
branch = if bl && not bf
then "\\-"
else if bf then "@-"
else "+-"
in (branch++l) : map (indent++) ls ++ gap
leftSpine :: Tree a -> ([a],a)
leftSpine = go where
go (Node x cs) = case cs of
[] -> ([],x)
_ -> let (xs,y) = go (head cs) in (x:xs,y)
rightSpine :: Tree a -> ([a],a)
rightSpine = go where
go (Node x cs) = case cs of
[] -> ([],x)
_ -> let (xs,y) = go (last cs) in (x:xs,y)
leftSpine_ :: Tree a -> [a]
leftSpine_ = go where
go (Node x cs) = case cs of
[] -> []
_ -> x : go (head cs)
rightSpine_ :: Tree a -> [a]
rightSpine_ = go where
go (Node x cs) = case cs of
[] -> []
_ -> x : go (last cs)
leftSpineLength :: Tree a -> Int
leftSpineLength = go 0 where
go n (Node x cs) = case cs of
[] -> n
_ -> go (n+1) (head cs)
rightSpineLength :: Tree a -> Int
rightSpineLength = go 0 where
go n (Node x cs) = case cs of
[] -> n
_ -> go (n+1) (last cs)
classifyTreeNode :: Tree a -> Either a a
classifyTreeNode (Node x cs) = case cs of { [] -> Left x ; _ -> Right x }
isTreeLeaf :: Tree a -> Maybe a
isTreeLeaf (Node x cs) = case cs of { [] -> Just x ; _ -> Nothing }
isTreeNode :: Tree a -> Maybe a
isTreeNode (Node x cs) = case cs of { [] -> Nothing ; _ -> Just x }
isTreeLeaf_ :: Tree a -> Bool
isTreeLeaf_ (Node x cs) = case cs of { [] -> True ; _ -> False }
isTreeNode_ :: Tree a -> Bool
isTreeNode_ (Node x cs) = case cs of { [] -> False ; _ -> True }
treeNodeNumberOfChildren :: Tree a -> Int
treeNodeNumberOfChildren (Node _ cs) = length cs
countTreeNodes :: Tree a -> Int
countTreeNodes = go where
go (Node x cs) = case cs of
[] -> 0
_ -> 1 + sum (map go cs)
countTreeLeaves :: Tree a -> Int
countTreeLeaves = go where
go (Node x cs) = case cs of
[] -> 1
_ -> sum (map go cs)
countTreeLabelsWith :: (a -> Bool) -> Tree a -> Int
countTreeLabelsWith f = go where
go (Node label cs) = (if f label then 1 else 0) + sum (map go cs)
countTreeNodesWith :: (Tree a -> Bool) -> Tree a -> Int
countTreeNodesWith f = go where
go node@(Node _ cs) = (if f node then 1 else 0) + sum (map go cs)
addUniqueLabelsTree :: Tree a -> Tree (a,Int)
addUniqueLabelsTree tree = head (addUniqueLabelsForest [tree])
addUniqueLabelsForest :: Forest a -> Forest (a,Int)
addUniqueLabelsForest forest = evalState (mapM globalAction forest) 1 where
globalAction tree =
unwrapMonad $ traverse localAction tree
localAction x = WrapMonad $ do
i <- get
put (i+1)
return (x,i)
addUniqueLabelsTree_ :: Tree a -> Tree Int
addUniqueLabelsTree_ = fmap snd . addUniqueLabelsTree
addUniqueLabelsForest_ :: Forest a -> Forest Int
addUniqueLabelsForest_ = map (fmap snd) . addUniqueLabelsForest
labelDepthTree :: Tree a -> Tree (a,Int)
labelDepthTree tree = worker 0 tree where
worker depth (Node label subtrees) = Node (label,depth) (map (worker (depth+1)) subtrees)
labelDepthForest :: Forest a -> Forest (a,Int)
labelDepthForest forest = map labelDepthTree forest
labelDepthTree_ :: Tree a -> Tree Int
labelDepthTree_ = fmap snd . labelDepthTree
labelDepthForest_ :: Forest a -> Forest Int
labelDepthForest_ = map (fmap snd) . labelDepthForest
labelNChildrenTree :: Tree a -> Tree (a,Int)
labelNChildrenTree (Node x subforest) =
Node (x, length subforest) (map labelNChildrenTree subforest)
labelNChildrenForest :: Forest a -> Forest (a,Int)
labelNChildrenForest forest = map labelNChildrenTree forest
labelNChildrenTree_ :: Tree a -> Tree Int
labelNChildrenTree_ = fmap snd . labelNChildrenTree
labelNChildrenForest_ :: Forest a -> Forest Int
labelNChildrenForest_ = map (fmap snd) . labelNChildrenForest
derivTrees :: [Int] -> [Tree ()]
derivTrees xs = derivTrees' (map (+1) xs)
derivTrees' :: [Int] -> [Tree ()]
derivTrees' [] = []
derivTrees' [n] =
if n>=1
then [unfoldTree f 1]
else []
where
f k = if k<n then ((),[k+1]) else ((),[])
derivTrees' ks =
if and (map (>0) ks)
then
[ Node () sub
| part <- parts
, let subtrees = map g part
, sub <- listTensor subtrees
]
else []
where
parts = partitionMultiset ks
g xs = derivTrees' (map (\x->x-1) xs)