@@ -40,6 +40,7 @@ module AtCoder.Extra.DsuMonoid
4040
4141 -- * Leader
4242 leader ,
43+ isLeader ,
4344
4445 -- * Component information
4546 same ,
@@ -48,8 +49,13 @@ module AtCoder.Extra.DsuMonoid
4849
4950 -- * Monoid values
5051 read ,
52+ write ,
53+ modify ,
54+ modifyM ,
5155 unsafeRead ,
5256 unsafeWrite ,
57+ unsafeModify ,
58+ unsafeModifyM ,
5359 )
5460where
5561
@@ -201,6 +207,21 @@ same dsu = Dsu.same (dsuDm dsu)
201207leader :: (HasCallStack , PrimMonad m ) => DsuMonoid (PrimState m ) a -> Int -> m Int
202208leader dsu = Dsu. leader (dsuDm dsu)
203209
210+ -- | Returns whether the vertex \(a\) is the representative of the connected component.
211+ --
212+ -- ==== Constraints
213+ -- - \(0 \leq a \lt n\)
214+ --
215+ -- ==== Complexity
216+ -- - \(O(\alpha(n))\) amortized
217+ --
218+ -- @since 1.6.0.0
219+ {-# INLINE isLeader #-}
220+ isLeader :: (HasCallStack , PrimMonad m ) => DsuMonoid (PrimState m ) a -> Int -> m Bool
221+ isLeader dsu v = do
222+ l <- Dsu. leader (dsuDm dsu) v
223+ pure $ l == v
224+
204225-- | Returns the size of the connected component that contains the vertex \(a\).
205226--
206227-- ==== Constraints
@@ -224,26 +245,73 @@ size dsu = Dsu.size (dsuDm dsu)
224245groups :: (PrimMonad m ) => DsuMonoid (PrimState m ) a -> m (V. Vector (VU. Vector Int ))
225246groups dsu = Dsu. groups (dsuDm dsu)
226247
227- -- | \(O(1)\) Reads the group value of the \(k\)-th node.
248+ -- | \(O(1)\) Reads the group value of the \(k\)-th node. \(k\) is automatically resolved to the
249+ -- leader vertex.
228250--
229251-- @since 1.5.3.0
230252{-# INLINE read #-}
231253read :: (PrimMonad m , VU. Unbox a ) => DsuMonoid (PrimState m ) a -> Int -> m a
232254read DsuMonoid {.. } i = do
233255 VGM. read mDm =<< Dsu. leader dsuDm i
234256
235- -- | \(O(1)\) Reads the group value of the \(k\)-th node.
257+ -- | \(O(1)\) Writes to the group value of the \(k\)-th node. \(k\) is automatically resolved to the
258+ -- leader vertex.
259+ --
260+ -- @since 1.6.0.0
261+ {-# INLINE write #-}
262+ write :: (PrimMonad m , VU. Unbox a ) => DsuMonoid (PrimState m ) a -> Int -> a -> m ()
263+ write DsuMonoid {.. } i x = do
264+ i' <- Dsu. leader dsuDm i
265+ VGM. write mDm i' x
266+
267+ -- | \(O(1)\) Modifies the group value of the \(k\)-th node. \(k\) is automatically resolved to the
268+ -- leader vertex.
269+ --
270+ -- @since 1.6.0.0
271+ {-# INLINE modify #-}
272+ modify :: (PrimMonad m , VU. Unbox a ) => DsuMonoid (PrimState m ) a -> (a -> a ) -> Int -> m ()
273+ modify DsuMonoid {.. } f i = do
274+ i' <- Dsu. leader dsuDm i
275+ VGM. modify mDm f i'
276+
277+ -- | \(O(1)\) Modifies the group value of the \(k\)-th node. \(k\) is automatically resolved to the
278+ -- leader vertex.
279+ --
280+ -- @since 1.6.0.0
281+ {-# INLINE modifyM #-}
282+ modifyM :: (PrimMonad m , VU. Unbox a ) => DsuMonoid (PrimState m ) a -> (a -> m a ) -> Int -> m ()
283+ modifyM DsuMonoid {.. } f i = do
284+ i' <- Dsu. leader dsuDm i
285+ VGM. modifyM mDm f i'
286+
287+ -- | \(O(1)\) Reads the \(k\)-th node.
236288--
237289-- @since 1.5.3.0
238290{-# INLINE unsafeRead #-}
239291unsafeRead :: (PrimMonad m , VU. Unbox a ) => DsuMonoid (PrimState m ) a -> Int -> m a
240292unsafeRead DsuMonoid {.. } i = do
241293 VGM. read mDm i
242294
243- -- | \(O(1)\) Writes to the group value of the \(k\)-th node.
295+ -- | \(O(1)\) Writes to the \(k\)-th node.
244296--
245297-- @since 1.5.3.0
246298{-# INLINE unsafeWrite #-}
247299unsafeWrite :: (PrimMonad m , VU. Unbox a ) => DsuMonoid (PrimState m ) a -> Int -> a -> m ()
248300unsafeWrite DsuMonoid {.. } i x = do
249301 VGM. write mDm i x
302+
303+ -- | \(O(1)\) Modifies the value of the \(k\)-th node.
304+ --
305+ -- @since 1.6.0.0
306+ {-# INLINE unsafeModify #-}
307+ unsafeModify :: (PrimMonad m , VU. Unbox a ) => DsuMonoid (PrimState m ) a -> (a -> a ) -> Int -> m ()
308+ unsafeModify DsuMonoid {.. } f i = do
309+ VGM. modify mDm f i
310+
311+ -- | \(O(1)\) Modifies the value of the \(k\)-th node.
312+ --
313+ -- @since 1.6.0.0
314+ {-# INLINE unsafeModifyM #-}
315+ unsafeModifyM :: (PrimMonad m , VU. Unbox a ) => DsuMonoid (PrimState m ) a -> (a -> m a ) -> Int -> m ()
316+ unsafeModifyM DsuMonoid {.. } f i = do
317+ VGM. modifyM mDm f i
0 commit comments