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

AtCoder.Extra.Pdsu

Description

A potentialized disjoint set union on a group under a differential constraint system. Each vertex v is assigned a potential value p(v), where representatives (leader) of each group have a potential of mempty, and other vertices have potentials relative to their representative.

The group type is represented as a Monoid with a inverse operator, passed on new. This approach avoids defining a separate typeclass for groups.

Invariant

New monoids always come from the left: new <> old. The order is important for non-commutative monoid implementations.

Since: 1.1.0.0

Synopsis

Pdsu

data Pdsu s a Source #

A potentialized disjoint set union on a group under a differential constraint system. Each vertex v is assigned a potential value p(v),

Example

Expand

Create a Pdsu with four vertices with potential type Sum Int. Use negate as the inverse operator:

>>> import AtCoder.Extra.Pdsu qualified as Pdsu
>>> import Data.Semigroup (Sum (..))
>>> dsu <- Pdsu.new @_ @(Sum Int) 4 negate

The API is similar to Dsu, but with differential potential values:

>>> Pdsu.merge dsu 1 0 (Sum 1)  -- p(1) - p(0) := Sum 1
True
>>> Pdsu.merge_ dsu 2 0 (Sum 2) -- p(2) - p(0) := Sum 2
>>> Pdsu.leader dsu 0
0

Potential values can be retrieved with pot:

>>> Pdsu.pot dsu 0
Sum {getSum = 0}
>>> Pdsu.pot dsu 1
Sum {getSum = 1}
>>> Pdsu.pot dsu 2
Sum {getSum = 2}

Difference of potentials in the same group can be retrieved with diff:

>>> Pdsu.diff dsu 2 1
Just (Sum {getSum = 1})
>>> Pdsu.diff dsu 2 3
Nothing

Retrieve group information with groups

>>> Pdsu.groups dsu
[[2,1,0],[3]]

Since: 1.1.0.0

Constructors

new Source #

Arguments

:: forall m a. (PrimMonad m, Monoid a, Unbox a) 
=> Int

The number of vertices

-> (a -> a)

The inverse operator of the monoid

-> m (Pdsu (PrimState m) a)

A DSU

O(n) Creates a new DSU under a differential constraint system.

Since: 1.1.0.0

Inspection

leader :: (HasCallStack, PrimMonad m, Semigroup a, Unbox a) => Pdsu (PrimState m) a -> Int -> m Int Source #

O(α(n)) Returns the representative of the connected component that contains the vertex.

Since: 1.1.0.0

pot :: (HasCallStack, PrimMonad m, Semigroup a, Unbox a) => Pdsu (PrimState m) a -> Int -> m a Source #

O(α(n)) Returns p(v), the potential value of vertex v relative to the reprensetative of its group.

Since: 1.1.0.0

diff :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Pdsu (PrimState m) a -> Int -> Int -> m (Maybe a) Source #

O(α(n)) Returns the potential of v1 relative to v2: p(v1)p1(v2) if the two vertices belong to the same group. Returns Nothing when the two vertices are not connected.

Since: 1.1.0.0

unsafeDiff :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Pdsu (PrimState m) a -> Int -> Int -> m a Source #

O(α(n)) Returns the potential of v1 relative to v2: p(v1)p1(v2) if the two vertices belong to the same group. Returns meaningless value if the two vertices are not connected.

Since: 1.1.0.0

same :: (HasCallStack, PrimMonad m, Semigroup a, Unbox a) => Pdsu (PrimState m) a -> Int -> Int -> m Bool Source #

O(α(n)) Returns whether the vertices a and b are in the same connected component.

Since: 1.1.0.0

canMerge :: (HasCallStack, PrimMonad m, Semigroup a, Eq a, Unbox a) => Pdsu (PrimState m) a -> Int -> Int -> a -> m Bool Source #

O(α(n)) Returns True if the two vertices belong to different groups or they belong to the same group under the condition p(v1)=dpp(v2). It's just a convenient helper function.

Since: 1.1.0.0

Merging

merge :: (HasCallStack, PrimMonad m, Monoid a, Ord a, Unbox a) => Pdsu (PrimState m) a -> Int -> Int -> a -> m Bool Source #

O(α(n)) Merges v1 to v2 with differential (relative) potential dp: p(v1):=dpp(v2). Returns True if they're newly merged.

Since: 1.1.0.0

merge_ :: (HasCallStack, PrimMonad m, Monoid a, Ord a, Unbox a) => Pdsu (PrimState m) a -> Int -> Int -> a -> m () Source #

O(α(n)) merge with the return value discarded.

Since: 1.1.0.0

Group information

size :: (HasCallStack, PrimMonad m, Semigroup a, Unbox a) => Pdsu (PrimState m) a -> Int -> m Int Source #

O(α(n)) Returns the number of vertices belonging to the same group.

Since: 1.1.0.0

groups :: (PrimMonad m, Semigroup a, Unbox a) => Pdsu (PrimState m) a -> m (Vector (Vector Int)) Source #

O(n) Divides the graph into connected components and returns the list of them.

Since: 1.1.0.0

Reset

clear :: forall m a. (PrimMonad m, Monoid a, Unbox a) => Pdsu (PrimState m) a -> m () Source #

O(n) Clears the Pdsu to the initial state.

Since: 1.1.0.0