structs-0.1.2: Strict GC'd imperative object-oriented programming with cheap pointers.

Copyright(C) 2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Struct.LinkCut

Description

 
Synopsis

Documentation

data LinkCut a s Source #

Amortized Link-Cut trees via splay trees based on Tarjan's little book.

These support O(log n) operations for a lot of stuff.

The parameter a is an arbitrary user-supplied monoid that will be summarized along the path to the root of the tree.

In this example the choice of Monoid is String, so we can get a textual description of the path to the root.

>>> x <- new "x"
>>> y <- new "y"
>>> link x y -- now x is a child of y
>>> x == y
False
>>> connected x y
True
>>> z <- new "z"
>>> link z x -- now z is a child of y
>>> (y ==) <$> root z
True
>>> cost z
"yxz"
>>> w <- new "w"
>>> u <- new "u"
>>> v <- new "v"
>>> link u w
>>> link v z
>>> link w z
>>> cost u
"yxzwu"
>>> (y ==) <$> root v
True
>>> connected x v
True
>>> cut z
     y
    x          z    y
   z    ==>   w v  x
  w v        u
 u
>>> connected x v
False
>>> cost u
"zwu"
>>> (z ==) <$> root v
True
Instances
Struct (LinkCut a) Source # 
Instance details

Defined in Data.Struct.Internal.LinkCut

Methods

struct :: Dict (Coercible (LinkCut a s) (Object s)) Source #

Eq (LinkCut a s) Source # 
Instance details

Defined in Data.Struct.Internal.LinkCut

Methods

(==) :: LinkCut a s -> LinkCut a s -> Bool #

(/=) :: LinkCut a s -> LinkCut a s -> Bool #

new :: PrimMonad m => a -> m (LinkCut a (PrimState m)) Source #

O(1). Allocate a new link-cut tree with a given monoidal summary.

link :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> LinkCut a (PrimState m) -> m () Source #

O(log n). link v w inserts v which must be the root of a tree in as a child of w. v and w must not be connected.

cut :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> m () Source #

O(log n). cut v removes the linkage between v upwards to whatever tree it was in, making v a root node.

Repeated calls on the same value without intermediate accesses are O(1).

root :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> m (LinkCut a (PrimState m)) Source #

O(log n). Find the root of a tree.

Repeated calls on the same value without intermediate accesses are O(1).

cost :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> m a Source #

O(log n). cost v computes the root-to-leaf path cost of v under whatever Monoid was built into the tree.

Repeated calls on the same value without intermediate accesses are O(1).

parent :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> m (LinkCut a (PrimState m)) Source #

O(log n). Find the parent of a node.

This will return Nil if the parent does not exist.

Repeated calls on the same value without intermediate accesses are O(1).

connected :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> LinkCut a (PrimState m) -> m Bool Source #

O(log n). connected v w determines if v and w inhabit the same tree.