hgeometry-combinatorial-0.12.0.3: Data structures, and Data types.
Safe HaskellNone
LanguageHaskell2010

Data.Tree.Util

Description

Tree-related utilities.

Synopsis

Documentation

>>> :{
let myTree = Node 0 [ Node 1 []
                    , Node 2 []
                    , Node 3 [ Node 4 [] ]
                    ]
:}

data TreeNode v a Source #

Nodes in a tree are typically either an internal node or a leaf node

Constructors

InternalNode v 
LeafNode a 

Instances

Instances details
Bifunctor TreeNode Source # 
Instance details

Defined in Data.Tree.Util

Methods

bimap :: (a -> b) -> (c -> d) -> TreeNode a c -> TreeNode b d #

first :: (a -> b) -> TreeNode a c -> TreeNode b c #

second :: (b -> c) -> TreeNode a b -> TreeNode a c #

Bitraversable TreeNode Source # 
Instance details

Defined in Data.Tree.Util

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> TreeNode a b -> f (TreeNode c d) #

Bifoldable TreeNode Source # 
Instance details

Defined in Data.Tree.Util

Methods

bifold :: Monoid m => TreeNode m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> TreeNode a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> TreeNode a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> TreeNode a b -> c #

(Eq v, Eq a) => Eq (TreeNode v a) Source # 
Instance details

Defined in Data.Tree.Util

Methods

(==) :: TreeNode v a -> TreeNode v a -> Bool #

(/=) :: TreeNode v a -> TreeNode v a -> Bool #

(Show v, Show a) => Show (TreeNode v a) Source # 
Instance details

Defined in Data.Tree.Util

Methods

showsPrec :: Int -> TreeNode v a -> ShowS #

show :: TreeNode v a -> String #

showList :: [TreeNode v a] -> ShowS #

_TreeNodeEither :: Iso' (TreeNode v p) (Either v p) Source #

A TreeNode is isomorphic to Either

Zipper on rose trees

data Zipper a Source #

Zipper for rose trees

Constructors

Zipper 

Fields

Instances

Instances details
Eq a => Eq (Zipper a) Source # 
Instance details

Defined in Data.Tree.Util

Methods

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

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

Show a => Show (Zipper a) Source # 
Instance details

Defined in Data.Tree.Util

Methods

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

show :: Zipper a -> String #

showList :: [Zipper a] -> ShowS #

root :: Tree a -> Zipper a Source #

Create a new zipper focussiong on the root.

up :: Zipper a -> Maybe (Zipper a) Source #

Move the focus to the parent of this node.

firstChild :: Zipper a -> Maybe (Zipper a) Source #

Move the focus to the first child of this node.

>>> firstChild $ root myTree
Just (Zipper {focus = Node {rootLabel = 1, subForest = []}, ancestors = [([],0,[Node {rootLabel = 2, subForest = []},Node {rootLabel = 3, subForest = [Node {rootLabel = 4, subForest = []}]}])]})

nextSibling :: Zipper a -> Maybe (Zipper a) Source #

Move the focus to the next sibling of this node

>>> (firstChild $ root myTree) >>= nextSibling
Just (Zipper {focus = Node {rootLabel = 2, subForest = []}, ancestors = [([Node {rootLabel = 1, subForest = []}],0,[Node {rootLabel = 3, subForest = [Node {rootLabel = 4, subForest = []}]}])]})

prevSibling :: Zipper a -> Maybe (Zipper a) Source #

Move the focus to the next sibling of this node

allChildren :: Zipper a -> [Zipper a] Source #

Given a zipper that focussses on some subtree t, construct a list with zippers that focus on each child.

allTrees :: Zipper a -> [Zipper a] Source #

Given a zipper that focussses on some subtree t, construct a list with zippers that focus on each of the nodes in the subtree of t.

unZipperLocal :: Zipper a -> Tree a Source #

Creates a new tree from the zipper that thas the current node as root. The ancestorTree (if there is any) forms the first child in this new root.

constructTree :: [([Tree a], a, [Tree a])] -> Maybe (Tree a) Source #

Constructs a tree from the list of ancestors (if there are any)

findEvert :: (a -> Bool) -> Tree a -> Maybe (Tree a) Source #

Given a predicate on an element, find a node that matches the predicate, and turn that node into the root of the tree.

running time: \(O(nT)\) where \(n\) is the size of the tree, and \(T\) is the time to evaluate a predicate.

>>> findEvert (== 4) myTree
Just (Node {rootLabel = 4, subForest = [Node {rootLabel = 3, subForest = [Node {rootLabel = 0, subForest = [Node {rootLabel = 1, subForest = []},Node {rootLabel = 2, subForest = []}]}]}]})
>>> findEvert (== 5) myTree
Nothing

findEvert' :: (Tree a -> Bool) -> Tree a -> Maybe (Tree a) Source #

Given a predicate matching on a subtree, find a node that matches the predicate, and turn that node into the root of the tree.

running time: \(O(nT(n))\) where \(n\) is the size of the tree, and \(T(m)\) is the time to evaluate a predicate on a subtree of size \(m\).

findPath Source #

Arguments

:: (a -> Bool)

is this node a starting node

-> (a -> Bool)

is this node an ending node

-> Tree a 
-> Maybe [a] 

Function to extract a path between a start node and an end node (if such a path exists). If there are multiple paths, no guarantees are given about which one is returned.

running time: \(O(n(T_p+T_s)\), where \(n\) is the size of the tree, and \(T_p\) and \(T_s\) are the times it takes to evaluate the isStartingNode and isEndingNode predicates.

>>> findPath (== 1) (==4) myTree
Just [1,0,3,4]
>>> findPath (== 1) (==2) myTree
Just [1,0,2]
>>> findPath (== 1) (==1) myTree
Just [1]
>>> findPath (== 1) (==2) myTree
Just [1,0,2]
>>> findPath (== 4) (==2) myTree
Just [4,3,0,2]

findNode :: (a -> Bool) -> Tree a -> Maybe [a] Source #

Given a predicate on a, find (the path to) a node that satisfies the predicate.

>>> findNode (== 4) myTree
Just [0,3,4]

findNodes :: (Tree a -> Bool) -> Tree a -> [[a]] Source #

Find all paths to nodes that satisfy the predicate

running time: \(O(nT(n))\) where \(n\) is the size of the tree, and \(T(m)\) is the time to evaluate a predicate on a subtree of size \(m\).

>>> findNodes ((< 4) . rootLabel) myTree
[[0],[0,1],[0,2],[0,3]]
>>> findNodes (even . rootLabel) myTree
[[0],[0,2],[0,3,4]]
>>> let size = length in findNodes ((> 1) . size) myTree
[[0],[0,3]]

levels :: Tree a -> NonEmpty (NonEmpty a) Source #

BFS Traversal of the rose tree that decomposes it into levels.

running time: \(O(n)\)