Processing math: 100%
ac-library-hs-1.2.0.0: Data structures and algorithms
Safe HaskellSafe-Inferred
LanguageGHC2021

AtCoder.Extra.Tree.Lct

Description

Link/cut tree: forest with monoid values.

Example

Expand

Create a link/cut tree of Sum Int with inverse operator negate:

>>> import AtCoder.Extra.Tree.Lct qualified as Lct
>>> import Data.Semigroup (Sum (..))
>>> import Data.Vector.Unboxed qualified as VU
>>> -- 0--1--2
>>> --    +--3
>>> lct <- Lct.buildInv negate (VU.generate 4 Sum) $ VU.fromList [(0, 1), (1, 2), (1, 3)]

Monoid products can be calculated for paths or subtrees:

>>> Lct.prodPath lct 0 2
Sum {getSum = 3}
>>> Lct.prodSubtree lct 1 {- parent -} 2
Sum {getSum = 4}

root returns the current root vertex of the underlying tree, which is not easy to predict:

>>> Lct.root lct 3
2

Set (evert) the root of the underlying tree to 0 and get the lca of vertices 2 and 3:

>>> Lct.evert lct 0
>>> Lct.lca lct 2 3
1

Similar to Hld, Lct allows various tree queries:

>>> Lct.parent lct 3
Just 1
>>> Lct.jump lct 2 3 2
3

Edges can be dynamically added (link) or removed (cut):

>>> -- 0  1  2
>>> --    +--3
>>> Lct.cut lct 0 1
>>> Lct.cut lct 1 2
>>> VU.generateM 4 (Lct.root lct)
[0,1,2,1]
>>> -- +-----+
>>> -- 0  1  2
>>> --    +--3
>>> Lct.link lct 0 2
>>> VU.generateM 4 (Lct.root lct)
[2,1,2,1]

Since: 1.1.1.0

Synopsis

Documentation

data Lct s a Source #

Link/cut tree.

Since: 1.1.1.0

Constructors

Lct 

Fields

  • nLct :: !Int

    The number of vertices.

    Since: 1.1.1.0

  • lLct :: !(MVector s Vertex)

    Decomposed node data storage: left children.

    Since: 1.1.1.0

  • rLct :: !(MVector s Vertex)

    Decomposed node data storage: right children.

    Since: 1.1.1.0

  • pLct :: !(MVector s Vertex)

    Decomposed node data storage: parents.

    Since: 1.1.1.0

  • sLct :: !(MVector s Int)

    Decomposed node data storage: subtree sizes.

    Since: 1.1.1.0

  • revLct :: !(MVector s Bit)

    Decomposed node data storage: reverse flag.

    Since: 1.1.1.0

  • vLct :: !(MVector s a)

    Decomposed node data storage: monoid values.

    Since: 1.1.1.0

  • prodLct :: !(MVector s a)

    Decomposed node data storage: monoid products.

    Since: 1.1.1.0

  • dualProdLct :: !(MVector s a)

    Decomposed node data storage: dual monod product (right fold). This is required for non-commutative monoids only.

    Since: 1.1.1.0

  • midLct :: !(MVector s a)

    Decomposed node data storage: path-parent monoid product. This works for subtree product queries over commutative monoids only.

    Since: 1.1.1.0

  • subtreeProdLct :: !(MVector s a)

    Decomposed node data storage: monoid product of subtree. This works for subtree product queries over commutative monoids only.

    Since: 1.1.1.0

  • invOpLct :: !(a -> a)

    Inverse operator of the monoid. This works for subtree product queries over commutative monoids only.

    Since: 1.1.1.0

type Vertex = Int Source #

Alias of vertex type.

Constructors

new :: (PrimMonad m, Monoid a, Unbox a) => Int -> m (Lct (PrimState m) a) Source #

O(n) Creates a link/cut tree with n vertices and no edges.

Since: 1.1.1.0

newInv :: (PrimMonad m, Monoid a, Unbox a) => (a -> a) -> Int -> m (Lct (PrimState m) a) Source #

