combinat-0.2.7.0: Generation of various combinatorial objects.

Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Trees.Nary

Contents

Description

N-ary trees.

Synopsis

Regular trees

ternaryTrees :: Int -> [Tree ()] Source

Ternary trees on n nodes (synonym for regularNaryTrees 3)

regularNaryTrees Source

Arguments

:: Int

degree = number of children of each node

-> Int

number of nodes

-> [Tree ()] 

regularNaryTrees d n returns the list of (rooted) trees on n nodes where each node has exactly d children. Note that the leaves do not count in n. Naive algorithm.

semiRegularTrees Source

Arguments

:: [Int]

set of allowed number of children

-> Int

number of nodes

-> [Tree ()] 

All trees on n nodes where the number of children of all nodes is in element of the given set. Example:

autoTabulate RowMajor (Right 5) $ map asciiTreeVertical 
                                $ map labelNChildrenTree_ 
                                $ semiRegularTrees [2,3] 2

[ length $ semiRegularTrees [2,3] n | n<-[0..] ] == [1,2,10,66,498,4066,34970,312066,2862562,26824386,...]

The latter sequence is A027307 in OEIS: https://oeis.org/A027307

Remark: clearly, we have

semiRegularTrees [d] n == regularNaryTrees d n

countTernaryTrees :: Integral a => a -> Integer Source

# = \frac {1} {(2n+1} \binom {3n} {n}

countRegularNaryTrees :: (Integral a, Integral b) => a -> b -> Integer Source

We have

length (regularNaryTrees d n) == countRegularNaryTrees d n == \frac {1} {(d-1)n+1} \binom {dn} {n} 

"derivation trees"

derivTrees :: [Int] -> [Tree ()] Source

Computes the set of equivalence classes of rooted trees (in the sense that the leaves of a node are unordered) with n = length ks leaves where the set of heights of the leaves matches the given set of numbers. The height is defined as the number of edges from the leaf to the root.

TODO: better name?

ASCII drawings

asciiTreeVertical_ :: Tree a -> ASCII Source

Vertical ASCII drawing of a tree, without labels. Example:

autoTabulate RowMajor (Right 5) $ map asciiTreeVertical_ $ regularNaryTrees 2 4 

Nodes are denoted by @, leaves by *.

asciiTreeVertical :: Show a => Tree a -> ASCII Source

Prints all labels. Example:

asciiTreeVertical $ addUniqueLabelsTree_ $ (regularNaryTrees 3 9) !! 666

Nodes are denoted by (label), leaves by label.

asciiTreeVerticalLeavesOnly :: Show a => Tree a -> ASCII Source

Prints the labels for the leaves, but not for the nodes.

Graphviz drawing

graphvizDotTree Source

Arguments

:: Show a 
=> Bool

reverse the direction of the arrow

-> String

name of the graph

-> Tree a 
-> Dot 

Generates graphviz .dot file from a tree. The first argument is the name of the graph.

graphvizDotForest Source

Arguments

:: Show a 
=> Bool

make the individual trees clustered subgraphs

-> Bool

reverse the direction of the arrows

-> String

name of the graph

-> Forest a 
-> Dot 

Generates graphviz .dot file from a forest. The first argument tells whether to make the individual trees clustered subgraphs; the second is the name of the graph.

Classifying nodes

classifyTreeNode :: Tree a -> Either a a Source

Left is leaf, Right is node

Counting nodes

Left and right spines

leftSpine :: Tree a -> ([a], a) Source

The leftmost spine (the second element of the pair is the leaf node)

leftSpine_ :: Tree a -> [a] Source

The leftmost spine without the leaf node

rightSpine :: Tree a -> ([a], a) Source

rightSpine_ :: Tree a -> [a] Source

leftSpineLength :: Tree a -> Int Source

The length (number of edges) on the left spine

leftSpineLength tree == length (leftSpine_ tree)

Unique labels

addUniqueLabelsTree :: Tree a -> Tree (a, Int) Source

Adds unique labels to the nodes (including leaves) of a Tree.

addUniqueLabelsForest :: Forest a -> Forest (a, Int) Source

Adds unique labels to the nodes (including leaves) of a Forest

Labelling by depth

labelDepthTree :: Tree a -> Tree (a, Int) Source

Attaches the depth to each node. The depth of the root is 0.

Labelling by number of children

labelNChildrenTree :: Tree a -> Tree (a, Int) Source

Attaches the number of children to each node.