dual-tree-0.2.3.1: Rose trees with cached and accumulating monoidal annotations
Copyright(c) 2011-2012 Brent Yorgey
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Data.Tree.DUAL.Internal

Description

This module provides access to all of the internals of the DUAL-tree implementation. Depend on the internals at your own risk! For a safe public API (and complete documentation), see Data.Tree.DUAL.

The main things exported by this module which are not exported from Data.Tree.DUAL are two extra types used in the implementation of DUALTree, along with functions for manipulating them. A type of non-empty trees, DUALTreeNE, is defined, as well as the type DUALTreeU which represents a non-empty tree paired with a cached u annotation. DUALTreeNE and DUALTreeU are mutually recursive, so that recursive tree nodes are interleaved with cached u annotations. DUALTree is defined by just wrapping DUALTreeU in 'Maybe. This method has the advantage that the type system enforces the invariant that there is only one representation for the empty tree. It also allows us to get away with only Semigroup constraints in many places.

Synopsis

DUAL-trees

data DUALTreeNE d u a l Source #

Non-empty DUAL-trees.

Constructors

Leaf u l

Leaf with data value and u annotation

LeafU u

Leaf with only u annotation

Concat (NonEmpty (DUALTreeU d u a l))

n-way branch, containing a non-empty list of subtrees.

Act d (DUALTreeU d u a l)

d annotation

Annot a (DUALTreeU d u a l)

Internal data value

Instances

Instances details
Functor (DUALTreeNE d u a) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

fmap :: (a0 -> b) -> DUALTreeNE d u a a0 -> DUALTreeNE d u a b #

(<$) :: a0 -> DUALTreeNE d u a b -> DUALTreeNE d u a a0 #

(Eq u, Eq l, Eq d, Eq a) => Eq (DUALTreeNE d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

(==) :: DUALTreeNE d u a l -> DUALTreeNE d u a l -> Bool #

(/=) :: DUALTreeNE d u a l -> DUALTreeNE d u a l -> Bool #

(Show u, Show l, Show d, Show a) => Show (DUALTreeNE d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

showsPrec :: Int -> DUALTreeNE d u a l -> ShowS #

show :: DUALTreeNE d u a l -> String #

showList :: [DUALTreeNE d u a l] -> ShowS #

(Action d u, Semigroup u) => Semigroup (DUALTreeNE d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

(<>) :: DUALTreeNE d u a l -> DUALTreeNE d u a l -> DUALTreeNE d u a l #

sconcat :: NonEmpty (DUALTreeNE d u a l) -> DUALTreeNE d u a l #

stimes :: Integral b => b -> DUALTreeNE d u a l -> DUALTreeNE d u a l #

newtype DUALTreeU d u a l Source #

A non-empty DUAL-tree paired with a cached u value. These should never be constructed directly; instead, use pullU.

Constructors

DUALTreeU 

Fields

Instances

Instances details
Functor (DUALTreeU d u a) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

fmap :: (a0 -> b) -> DUALTreeU d u a a0 -> DUALTreeU d u a b #

(<$) :: a0 -> DUALTreeU d u a b -> DUALTreeU d u a a0 #

(Eq u, Eq l, Eq d, Eq a) => Eq (DUALTreeU d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

(==) :: DUALTreeU d u a l -> DUALTreeU d u a l -> Bool #

(/=) :: DUALTreeU d u a l -> DUALTreeU d u a l -> Bool #

(Show u, Show l, Show d, Show a) => Show (DUALTreeU d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

showsPrec :: Int -> DUALTreeU d u a l -> ShowS #

show :: DUALTreeU d u a l -> String #

showList :: [DUALTreeU d u a l] -> ShowS #

(Semigroup u, Action d u) => Semigroup (DUALTreeU d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

(<>) :: DUALTreeU d u a l -> DUALTreeU d u a l -> DUALTreeU d u a l #

sconcat :: NonEmpty (DUALTreeU d u a l) -> DUALTreeU d u a l #

stimes :: Integral b => b -> DUALTreeU d u a l -> DUALTreeU d u a l #

newtype 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.

Constructors

DUALTree 

Fields

Instances

Instances details
Functor (DUALTree d u a) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

fmap :: (a0 -> b) -> DUALTree d u a a0 -> DUALTree d u a b #

(<$) :: a0 -> DUALTree d u a b -> DUALTree d u a a0 #

(Eq u, Eq l, Eq d, Eq a) => Eq (DUALTree d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

(==) :: DUALTree d u a l -> DUALTree d u a l -> Bool #

(/=) :: DUALTree d u a l -> DUALTree d u a l -> Bool #

(Show u, Show l, Show d, Show a) => Show (DUALTree d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

showsPrec :: Int -> DUALTree d u a l -> ShowS #

show :: DUALTree d u a l -> String #

showList :: [DUALTree d u a l] -> ShowS #

(Semigroup u, Action d u) => Semigroup (DUALTree d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

(<>) :: DUALTree d u a l -> DUALTree d u a l -> DUALTree d u a l #

sconcat :: NonEmpty (DUALTree d u a l) -> DUALTree d u a l #

stimes :: Integral b => b -> DUALTree d u a l -> DUALTree d u a l #

(Semigroup u, Action d u) => Monoid (DUALTree d u a l) Source # 
Instance details

Defined in Data.Tree.DUAL.Internal

Methods

mempty :: DUALTree d u a l #

mappend :: DUALTree d u a l -> DUALTree d u a l -> DUALTree d u a l #

mconcat :: [DUALTree d u a l] -> DUALTree d u a l #

Constructing DUAL-trees

empty :: DUALTree d u a l Source #

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

leaf :: u -> l -> DUALTree d u a l Source #

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

leafU :: u -> DUALTree d u a l Source #

Construct a leaf node from a u annotation.

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

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 l Source #

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 l Source #

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 l Source #

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.

mapUNE :: (u -> u') -> DUALTreeNE d u a l -> DUALTreeNE d u' a l Source #

Map a function (which must be a monoid homomorphism, and commute with the action of d) over all the u annotations in a non-empty DUAL-tree.

mapUU :: (u -> u') -> DUALTreeU d u a l -> DUALTreeU d u' a l Source #

Map a function (which must be a monoid homomorphism, and commute with the action of d) over all the u annotations in a non-empty DUAL-tree paired with its cached u value.

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

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

nonEmpty :: DUALTree d u a l -> Maybe (u, DUALTreeNE d u a l) Source #

Decompose a DUAL-tree into either Nothing (if empty) or a top-level cached u annotation paired with a non-empty DUAL-tree.

getU :: DUALTree d u a l -> Maybe u Source #

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

foldDUALNE Source #

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 LeafU nodes

-> (NonEmpty r -> r)

Combine results at a branch node

-> (d -> r -> r)

Process an internal d node

-> (a -> r -> r)

Process an internal datum

-> DUALTreeNE d u a l 
-> r 

Fold for non-empty DUAL-trees.

foldDUAL Source #

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

-> (d -> r -> r)

Process an internal d 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, internal d values, 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. If you do need access to u values, you can duplicate the values you need in the internal data nodes.

Be careful not to mix up the d values at internal nodes with the d values at leaves. Each d value at a leaf satisfies the property that it is the mconcat of all internal d values along the path from the root to the leaf.

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.