lca-0.4: O(log n) persistent online lowest common ancestor search without preprocessing
Copyright(C) 2012-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.LCA.Online.Monoidal

Description

Provides online calculation of the the lowest common ancestor in O(log h) by compressing the spine of the paths using a skew-binary random access list.

This library implements the technique described in my talk

http://www.slideshare.net/ekmett/skewbinary-online-lowest-common-ancestor-search

to improve the known asymptotic bounds on both online lowest common ancestor search

http://en.wikipedia.org/wiki/Lowest_common_ancestor

and the online level ancestor problem:

http://en.wikipedia.org/wiki/Level_ancestor_problem

Algorithms used here assume that the key values chosen for k are globally unique.

This version provides access to a monoidal "summary" of the elided path for many operations.

Synopsis

Documentation

data Path a Source #

A compressed Path as a skew binary random access list

Instances

Instances details
Foldable Path Source # 
Instance details

Defined in Data.LCA.Online.Monoidal

Methods

fold :: Monoid m => Path m -> m #

foldMap :: Monoid m => (a -> m) -> Path a -> m #

foldMap' :: Monoid m => (a -> m) -> Path a -> m #

foldr :: (a -> b -> b) -> b -> Path a -> b #

foldr' :: (a -> b -> b) -> b -> Path a -> b #

foldl :: (b -> a -> b) -> b -> Path a -> b #

foldl' :: (b -> a -> b) -> b -> Path a -> b #

foldr1 :: (a -> a -> a) -> Path a -> a #

foldl1 :: (a -> a -> a) -> Path a -> a #

toList :: Path a -> [a] #

null :: Path a -> Bool #

length :: Path a -> Int #

elem :: Eq a => a -> Path a -> Bool #

maximum :: Ord a => Path a -> a #

minimum :: Ord a => Path a -> a #

sum :: Num a => Path a -> a #

product :: Num a => Path a -> a #

Read a => Read (Path a) Source # 
Instance details

Defined in Data.LCA.Online.Monoidal

Show a => Show (Path a) Source # 
Instance details

Defined in Data.LCA.Online.Monoidal

Methods

showsPrec :: Int -> Path a -> ShowS #

show :: Path a -> String #

showList :: [Path a] -> ShowS #

toList :: Path a -> [(Int, a)] Source #

Convert a Path to a list of (ID, value) pairs.

fromList :: Monoid a => [(Int, a)] -> Path a Source #

Build a Path from a list of (ID, value) pairs.

map :: Monoid b => (a -> b) -> Path a -> Path b Source #

O(n) Re-annotate a Path full of monoidal values using a different Monoid.

mapHom :: (a -> b) -> Path a -> Path b Source #

O(n) Re-annotate a Path full of monoidal values/

Unlike map, mapHom f assumes that f is a Monoid homomorphism, that is to say you must ensure

f a `mappend` f b = f (a `mappend` b)
f mempty = mempty

mapWithKey :: Monoid b => (Int -> a -> b) -> Path a -> Path b Source #

O(n) Re-annotate a Path full of monoidal values with access to the key.

traverse :: (Applicative f, Monoid b) => (a -> f b) -> Path a -> f (Path b) Source #

Traverse a Path yielding a new monoidal annotation.

traverseWithKey :: (Applicative f, Monoid b) => (Int -> a -> f b) -> Path a -> f (Path b) Source #

Traverse a Path with access to the node IDs.

empty :: Path a Source #

The empty Path

cons :: Monoid a => Int -> a -> Path a -> Path a Source #

O(1) Invariant: most operations assume that the keys k are globally unique

Extend the Path with a new node ID and value.

uncons :: Monoid a => Path a -> Maybe (Int, a, Path a) Source #

O(1) Extract the node ID and value from the newest node on the Path.

view :: Monoid a => Path a -> View Path a Source #

O(1) Extract the node ID and value from the newest node on the Path, slightly faster than uncons.

null :: Path a -> Bool Source #

O(1) Returns True iff the path is empty.

length :: Path a -> Int Source #

O(1) Determine the length of a Path.

measure :: Monoid a => Path a -> a Source #

Extract a monoidal summary of a Path.

isAncestorOf :: Monoid b => Path a -> Path b -> Bool Source #

O(log h) xs `isAncestorOf` ys holds when xs is a prefix starting at the root of path ys.

keep :: Monoid a => Int -> Path a -> Path a Source #

O(log (h - k)) to keep k elements of Path of length h

This solves the online version of the "level ancestor problem" with no preprocessing in O(log h) time, improving known complexity bounds.

http://en.wikipedia.org/wiki/Level_ancestor_problem

mkeep :: (Monoid a, Monoid b) => (a -> b) -> Int -> Path a -> (b, Path a) Source #

O(log (h - k)) to keep k elements of Path of length h, and provide a monoidal summary of the dropped elements using a supplied monoid homomorphism.

drop :: Monoid a => Int -> Path a -> Path a Source #

O(log k) to drop k elements from a Path

mdrop :: (Monoid a, Monoid b) => (a -> b) -> Int -> Path a -> (b, Path a) Source #

O(log k) to drop k elements from a Path and provide a monoidal summary of the dropped elements using a suplied monoid homomorphism

(~=) :: Path a -> Path b -> Bool infix 4 Source #

O(1) Compare to see if two trees have the same root key

lca :: (Monoid a, Monoid b) => Path a -> Path b -> Path a Source #

O(log h) Compute the lowest common ancestor of two paths

>>> let fromList' = fromList . fmap (flip (,) ())
>>> length (lca (fromList' [1, 2, 3, 4, 5, 6]) (fromList' [7, 8, 3, 4, 5, 6]))
4

mlca :: (Monoid a, Monoid b, Monoid c, Monoid d) => (a -> c) -> (b -> d) -> Path a -> Path b -> (c, Path a, d, Path b) Source #

O(log h) Compute the lowest common ancestor of two paths along with a monoidal summary of their respective tails using the supplied monoid homomorphisms.