diagrams-core-0.5: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellSafe-Infered

Graphics.Rendering.Diagrams.UDTree

Contents

Description

Rose (n-way) trees with both upwards- and downwards-traveling monoidal annotations, used as the basis for representing diagrams.

Synopsis

UD-trees

data UDTree u d a Source

Abstractly, a UDTree is a rose (n-way) tree with data at the leaves and two types of monoidal annotations, one (called u) travelling "up" the tree and one (called d) traveling "down".

Specifically, every node (both leaf nodes and internal nodes) has two annotations, one of type d and one of type u, subject to the following constraints:

  • The d annotation at a leaf node is equal to the mconcat of all the d annotations along the path from the root to the leaf node.
  • The u annotation at an internal node is equal to v1 `mappend` (mconcat us) `mappend` v2 for some values v1 and v2 (possibly mempty), where us is the list (in left-right order) of the u annotations on the immediate child nodes of the given node. Intuitively, we are "caching" the mconcat of u annotations from the leaves up, except that at any point we may insert "extra" information.

In addition, d may have an action on u (see the Action type class, defined in Graphics.Rendering.Diagrams.Monoids), in which case applying a d annotation to a tree will transform all the u annotations by acting on them. The constraints on u annotations are maintained since the action is required to be a monoid homomorphism.

Constructors

Leaf u a 
Branch u [d] [UDTree u d a] 

Instances

Functor (UDTree u d) 
(Action d u, Monoid u, Monoid d) => Monoid (UDTree u d a)

UDTrees form a monoid where mappend corresponds to adjoining two trees under a common parent root. Note that this technically does not satisfy associativity, but it does with respect to flatten which is what we really care about. mconcat is specialized to put all the trees under a single parent.

(Action d u, Monoid u, Monoid d) => Semigroup (UDTree u d a) 
Newtype (QDiagram b v m) (UDTree (UpAnnots v m) (DownAnnots v) (Prim b v)) 

Constructing UD-trees

leaf :: u -> a -> UDTree u d aSource

Construct a leaf node from a u annotation and datum.

branchD :: (Action d u, Monoid u) => d -> [UDTree u d a] -> UDTree u d aSource

Construct a branch node with an explicit d annotation.

branch :: (Action d u, Monoid u, Monoid d) => [UDTree u d a] -> UDTree u d aSource

Construct a branch node with a default (identity) d annotation.

Modifying UD-trees

applyD :: Action d u => d -> UDTree u d a -> UDTree u d aSource

Add a d annotation to the root, combining it (on the left) with any pre-existing d annotation, and transforming all u annotations by the action of d.

applyUpre :: (Semigroup u, Action d u) => u -> UDTree u d a -> UDTree u d aSource

Add a u annotation to the root, combining it (on the left) with the existing u annotation.

applyUpost :: (Semigroup u, Action d u) => u -> UDTree u d a -> UDTree u d aSource

Add a u annotation to the root, combining it (on the right) with the existing u annotation.

mapU :: (u -> u') -> UDTree u d a -> UDTree u' d aSource

Map a function over all the u annotations. 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 (act d u) == act d (f u).

Accessors and destructors

getU :: Action d u => UDTree u d a -> uSource

Get the u annotation at the root.

getU' :: (Action d (u' ::: Nil), u :>: u') => UDTree u d a -> u'Source

Get a particular component from a the u annotation at the root. This method is provided for convenience, since its context only requires an action of d on u', rather than on u in its entirety.

foldUDSource

Arguments

:: (Monoid r, Semigroup d, Monoid d, Action d u) 
=> (u -> d -> a -> r)

Function for processing leaf nodes. Given the u annotation at this node, the mconcat of all d annotations above, and the leaf value.

-> (u -> d -> r -> r)

Function for processing internal nodes. Given the u and d annotations at this node and the mconcat of the recursive results.

-> UDTree u d a 
-> r 

A fold for UDTrees.

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

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