O(n+mlogn) Creates a link/cut tree with an inverse operator, initial monoid values and no edges. This setup enables subtree queries (prodSubtree).

Since: 1.1.1.0

build Source #

Arguments

:: (HasCallStack, PrimMonad m, Monoid a, Unbox a) 
=> Vector a

Vertex monoid values

-> Vector (Vertex, Vertex)

Edges

-> m (Lct (PrimState m) a)

Link/cut tree

O(n+mlogn) Creates a link/cut tree of initial monoid values and initial edges.

Since: 1.1.1.0

buildInv Source #

Arguments

:: (HasCallStack, PrimMonad m, Monoid a, Unbox a) 
=> (a -> a)

Inverse operator

-> Vector a

Vertex monoid values

-> Vector (Vertex, Vertex)

Edges

-> m (Lct (PrimState m) a)

Link/cut tree

O(n+mlogn) Creates a link/cut tree with an inverse operator, initial monoid values and initial edges. This setup enables subtree queries (prodSubtree).

Since: 1.1.1.0

Modifications

Write

write :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Vertex -> a -> m () Source #

Amortized O(logn). Writes the monoid value of a vertex.

Since: 1.1.1.0

modify :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> (a -> a) -> Vertex -> m () Source #

Amortized O(logn). Modifies the monoid value of a vertex with a pure function.

Since: 1.1.1.0

modifyM :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> (a -> m a) -> Vertex -> m () Source #

Amortized O(logn). Modifies the monoid value of a vertex with a monadic function.

Since: 1.1.1.0

Link/cut

link :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Vertex -> Vertex -> m () Source #

Amortized O(logn). Creates an edge between c and p. In the represented tree, the parent of c will be p after this operation.

Since: 1.1.1.0

cut :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Vertex -> Vertex -> m () Source #

Amortized O(logN). Deletes an edge between u and v.

Since: 1.1.1.0

Evert/expose

evert :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Vertex -> m () Source #

Amortized O(logn). Makes v a new root of the underlying tree.

Since: 1.1.1.0

expose :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Vertex -> m Vertex Source #

Amortized O(logn). Makes v and the root to be in the same preferred path (auxiliary tree). After the opeartion, v will be the new root and all the children will be detached from the preferred path.

Since: 1.1.1.0

expose_ :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Vertex -> m () Source #

Amortized O(logn). expose with the return value discarded.

Since: 1.1.1.0

Tree queries

Root, parent, jump, LCA

root :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Int -> m Vertex Source #

O(logn) Returns the root of the underlying tree. Two vertices in the same connected component have the same root vertex.

Since: 1.1.1.0

parent :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Int -> m (Maybe Vertex) Source #

O(logn) Returns the parent vertex in the underlying tree.

Since: 1.1.1.0

jump :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Vertex -> Vertex -> Int -> m Vertex Source #

O(logn) Given a path between u and v, returns the k-th vertex of the path.

Constraints

  • The k-th vertex must exist.

Since: 1.1.1.0

lca :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Int -> Int -> m Vertex Source #

O(logn) Returns the LCA of u and v. Because the root of the underlying changes in almost every operation, one might want to use evert beforehand.

Constraints

  • u and v must be in the same connected component.

Since: 1.1.1.0

Products

prodPath :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Lct (PrimState m) a -> Vertex -> Vertex -> m a Source #

Amortized O(logn). Folds a path between u and v (inclusive).

Since: 1.1.1.0

prodSubtree Source #

Arguments

:: (HasCallStack, PrimMonad m, Monoid a, Unbox a) 
=> Lct (PrimState m) a

Link/cut tree

-> Vertex

Vertex

-> Vertex

Root or parent

-> m a

Subtree's monoid product

Amortized O(logn). Fold the subtree under v, considering p as the root-side vertex. Or, if p equals to v, v will be the new root.

Constraints

  • The inverse operator has to be set on consturction (newInv or buildInv).

Since: 1.1.1.0