Processing math: 100%
ac-library-hs-1.5.1.0: Data structures and algorithms
Safe HaskellNone
LanguageGHC2021

AtCoder.Extra.Tree.Lct

Description

Link/cut tree: dynamic forest with monoid values on vertices. If you need to have monoid values on edges, treat the original edges as new vertices.

  • Most operations are unsafe; user must ensure connectivities of u and v before running each query.
  • This specific implementation is not capable of applying monoid action to a subtree.

Example

Expand

Create a link/cut tree of monoid 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)]
prodPath, prodSubtree, prodTree

Monoid products can be calculated for paths or subtrees:

>>> Lct.prodPath lct 0 2
Sum {getSum = 3}
>>> -- If we create the LCT with `buildInv`, we can use `prodSubtree`:
>>> 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
lca, jump, lengthBetween

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.jump lct {- path -} 2 3 {- k -} 2
3
>>> Lct.jumpMaybe lct {- path -} 2 3 {- k -} 1000
Nothing
>>> Lct.lengthBetween lct {- path -} 2 3
2
parent
>>> Lct.evert lct 0  -- set root `0`
>>> Lct.parent lct 0 -- under root `0`, parent of `0` is `Nothing`:
Nothing
>>> Lct.evert lct 0  -- set root `0`
>>> Lct.parent lct 1 -- under root `0`, parent of `1` is `0`:
Just 0
link / cut

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

    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 monoid products (right foldings). This is required for non-commutative monoids only.

    Since: 1.1.1.0

  • midLct :: !(MVector s a)

    Decomposed node data storage: path-parent monoid products. 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. This setup disables subtree queries (prodSubtree).

Since: 1.1.1.0

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

O(n) 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. This setup disables subtree queries (prodSubtree).

Constraints

  • 0u,v<n

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

Constraints

  • 0u,v<n

Since: 1.1.1.0

Monoid value access

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

O(1). Reads the monoid value on a vertex v.

Constraints

  • 0v<n

Since: 1.5.1.0

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

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

Constraints

  • 0v<n

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). Given a user function f, modifies the monoid value of a vertex v.

Constraints

  • 0v<n

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). Given a user function f, modifies the monoid value of a vertex v.

Constraints

  • 0v<n

Since: 1.1.1.0

Tree operations

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 p will be the parent of c.

Constraints

  • 0c,p<n
  • uv
  • c and p are in different trees, otherwise the behavior is undefined.

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.

Constraints

  • 0u,v<n
  • uv
  • There's an edge between u and v, otherwise the behavior is undefined.

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.

Constraints

  • 0v<n

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 operation, v will be the new root and all the children will be detached from the preferred path.

Constraints

  • 0v<n

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.

Constraints

  • 0v<n

Since: 1.1.1.0

Tree queries

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

O(logn) Returns the root of the underlying tree.

Constraints

  • 0v<n

Since: 1.1.1.0

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

O(logn) Returns whether the vertices u and v are in the same connected component (have the same root).

Constraints

  • 0u,v<n

Since: 1.5.1.0

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

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

Constraints

  • 0v<n

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 from u in the path.

Constraints

  • 0u,v<n
  • 0k<|path|
  • u and v must be in the same connected component, otherwise the vehavior is undefined.

Since: 1.1.1.0

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

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

Constraints

  • 0u,v<n
  • u and v must be in the same connected component, otherwise the vehavior is undefined.

Since: 1.5.1.0

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

O(logn) Returns the length of path between u and v.

Constraints

  • 0u,v<n
  • u and v must be in the same connected component.

Since: 1.5.1.0

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

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

Constraints

  • 0u,v<n
  • u and v must be in the same connected component.

Since: 1.1.1.0

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

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

Constraints

  • 0u,v<n

Since: 1.5.1.0

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

Constraints

  • 0u,v<n
  • u and v must be in the same connected component, otherwise the return value is nonsense.

Since: 1.1.1.0

prodSubtree Source #

Arguments

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

Link/cut tree

-> Vertex

Vertex v

-> Vertex

Parent p (not need be adjacent to v), or same as v, making it a new root.

-> 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 v, v will be the new root.

Constraints

  • The inverse operator must be set on construction (newInv or buildInv).
  • 0u,v<n

Since: 1.1.1.0

prodTree Source #

Arguments

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

Link/cut tree

-> Vertex

Vertex v

-> m a

Subtree's monoid product

Amortized O(logn). Fold a tree that contains v.

Constraints

  • The inverse operator must be set on construction (newInv or buildInv).
  • 0v<n

Since: 1.5.1.0