Safe Haskell | None |
---|---|
Language | Haskell2010 |
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:
- data BinTree a
- leaf :: BinTree ()
- graft :: BinTree (BinTree a) -> BinTree a
- data BinTree' a b
- forgetNodeDecorations :: BinTree' a b -> BinTree a
- data Paren
- parenthesesToString :: [Paren] -> String
- stringToParentheses :: String -> [Paren]
- numberOfNodes :: HasNumberOfNodes t => t -> Int
- numberOfLeaves :: HasNumberOfLeaves t => t -> Int
- toRoseTree :: BinTree a -> Tree (Maybe a)
- toRoseTree' :: BinTree' a b -> Tree (Either b a)
- module Data.Tree
- enumerateLeaves_ :: BinTree a -> BinTree Int
- enumerateLeaves :: BinTree a -> BinTree (a, Int)
- enumerateLeaves' :: BinTree a -> (Int, BinTree (a, Int))
- nestedParentheses :: Int -> [[Paren]]
- randomNestedParentheses :: RandomGen g => Int -> g -> ([Paren], g)
- nthNestedParentheses :: Int -> Integer -> [Paren]
- countNestedParentheses :: Int -> Integer
- fasc4A_algorithm_P :: Int -> [[Paren]]
- fasc4A_algorithm_W :: RandomGen g => Int -> g -> ([Paren], g)
- fasc4A_algorithm_U :: Int -> Integer -> [Paren]
- binaryTrees :: Int -> [BinTree ()]
- countBinaryTrees :: Int -> Integer
- binaryTreesNaive :: Int -> [BinTree ()]
- randomBinaryTree :: RandomGen g => Int -> g -> (BinTree (), g)
- fasc4A_algorithm_R :: RandomGen g => Int -> g -> (BinTree' Int Int, g)
- asciiBinaryTree_ :: BinTree a -> ASCII
- type Dot = String
- graphvizDotBinTree :: Show a => String -> BinTree a -> Dot
- graphvizDotBinTree' :: (Show a, Show b) => String -> BinTree' a b -> Dot
- graphvizDotForest :: Show a => Bool -> Bool -> String -> Forest a -> Dot
- graphvizDotTree :: Show a => Bool -> String -> Tree a -> Dot
- forestToNestedParentheses :: Forest a -> [Paren]
- forestToBinaryTree :: Forest a -> BinTree ()
- nestedParenthesesToForest :: [Paren] -> Maybe (Forest ())
- nestedParenthesesToForestUnsafe :: [Paren] -> Forest ()
- nestedParenthesesToBinaryTree :: [Paren] -> Maybe (BinTree ())
- nestedParenthesesToBinaryTreeUnsafe :: [Paren] -> BinTree ()
- binaryTreeToForest :: BinTree a -> Forest ()
- binaryTreeToNestedParentheses :: BinTree a -> [Paren]
Types
A binary tree with leaves decorated with type a
.
Monad BinTree Source | |
Functor BinTree Source | |
Applicative BinTree Source | |
Foldable BinTree Source | |
Traversable BinTree Source | |
Eq a => Eq (BinTree a) Source | |
Ord a => Ord (BinTree a) Source | |
Read a => Read (BinTree a) Source | |
Show a => Show (BinTree a) Source | |
HasNumberOfLeaves (BinTree a) Source | |
HasNumberOfNodes (BinTree a) Source | |
DrawASCII (BinTree ()) Source |
A binary tree with leaves and internal nodes decorated
with types a
and b
, respectively.
forgetNodeDecorations :: BinTree' a b -> BinTree a Source
parenthesesToString :: [Paren] -> String Source
stringToParentheses :: String -> [Paren] Source
numberOfNodes :: HasNumberOfNodes t => t -> Int Source
numberOfLeaves :: HasNumberOfLeaves t => t -> Int Source
Conversion to rose trees (Data.Tree
)
toRoseTree :: BinTree a -> Tree (Maybe a) Source
Convert a binary tree to a rose tree (from Data.Tree)
toRoseTree' :: BinTree' a b -> Tree (Either b a) Source
module Data.Tree
Enumerate leaves
enumerateLeaves_ :: BinTree a -> BinTree Int Source
Enumerates the leaves a tree, starting from 0, ignoring old labels
enumerateLeaves :: BinTree a -> BinTree (a, Int) Source
Enumerates the leaves a tree, starting from zero
enumerateLeaves' :: BinTree a -> (Int, BinTree (a, Int)) Source
Enumerates the leaves a tree, starting from zero, and also returns the number of leaves
Nested parentheses
nestedParentheses :: Int -> [[Paren]] Source
Generates all sequences of nested parentheses of length 2n
in
lexigraphic order.
Synonym for fasc4A_algorithm_P
.
randomNestedParentheses :: RandomGen g => Int -> g -> ([Paren], g) Source
Synonym for fasc4A_algorithm_W
.
nthNestedParentheses :: Int -> Integer -> [Paren] Source
Synonym for fasc4A_algorithm_U
.
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.
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
:: 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.
Generates graphviz .dot
file from a tree. The first argument is
the name of the graph.
Bijections
forestToNestedParentheses :: Forest a -> [Paren] Source
forestToBinaryTree :: Forest a -> BinTree () Source
nestedParenthesesToForest :: [Paren] -> Maybe (Forest ()) Source
nestedParenthesesToForestUnsafe :: [Paren] -> Forest () Source
nestedParenthesesToBinaryTree :: [Paren] -> Maybe (BinTree ()) Source
nestedParenthesesToBinaryTreeUnsafe :: [Paren] -> BinTree () Source
binaryTreeToForest :: BinTree a -> Forest () Source
binaryTreeToNestedParentheses :: BinTree a -> [Paren] Source