| Copyright | (C) 2015 Edward Kmett |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Edward Kmett <ekmett@gmail.com> |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Struct.Internal.LinkCut
Description
- newtype LinkCut a s = LinkCut (Object s)
- path :: Slot (LinkCut a) (LinkCut a)
- parent :: Slot (LinkCut a) (LinkCut a)
- left :: Slot (LinkCut a) (LinkCut a)
- right :: Slot (LinkCut a) (LinkCut a)
- value :: Field (LinkCut a) a
- summary :: Field (LinkCut a) a
- new :: (PrimMonad m, Monoid a) => a -> m (LinkCut a (PrimState m))
- cut :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> m ()
- link :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> LinkCut a (PrimState m) -> m ()
- connected :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> LinkCut a (PrimState m) -> m Bool
- cost :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> m a
- root :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> m (LinkCut a (PrimState m))
- up :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> m (LinkCut a (PrimState m))
- summarize :: Monoid a => LinkCut a s -> ST s a
- access :: Monoid a => LinkCut a s -> ST s ()
- splay :: Monoid a => LinkCut a s -> ST s ()
Documentation
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 == yFalse>>>connected x yTrue>>>z <- new "z">>>link z x -- now z is a child of y>>>(y ==) <$> root zTrue>>>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 vTrue>>>connected x vTrue>>>cut z
y
x z y
z ==> w v x
w v u
u
>>>connected x vFalse>>>cost u"zwu">>>(z ==) <$> root vTrue
new :: (PrimMonad m, Monoid a) => 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). removes the linkage between cut vv 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
connected :: (PrimMonad m, Monoid a) => LinkCut a (PrimState m) -> LinkCut a (PrimState m) -> m Bool Source
O(log n). determines if connected v wv and w inhabit the same tree.
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).