ForestStructures-0.0.0.2: Tree- and forest structures

Safe HaskellNone
LanguageHaskell2010

Data.Forest.Static

Contents

Description

A data structure for a static forest.

Synopsis

Documentation

data TreeOrder Source #

Kind of possible TreeOrders.

TODO In for in-order traversal?

TODO Unordered for trees that have no sorted order?

Constructors

Pre 
Post 
Unordered 

data Forest p v a where Source #

A static forest structure. While traversals are always explicitly possible by following the indices, the nodes themselves shall always be ordered by the type p :: TreeOrder. This is not completely enforced, given that Forest is exporting the constructor, but encouraged via construction with helper functions. The labels of type a (in label) require a vector structure v for O(1) access.

Constructors

Forest :: Vector v a => {..} -> Forest p v a 

Fields

  • label :: v a

    Each node k in [0..n-1] has a label at label ! k.

  • parent :: Vector Int

    Each node k has a parent node, or -1 if there is no such parent.

  • children :: Vector (Vector Int)

    Each node k has a vector of indices for its children. For leaf nodes, the vector is empty.

  • lsib :: Vector Int

    The left sibling for a node k. Will *not* cross subtrees. I.e. if k is lsib of l, then k and l have the same parent.

  • rsib :: Vector Int

    The right sibling for a node k.

  • roots :: Vector Int

    The roots of the individual trees, the forest was constructed from.

Instances

(Show a, Show (v a)) => Show (Forest p v a) Source # 

Methods

showsPrec :: Int -> Forest p v a -> ShowS #

show :: Forest p v a -> String #

showList :: [Forest p v a] -> ShowS #

forestWith :: Vector v a => (forall a. [Tree a] -> [a]) -> [Tree a] -> Forest (p :: TreeOrder) v a Source #

Construct a static Forest with a tree traversal function. I.e. forestWith preorderF trees will construct a pre-order forest from the list of trees.

Siblings span trees in the forest!

forestPre :: Vector v a => [Tree a] -> Forest Pre v a Source #

Construct a pre-ordered forest.

forestPost :: Vector v a => [Tree a] -> Forest Post v a Source #

Construct a post-ordered forest.

addIndices :: Int -> Tree a -> Tree (Int, a) Source #

Add pre-ordered (!) indices. First argument is the starting index.

addIndicesF :: Int -> [Tree a] -> [Tree (Int, a)] Source #

Add pre-ordered (!) indices, but to a forest.

addIndicesF' :: Int -> [Tree a] -> [Tree Int] Source #

Add pre-ordered (!) indices to a forest, but throw the label away as well.

parentChildrenF :: Int -> [Tree (Int, a)] -> [Tree (Int, Int, [Int], a)] Source #

Add parent + children information. Yields (Index,Parent,[Child],Label). Parent is -1 if root node.

lrSiblingF :: [Tree (Int, a)] -> Map Int (Int, Int) Source #

Return a map with all the nearest siblings for each node, for a forest.

lrSibling :: Tree (Int, a) -> Map Int (Int, Int) Source #

Return a map with all the nearest siblings for each node, for a tree.

leftMostLeaves :: Forest p v a -> Vector Int Source #

Return the left-most leaf for each node.

leftMostLeaf :: Forest p v a -> Int -> Int Source #

Just the leaf-most leaf for a certain node.

rightMostLeaves :: Forest p v a -> Vector Int Source #

Return the right-most leaf for each node.

rightMostLeaf :: Forest p v a -> Int -> Int Source #

Given a tree, and a node index, return the right-most leaf for the node.

leftKeyRoots :: Forest Post v a -> Vector Int Source #

Return all left key roots. These are the nodes that have no (super-) parent with the same left-most leaf.

This function is somewhat specialized for tree editing.

TODO group by

sortedSubForests :: Forest p v a -> [Vector Int] Source #

Returns the list of all sorted subsets of subforests in the forest. If the forest is given in pre-order, then The subsets are returned in reversed pre-order.

TODO turn this into newtype vectors that enforce size >= 1.

newtype Srt Source #

Constructors

Srt 

Fields

Instances

Eq Srt Source # 

Methods

(==) :: Srt -> Srt -> Bool #

(/=) :: Srt -> Srt -> Bool #

Ord Srt Source # 

Methods

compare :: Srt -> Srt -> Ordering #

(<) :: Srt -> Srt -> Bool #

(<=) :: Srt -> Srt -> Bool #

(>) :: Srt -> Srt -> Bool #

(>=) :: Srt -> Srt -> Bool #

max :: Srt -> Srt -> Srt #

min :: Srt -> Srt -> Srt #

Show Srt Source # 

Methods

showsPrec :: Int -> Srt -> ShowS #

show :: Srt -> String #

showList :: [Srt] -> ShowS #

forestToTrees :: Forest p v a -> Forest a Source #

Given a forest, return the list of trees that constitue the forest.

QuickCheck

newtype QCTree a Source #

Wrapped quickcheck instance for Tree.

Constructors

QCTree 

Fields

Instances

Show a => Show (QCTree a) Source # 

Methods

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

show :: QCTree a -> String #

showList :: [QCTree a] -> ShowS #

Arbitrary a => Arbitrary (QCTree a) Source # 

Methods

arbitrary :: Gen (QCTree a) #

shrink :: QCTree a -> [QCTree a] #

Test functions

runtest :: [Tree Char] -> IO () Source #