Maintainer | diagrams-discuss@googlegroups.com |
---|---|
Safe Haskell | None |
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 typeu
. 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 cachedu
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 onu
(see theAction
type class, defined in Data.Monoid.Action from themonoid-extras
package). Semantically speaking, applying ad
annotation to a tree transforms all theu
annotations below it by acting on them. Operationally, however, since the action must be a monoid homomorphism, applying ad
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 byu
andd
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 thed
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.
- data DUALTree d u a l
- empty :: DUALTree d u a l
- leaf :: u -> l -> DUALTree d u a l
- leafU :: u -> DUALTree d u a l
- annot :: (Semigroup u, Action d u) => a -> DUALTree d u a l -> DUALTree d u a l
- applyD :: (Semigroup d, Semigroup u, Action d u) => d -> DUALTree d u a l -> DUALTree d u a l
- applyUpre :: (Semigroup u, Action d u) => u -> DUALTree d u a l -> DUALTree d u a l
- applyUpost :: (Semigroup u, Action d u) => u -> DUALTree d u a l -> DUALTree d u a l
- mapU :: (u -> u') -> DUALTree d u a l -> DUALTree d u' a l
- getU :: DUALTree d u a l -> Maybe u
- foldDUAL :: (Semigroup d, Monoid d) => (d -> l -> r) -> r -> (NonEmpty r -> r) -> (a -> r -> r) -> DUALTree d u a l -> Maybe r
- flatten :: (Semigroup d, Monoid d) => DUALTree d u a l -> [(l, d)]
DUAL-trees
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 thatfmap
of course cannot alter anyu
annotations. -
Semigroup
.DUALTreeNE
s form a semigroup where(<>)
corresponds to adjoining two trees under a common parent root, withsconcat
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 underflatten
. Technically usingfoldDUAL
directly enables one to observe the difference, but it is understood thatfoldDUAL
should be used only in ways such that reassociation of subtrees "does not matter". -
Monoid
. The identity is the empty tree.
Typeable4 DUALTree | |
(Semigroup d, Semigroup u, Action d u) => Action (DAct d) (DUALTree d u a l) | Apply a |
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.
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.
:: (Semigroup d, Monoid d) | |
=> (d -> l -> r) | Process a leaf datum along with the
accumulation of |
-> r | Replace |
-> (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.