Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Heavy-light decomposition is a method for partitioning a tree into segments with consecutive
indices. It processes various path queries in \(O(\log n)\) time. For segment tree integration
and monoid products, refer to the TreeMonoid
module.
Overview of the internals
The following is for understanding the internals, not for using the API. Skip to the examples if you want.
Original tree
Consider a tree with arbitrary vertex order:
0--8--7--3--1--2--12--13--15--14 XX: original Vertex | | --: edge 10--5 11--8--6 |: edge | 4
indexHld
: Vertex -> VertexHld
The tree vertices are reindexed with indexHld
, where each segment is assigned consecutive
vertex indices:
0==1==2==3==4==5==6==7==8==9 XX: VertexHld | | ==: edges on the same semgent 14==13 10==11==12 |: edge between different segments | 15
Note that vertices on higher (closer to the root) segments are assigned smaller indices. This is
very internally very important when calculating lca
.
headHld
: Vertex -> Vertex
headHld
points the "head" vertex of each segment. It can be used for finding LCA of two
vertices. To find the LCA, move up to the head, go up to the parental segment's vertex and
repeat until the two vertices are on the same segment.
0==0==0==0==0==0==0==0==0==0 XX: original Vertex | | 5==5 11==11==11 | 4
headHld
also works for identifying segments. When two vertices are on the same segment, they
have the same head.
parentHld
: Vertex -> Vertex
parentHld
points the parental segment's vertex from a head:
(-1)==0==8==7==3==1==2==12==13==15 XX: original Vertex | | 5==8 1==11=8 | 5
Example
Create an Hld
for a tree:
>>>
import AtCoder.Extra.Graph qualified as Gr
>>>
import AtCoder.Extra.Tree.Hld qualified as Hld
>>>
import Data.Vector.Unboxed qualified as VU
>>>
-- 0--1--2--3
>>>
-- +
>>>
-- +--4--5
>>>
let n = 6
>>>
let tree = Gr.build' n . Gr.swapDupe' $ VU.fromList [(0, 1), (1, 2), (2, 3), (1, 4), (4, 5)]
>>>
let hld = Hld.new tree
Hld
can process various queries in \(O(\log n)\) time:
>>>
Hld.ancestor hld 5 3 -- go up three parents from `5`
0
>>>
Hld.jump hld 5 2 3 -- go to the third vertex from `5` to `2`:
Just 2
>>>
Hld.lengthBetween hld 5 3 -- get the length (the number of edges) between `5` and `3`:
4
>>>
Hld.path hld 5 3 -- get the path between `5` and `3`:
[5,4,1,2,3]
Our Hld
is rooted at 0
vertex and subtree queries are available:
>>>
Hld.isInSubtree hld 2 3 -- `3` is in the subtree of `2`
True
>>>
Hld.isInSubtree hld 2 4 -- `4` is not in the subtree of `2`
False
Segment queries
Products and segment queries are primarily used by the TreeMonoid
module and is not intended
for diretct use, but here's some examples. This time the reindex by the HLD is identity:
>>>
Hld.indexHld hld
[0,1,2,3,4,5]
So we can easily understand the outputs:
>>>
Hld.pathSegmentsInclusive Hld.WeightsAreOnVertices hld 5 3
[(5,4),(1,3)]
>>>
Hld.pathSegmentsInclusive Hld.WeightsAreOnEdges hld 5 3 -- LCA (1) is removed
[(5,4),(2,3)]
>>>
Hld.subtreeSegmentInclusive hld 1
(1,5)
Since: 1.1.0.0
Synopsis
- data Hld = Hld {}
- type Vertex = Int
- type VertexHld = Vertex
- new :: forall w. HasCallStack => Csr w -> Hld
- newAt :: forall w. HasCallStack => Csr w -> Vertex -> Hld
- lca :: HasCallStack => Hld -> Vertex -> Vertex -> Vertex
- ancestor :: HasCallStack => Hld -> Vertex -> Int -> Vertex
- jump :: HasCallStack => Hld -> Vertex -> Vertex -> Int -> Maybe Vertex
- lengthBetween :: HasCallStack => Hld -> Vertex -> Vertex -> Int
- path :: HasCallStack => Hld -> Vertex -> Vertex -> [Vertex]
- pathSegmentsInclusive :: HasCallStack => WeightPolicy -> Hld -> Vertex -> Vertex -> [(VertexHld, VertexHld)]
- subtreeSegmentInclusive :: HasCallStack => Hld -> Vertex -> (VertexHld, VertexHld)
- isInSubtree :: HasCallStack => Hld -> Vertex -> Vertex -> Bool
- data WeightPolicy
- prod :: (HasCallStack, Monoid mono, Monad m) => WeightPolicy -> Hld -> (VertexHld -> VertexHld -> m mono) -> (VertexHld -> VertexHld -> m mono) -> Vertex -> Vertex -> m mono
Hld
Hld
partitions a tree into segments and assignes contiguous VertexHld
for each segment.
Since: 1.1.0.0
Constructors
new :: forall w. HasCallStack => Csr w -> Hld Source #
\(O(n)\) Creates an Hld
with \(0\) as the root vertex.
Since: 1.1.0.0
newAt :: forall w. HasCallStack => Csr w -> Vertex -> Hld Source #
\(O(n)\) Creates an Hld
with a root vertex specified.
Since: 1.1.0.0
LCA
lca :: HasCallStack => Hld -> Vertex -> Vertex -> Vertex Source #
\(O(\log n)\) Calculates the lowest common ancestor of \(u\) and \(v\).
Since: 1.1.0.0
Jump
ancestor :: HasCallStack => Hld -> Vertex -> Int -> Vertex Source #
\(O(\log n)\) Go up \(k\) times from a vertex \(v\) to the root node. Throws an error if \(k\) is bigger than the depth of \(v\).
Since: 1.1.0.0
jump :: HasCallStack => Hld -> Vertex -> Vertex -> Int -> Maybe Vertex Source #
\(O(\log n)\) Returns the \(k\)-th vertex of the path between \(u\) and \(v\) from \(u\).
Throws an error if k
is out
Since: 1.1.0.0
Path
lengthBetween :: HasCallStack => Hld -> Vertex -> Vertex -> Int Source #
\(O(\log n)\) Returns the length of the path between \(u\) and \(v\).
Since: 1.1.0.0
path :: HasCallStack => Hld -> Vertex -> Vertex -> [Vertex] Source #
\(O(n)\) Returns the vertices on the path between \(u\) and \(v\).
Since: 1.1.0.0
pathSegmentsInclusive :: HasCallStack => WeightPolicy -> Hld -> Vertex -> Vertex -> [(VertexHld, VertexHld)] Source #
\(O(\log n)\) Decomposes a path between two vertices \(u\) and \(v\) into segments. Each
segment is represented as an inclusive range \([u_i, v_i]\) of VertexHLD
.
The LCA is omitted from the returning vertices when the weight policy is set to
WeightsAreOnEdges
. This is the trick to put edge weights to on vertices.
Since: 1.1.0.0
Subtree
subtreeSegmentInclusive :: HasCallStack => Hld -> Vertex -> (VertexHld, VertexHld) Source #
\(O(1)\) Returns a half-open interval of VertexHld
\([\mathrm{start}, \mathrm{end})\) that
corresponds to the subtree segments rooted at the given subtreeRoot
.
Since: 1.1.0.0
isInSubtree :: HasCallStack => Hld -> Vertex -> Vertex -> Bool Source #
\(O(1)\) Returns True
if \(u\) is in a subtree of \(r\).
Since: 1.1.0.0
Products
data WeightPolicy Source #
Represents whether weights are put on vertices or edges.
Since: 1.1.0.0
WeightsAreOnVertices | Weights are put on vertices. Since: 1.1.0.0 |
WeightsAreOnEdges | Weights are put on edges. Since: 1.1.0.0 |
Instances
Show WeightPolicy Source # | Since: 1.1.0.0 |
Defined in AtCoder.Extra.Tree.Hld showsPrec :: Int -> WeightPolicy -> ShowS # show :: WeightPolicy -> String # showList :: [WeightPolicy] -> ShowS # | |
Eq WeightPolicy Source # | Since: 1.1.0.0 |
Defined in AtCoder.Extra.Tree.Hld (==) :: WeightPolicy -> WeightPolicy -> Bool # (/=) :: WeightPolicy -> WeightPolicy -> Bool # |
:: (HasCallStack, Monoid mono, Monad m) | |
=> WeightPolicy | The |
-> Hld | The |
-> (VertexHld -> VertexHld -> m mono) | User function for getting products in \([u, v)\), where \(u < v\) and \(\mathrm{depth}(u) < \mathrm{depth}(v)\). |
-> (VertexHld -> VertexHld -> m mono) | User function for getting products in \([u, v)\), where \(u < v\) and \(\mathrm{depth}(u) > \mathrm{depth}(v)\). |
-> Vertex | \(u\). |
-> Vertex | \(v\). |
-> m mono | Product of the path between \(u\) and \(v\). |
\(O(\log n f)\) Returns product of the path between \(u\) and \(v\), using the user functions of time complexity \(O(f)\).
Since: 1.1.0.0