dual-tree-0.1.0.1: Rose trees with cached and accumulating monoidal annotations

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Data.Tree.DUAL

Contents

Description

Rose (n-ary) trees with both upwards- (i.e. cached) and downwards-traveling (i.e. accumulating) monoidal annotations. This is used as the core data structure underlying the diagrams framework (http://projects.haskell.org/diagrams), but potentially has other applications as well.

Abstractly, a DUALTree is a rose (n-ary) tree with data (of type l) at leaves, data (of type a) at internal nodes, and two types of monoidal annotations, one (of type u) travelling "up" the tree and one (of type d) traveling "down".

Specifically, there are five types of nodes:

  • Leaf nodes which contain a data value of type l and an annotation of type u. The annotation represents information about a tree that should be accumulated (e.g. number of leaves, some sort of "weight", etc.). If you are familiar with finger trees (http://www.soi.city.ac.uk/~ross/papers/FingerTree.html, http://hackage.haskell.org/package/fingertree), it is the same idea.
  • There is also a special type of leaf node which contains only a u value, and no data. This allows cached u values to be "modified" by inserting extra annotations.
  • Branch nodes, containing a list of subtrees.
  • Internal nodes with a value of type d. d may have an action on u (see the Action type class, defined in Data.Monoid.Action from the monoid-extras package). Semantically speaking, applying a d annotation to a tree transforms all the u annotations below it by acting on them. Operationally, however, since the action must be a monoid homomorphism, applying a d annotation can actually be done in constant time.
  • Internal nodes with data values of type a, possibly of a different type than those in the leaves. These are just "along for the ride" and are unaffected by u and d annotations.

There are two critical points to note about u and d annotations:

  • The combined u annotation for an entire tree is always cached at the root and available in constant (amortized) time.
  • The mconcat of all the d annotations along the path from the root to each leaf is available along with the leaf during a fold operation.

A fold over a DUALTree is given access to the internal and leaf data, and the accumulated d values at each leaf. It is also allowed to replace "u-only" leaves with a constant value. In particular, however, it is not given access to any of the u annotations, the idea being that those are used only for constructing trees. It is also not given access to d values as they occur in the tree, only as they accumulate at leaves. If you do need access to u or d values, you can duplicate the values you need in the internal data nodes.

Synopsis

DUAL-trees

data DUALTree d u a l Source

Rose (n-ary) trees with both upwards- (i.e. cached) and downwards-traveling (i.e. accumulating) monoidal annotations. Abstractly, a DUALTree is a rose (n-ary) tree with data (of type l) at leaves, data (of type a) at internal nodes, and two types of monoidal annotations, one (of type u) travelling "up" the tree and one (of type d) traveling "down". See the documentation at the top of this file for full details.

DUALTree comes with some instances:

  • Functor, for modifying leaf data. Note that fmap of course cannot alter any u annotations.
  • Semigroup. DUALTreeNEs form a semigroup where (<>) corresponds to adjoining two trees under a common parent root, with sconcat specialized to put all the trees under a single parent. Note that this does not satisfy associativity up to structural equality, but only up to observational equivalence under flatten. Technically using foldDUAL directly enables one to observe the difference, but it is understood that foldDUAL should be used only in ways such that reassociation of subtrees "does not matter".
  • Monoid. The identity is the empty tree.

Instances

Typeable4 DUALTree 
(Semigroup d, Semigroup u, Action d u) => Action (DAct d) (DUALTree d u a l)

Apply a d annotation at the root of a tree. Semantically, all u annotations are transformed by the action of d, although operationally act incurs only a constant amount of work.

Functor (DUALTree d u a) 
(Eq d, Eq u, Eq a, Eq l) => Eq (DUALTree d u a l) 
(Show d, Show u, Show a, Show l) => Show (DUALTree d u a l) 
(Semigroup u, Action d u) => Monoid (DUALTree d u a l) 
(Semigroup u, Action d u) => Semigroup (DUALTree d u a l) 
Newtype (DUALTree d u a l) (Option (DUALTreeU d u a l)) 

Constructing DUAL-trees

empty :: DUALTree d u a lSource

The empty DUAL-tree. This is a synonym for mempty, but with a more general type.

leaf :: u -> l -> DUALTree d u a lSource

Construct a leaf node from a u annotation along with a leaf datum.

leafU :: u -> DUALTree d u a lSource

Construct a leaf node from a u annotation.

annot :: (Semigroup u, Action d u) => a -> DUALTree d u a l -> DUALTree d u a lSource

Add an internal data value at the root of a tree. Note that this only works on non-empty trees; on empty trees this function is the identity.

applyD :: (Semigroup d, Semigroup u, Action d u) => d -> DUALTree d u a l -> DUALTree d u a lSource

Apply a d annotation at the root of a tree, transforming all u annotations by the action of d.

Modifying DUAL-trees

applyUpre :: (Semigroup u, Action d u) => u -> DUALTree d u a l -> DUALTree d u a lSource

Add a u annotation to the root, combining it (on the left) with the existing cached u annotation. This function is provided just for convenience; applyUpre u t = leafU u <> t.

applyUpost :: (Semigroup u, Action d u) => u -> DUALTree d u a l -> DUALTree d u a lSource

Add a u annotation to the root, combining it (on the right) with the existing cached u annotation. This function is provided just for convenience; applyUpost u t = t <> leafU u.

mapU :: (u -> u') -> DUALTree d u a l -> DUALTree d u' a lSource

Map a function over all the u annotations in a DUAL-tree. The function must be a monoid homomorphism, and must commute with the action of d on u. That is, to use mapU f safely it must be the case that

  • f mempty == mempty
  • f (u1 <> u2) == f u1 <> f u2
  • f (act d u) == act d (f u)

Accessors and eliminators

getU :: DUALTree d u a l -> Maybe uSource

Get the u annotation at the root, or Nothing if the tree is empty.

foldDUALSource

Arguments

:: (Semigroup d, Monoid d) 
=> (d -> l -> r)

Process a leaf datum along with the accumulation of d values along the path from the root

-> r

Replace u-only nodes

-> (NonEmpty r -> r)

Combine results at a branch node

-> (a -> r -> r)

Process an internal datum

-> DUALTree d u a l 
-> Maybe r 

Fold for DUAL-trees. It is given access to the internal and leaf data, and the accumulated d values at each leaf. It is also allowed to replace "u-only" leaves with a constant value. In particular, however, it is not given access to any of the u annotations, the idea being that those are used only for constructing trees. It is also not given access to d values as they occur in the tree, only as they accumulate at leaves. If you do need access to u or d values, you can duplicate the values you need in the internal data nodes.

The result is Nothing if and only if the tree is empty.

flatten :: (Semigroup d, Monoid d) => DUALTree d u a l -> [(l, d)]Source

A specialized fold provided for convenience: flatten a tree into a list of leaves along with their d annotations, ignoring internal data values.