| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Debug.Trace.Tree.Edged
Description
Edge-labelled rose trees
Intended to be double imported:
import Debug.Trace.Tree.Edged import qualified Debug.Trace.Tree.Edged as Edged
- data ETree k v = Node v (Assoc k (ETree k v))
- elems :: ETree k v -> [v]
- keys :: ETree k v -> [k]
- mapEdges :: (v -> v -> k -> k') -> ETree k v -> ETree k' v
- data Hide = HideNode Coords
- hideNodes :: forall k v. [Hide] -> ETree k (v, Metadata) -> ETree k (Maybe v, Metadata)
- type Depth = Int
- type Offset = Int
- data Coords = Coords {}
- data Metadata = Metadata {}
- annotate :: ETree k v -> ETree k (v, Metadata)
- pushEdges :: k -> ETree k v -> Tree (k, v)
- pullEdges :: Tree (k, v) -> (k, ETree k v)
- liftTree :: (Tree (k, v) -> Tree ((k, v), b)) -> k -> ETree k v -> ETree k (v, b)
- liftTree' :: (forall a. Tree a -> Tree (a, b)) -> ETree k v -> ETree k (v, b)
Documentation
Tree with nodes labelled with v and arrows labelled with k
Standard operations
mapEdges :: (v -> v -> k -> k') -> ETree k v -> ETree k' v Source
Change the edges of the tree, providing source and target
Hiding nodes
Specification of nodes to hide
Annotation
Offset of a node in the tree
This is the horizontal offset of a node across all nodes at that depth.
For example, the offsets of
A / \ B C / \ \ D E F
are given by
(A,0)
/ \
(B,0) (C,1)
/ \ \
(D,0) (E,1) (F,2)Similarly, the offsets of
A / \ B C / \ D E
are given by
(A,0)
/ \
(B,0) (C,1)
/ \
(D,0) (E,1)Note that in this second example, D gets number 0 because it's the first node at this level; it's therefore not the case that the nodes with number 0 necessarily make up the _spine_ of the tree.
Coordinates of a node in the tree
Constructors
| Coords | |
Metadata of a node in the tree
Interaction between ETree and Tree
pushEdges :: k -> ETree k v -> Tree (k, v) Source
Push each edge label to a subtree into the node of that subtree
Since there is no edge to the root of the tree, the "edge" to that root must be passed in as an argument.