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:
Synopsis
- 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)
- data Tree a = Node {}
- type Forest a = [Tree a]
- 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
.
Instances
A binary tree with leaves and internal nodes decorated
with types a
and b
, respectively.
Instances
(Eq b, Eq a) => Eq (BinTree' a b) Source # | |
(Ord b, Ord a) => Ord (BinTree' a b) Source # | |
Defined in Math.Combinat.Trees.Binary | |
(Read b, Read a) => Read (BinTree' a b) Source # | |
(Show b, Show a) => Show (BinTree' a b) Source # | |
HasNumberOfLeaves (BinTree' a b) Source # | |
Defined in Math.Combinat.Trees.Binary numberOfLeaves :: BinTree' a b -> Int Source # | |
HasNumberOfNodes (BinTree' a b) Source # | |
Defined in Math.Combinat.Trees.Binary numberOfNodes :: BinTree' a b -> Int Source # |
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)
Multi-way trees, also known as rose trees.
Instances
Monad Tree | |
Functor Tree | |
MonadFix Tree | Since: containers-0.5.11 |
Applicative Tree | |
Foldable Tree | |
Defined in Data.Tree fold :: Monoid m => Tree m -> m # foldMap :: Monoid m => (a -> m) -> Tree a -> m # foldr :: (a -> b -> b) -> b -> Tree a -> b # foldr' :: (a -> b -> b) -> b -> Tree a -> b # foldl :: (b -> a -> b) -> b -> Tree a -> b # foldl' :: (b -> a -> b) -> b -> Tree a -> b # foldr1 :: (a -> a -> a) -> Tree a -> a # foldl1 :: (a -> a -> a) -> Tree a -> a # elem :: Eq a => a -> Tree a -> Bool # maximum :: Ord a => Tree a -> a # | |
Traversable Tree | |
Eq1 Tree | Since: containers-0.5.9 |
Ord1 Tree | Since: containers-0.5.9 |
Read1 Tree | Since: containers-0.5.9 |
Show1 Tree | Since: containers-0.5.9 |
MonadZip Tree | |
Eq a => Eq (Tree a) | |
Data a => Data (Tree a) | |
Defined in Data.Tree gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tree a -> c (Tree a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tree a) # toConstr :: Tree a -> Constr # dataTypeOf :: Tree a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tree a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tree a)) # gmapT :: (forall b. Data b => b -> b) -> Tree a -> Tree a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tree a -> r # gmapQ :: (forall d. Data d => d -> u) -> Tree a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tree a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tree a -> m (Tree a) # | |
Read a => Read (Tree a) | |
Show a => Show (Tree a) | |
Generic (Tree a) | |
NFData a => NFData (Tree a) | |
HasNumberOfLeaves (Tree a) Source # | |
Defined in Math.Combinat.Trees.Nary numberOfLeaves :: Tree a -> Int Source # | |
HasNumberOfNodes (Tree a) Source # | |
Defined in Math.Combinat.Trees.Nary numberOfNodes :: Tree a -> Int Source # | |
DrawASCII (Tree ()) Source # | |
Generic1 Tree | |
type Rep (Tree a) | Since: containers-0.5.8 |
Defined in Data.Tree type Rep (Tree a) = D1 (MetaData "Tree" "Data.Tree" "containers-0.5.11.0" False) (C1 (MetaCons "Node" PrefixI True) (S1 (MetaSel (Just "rootLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Just "subForest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Forest a)))) | |
type Rep1 Tree | Since: containers-0.5.8 |
Defined in Data.Tree type Rep1 Tree = D1 (MetaData "Tree" "Data.Tree" "containers-0.5.11.0" False) (C1 (MetaCons "Node" PrefixI True) (S1 (MetaSel (Just "rootLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1 :*: S1 (MetaSel (Just "subForest") NoSourceUnpackedness NoSourceStrictness DecidedLazy) ([] :.: Rec1 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
.
countNestedParentheses :: Int -> Integer Source #
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 #
nestedParenthesesToForestUnsafe :: [Paren] -> Forest () Source #
nestedParenthesesToBinaryTreeUnsafe :: [Paren] -> BinTree () Source #
binaryTreeToForest :: BinTree a -> Forest () Source #
binaryTreeToNestedParentheses :: BinTree a -> [Paren] Source #