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

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

Data.Struct.Internal.LinkCut

Description

 
Synopsis

Documentation

>>> import Data.Struct.Internal.LinkCut

newtype 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

Constructors

LinkCut (Object s) 
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 #

allocLinkCut :: forall a. forall m. PrimMonad m => m (LinkCut a (PrimState m)) Source #

newLinkCut :: forall a. forall m. PrimMonad m => LinkCut a (PrimState m) -> LinkCut a (PrimState m) -> LinkCut a (PrimState m) -> LinkCut a (PrimState m) -> a -> a -> m (LinkCut a (PrimState m)) Source #

summary :: forall a. Field (LinkCut a) a Source #

value :: forall a. Field (LinkCut a) a Source #

right :: forall a. Slot (LinkCut a) (LinkCut a) Source #

left :: forall a. Slot (LinkCut a) (LinkCut a) Source #

parent :: forall a. Slot (LinkCut a) (LinkCut a) Source #

path :: forall a. Slot (LinkCut a) (LinkCut a) Source #

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

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

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

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.

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.

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

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

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

O(log n). Move upward one level.

This will return Nil if the parent is not available.

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

summarize :: Monoid a => LinkCut a s -> ST s a Source #

O(1)

access :: Monoid a => LinkCut a s -> ST s () Source #

O(log n)

splay :: Monoid a => LinkCut a s -> ST s () Source #

O(log n). Splay within an auxiliary tree