combinat-0.2.7.0: Generation of various combinatorial objects.

Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Trees.Binary

Contents

Description

Binary trees, forests, etc. See: Donald E. Knuth: The Art of Computer Programming, vol 4, pre-fascicle 4A.

For example, here are all the binary trees on 4 nodes:

Synopsis

Types

data BinTree a Source

A binary tree with leaves decorated with type a.

Constructors

Branch (BinTree a) (BinTree a) 
Leaf a 

Instances

data BinTree' a b Source

A binary tree with leaves and internal nodes decorated with types a and b, respectively.

Constructors

Branch' (BinTree' a b) b (BinTree' a b) 
Leaf' a 

Instances

(Eq a, Eq b) => Eq (BinTree' a b) 
(Ord a, Ord b) => Ord (BinTree' a b) 
(Read a, Read b) => Read (BinTree' a b) 
(Show a, Show b) => Show (BinTree' a b) 

data Paren Source

Constructors

LeftParen 
RightParen 

Conversion to rose trees (Data.Tree)

toRoseTree :: BinTree a -> Tree (Maybe a) Source

Convert a binary tree to a rose tree (from Data.Tree)

module Data.Tree

Nested parentheses

nestedParentheses :: Int -> [[Paren]] Source

Generates all sequences of nested parentheses of length 2n in lexigraphic order.

Synonym for fasc4A_algorithm_P.

fasc4A_algorithm_P :: Int -> [[Paren]] Source

Generates all sequences of nested parentheses of length 2n. Order is lexicographical (when right parentheses are considered smaller then left ones). Based on "Algorithm P" in Knuth, but less efficient because of the "idiomatic" code.

fasc4A_algorithm_W :: RandomGen g => Int -> g -> ([Paren], g) Source

Generates a uniformly random sequence of nested parentheses of length 2n. Based on "Algorithm W" in Knuth.

fasc4A_algorithm_U Source

Arguments

:: Int

n

-> Integer

N; should satisfy 1 <= N <= C(n)

-> [Paren] 

Nth sequence of nested parentheses of length 2n. The order is the same as in fasc4A_algorithm_P. Based on "Algorithm U" in Knuth.

Generating binary trees

binaryTrees :: Int -> [BinTree ()] Source

Generates all binary trees with n nodes. At the moment just a synonym for binaryTreesNaive.

countBinaryTrees :: Int -> Integer Source

# = Catalan(n) = \frac { 1 } { n+1 } \binom { 2n } { n }.

This is also the counting function for forests and nested parentheses.

binaryTreesNaive :: Int -> [BinTree ()] Source

Generates all binary trees with n nodes. The naive algorithm.

randomBinaryTree :: RandomGen g => Int -> g -> (BinTree (), g) Source

Generates an uniformly random binary tree, using fasc4A_algorithm_R.

fasc4A_algorithm_R :: RandomGen g => Int -> g -> (BinTree' Int Int, g) Source

Grows a uniformly random binary tree. "Algorithm R" (Remy's procudere) in Knuth. Nodes are decorated with odd numbers, leaves with even numbers (from the set [0..2n]). Uses mutable arrays internally.

ASCII drawing

asciiBinaryTree_ :: BinTree a -> ASCII Source

Draws a binary tree in ASCII, ignoring node labels.

Example:

autoTabulate RowMajor (Right 5) $ map asciiBinaryTree_ $ binaryTrees 4

Graphviz drawing

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.

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.

Bijections