combinat-0.2.10.0: Generate and manipulate various combinatorial objects.
Safe HaskellNone
LanguageHaskell2010

Math.Combinat.Trees.Nary

Description

N-ary trees.

Synopsis

Types

module Data.Tree

data Tree a #

Non-empty, possibly infinite, multi-way trees; also known as rose trees.

Constructors

Node 

Fields

Instances

Instances details
Monad Tree 
Instance details

Defined in Data.Tree

Methods

(>>=) :: Tree a -> (a -> Tree b) -> Tree b #

(>>) :: Tree a -> Tree b -> Tree b #

return :: a -> Tree a #

Functor Tree 
Instance details

Defined in Data.Tree

Methods

fmap :: (a -> b) -> Tree a -> Tree b #

(<$) :: a -> Tree b -> Tree a #

MonadFix Tree

Since: containers-0.5.11

Instance details

Defined in Data.Tree

Methods

mfix :: (a -> Tree a) -> Tree a #

Applicative Tree 
Instance details

Defined in Data.Tree

Methods

pure :: a -> Tree a #

(<*>) :: Tree (a -> b) -> Tree a -> Tree b #

liftA2 :: (a -> b -> c) -> Tree a -> Tree b -> Tree c #

(*>) :: Tree a -> Tree b -> Tree b #

(<*) :: Tree a -> Tree b -> Tree a #

Foldable Tree 
Instance details

Defined in Data.Tree

Methods

fold :: Monoid m => Tree m -> m #

foldMap :: Monoid m => (a -> m) -> Tree a -> 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 #

toList :: Tree a -> [a] #

null :: Tree a -> Bool #

length :: Tree a -> Int #

elem :: Eq a => a -> Tree a -> Bool #

maximum :: Ord a => Tree a -> a #

minimum :: Ord a => Tree a -> a #

sum :: Num a => Tree a -> a #

product :: Num a => Tree a -> a #

Traversable Tree 
Instance details

Defined in Data.Tree

Methods

traverse :: Applicative f => (a -> f b) -> Tree a -> f (Tree b) #

sequenceA :: Applicative f => Tree (f a) -> f (Tree a) #

mapM :: Monad m => (a -> m b) -> Tree a -> m (Tree b) #

sequence :: Monad m => Tree (m a) -> m (Tree a) #

Eq1 Tree

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftEq :: (a -> b -> Bool) -> Tree a -> Tree b -> Bool #

Ord1 Tree

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftCompare :: (a -> b -> Ordering) -> Tree a -> Tree b -> Ordering #

Read1 Tree

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Tree a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Tree a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Tree a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Tree a] #

Show1 Tree

Since: containers-0.5.9

Instance details

Defined in Data.Tree

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Tree a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Tree a] -> ShowS #

MonadZip Tree 
Instance details

Defined in Data.Tree

Methods

mzip :: Tree a -> Tree b -> Tree (a, b) #

mzipWith :: (a -> b -> c) -> Tree a -> Tree b -> Tree c #

munzip :: Tree (a, b) -> (Tree a, Tree b) #

Eq a => Eq (Tree a) 
Instance details

Defined in Data.Tree

Methods

(==) :: Tree a -> Tree a -> Bool #

(/=) :: Tree a -> Tree a -> Bool #

Data a => Data (Tree a) 
Instance details

Defined in Data.Tree

Methods

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 :: forall r r'. (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) 
Instance details

Defined in Data.Tree

Show a => Show (Tree a) 
Instance details

Defined in Data.Tree

Methods

showsPrec :: Int -> Tree a -> ShowS #

show :: Tree a -> String #

showList :: [Tree a] -> ShowS #

Generic (Tree a)

Since: containers-0.5.8

Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: Type -> Type #

Methods

from :: Tree a -> Rep (Tree a) x #

to :: Rep (Tree a) x -> Tree a #

NFData a => NFData (Tree a) 
Instance details

Defined in Data.Tree

Methods

rnf :: Tree a -> () #

HasNumberOfLeaves (Tree a) Source # 
Instance details

Defined in Math.Combinat.Trees.Nary

Methods

numberOfLeaves :: Tree a -> Int Source #

HasNumberOfNodes (Tree a) Source # 
Instance details

Defined in Math.Combinat.Trees.Nary

Methods

numberOfNodes :: Tree a -> Int Source #

DrawASCII (Tree ()) Source # 
Instance details

Defined in Math.Combinat.Trees.Nary

Methods

ascii :: Tree () -> ASCII Source #

Generic1 Tree

Since: containers-0.5.8

Instance details

Defined in Data.Tree

Associated Types

type Rep1 Tree :: k -> Type #

Methods

from1 :: forall (a :: k). Tree a -> Rep1 Tree a #

to1 :: forall (a :: k). Rep1 Tree a -> Tree a #

type Rep (Tree a) 
Instance details

Defined in Data.Tree

type Rep (Tree a) = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.2.1" '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 
Instance details

Defined in Data.Tree

type Rep1 Tree = D1 ('MetaData "Tree" "Data.Tree" "containers-0.6.2.1" 'False) (C1 ('MetaCons "Node" 'PrefixI 'True) (S1 ('MetaSel ('Just "rootLabel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Just "subForest") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) ([] :.: Rec1 Tree)))

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.

Orphan instances

HasNumberOfLeaves (Tree a) Source # 
Instance details

Methods

numberOfLeaves :: Tree a -> Int Source #

HasNumberOfNodes (Tree a) Source # 
Instance details

Methods

numberOfNodes :: Tree a -> Int Source #

DrawASCII (Tree ()) Source # 
Instance details

Methods

ascii :: Tree () -> ASCII Source #