ac-library-hs-1.2.0.0: Data structures and algorithms
Safe HaskellSafe-Inferred
LanguageGHC2021

AtCoder.Extra.Seq

Description

Dynamic sequence of monoid values with monoid actions on them through the SegAct instance.

Example

Expand

Create a Seq storage of length \(10\):

>>> import AtCoder.Extra.Monoid.RangeAdd qualified as RangeAdd
>>> import AtCoder.Extra.Seq qualified as Seq
>>> import AtCoder.LazySegTree (SegAct (..))
>>> import Data.Semigroup (Sum (..))
>>> import Data.Vector.Unboxed qualified as VU
>>> seq <- Seq.new @_ @(RangeAdd.RangeAdd (Sum Int)) @(Sum Int) 10

Allocate a sequence of \(0, 1, 2, 3\):

>>> handle <- Seq.newSeq seq (VU.fromList [0, 1, 2, 3])

Get monoid products:

>>> Seq.prodAll seq handle
Sum {getSum = 6}
>>> Seq.prod seq handle 1 3
Sum {getSum = 3}

read, write, modify and exchange are available:

>>> -- [0, 1, 2, 3] -> [0, 10, 2, 30]
>>> Seq.write seq handle 3 30
>>> Seq.modify seq handle (* 10) 1

Actions can be performed with SegAct instances:

>>> -- [0, 10, 2, 30] -> [0, 20, 12, 40]
>>> Seq.applyIn seq handle 1 4 (RangeAdd.new 10)
>>> Seq.prod seq handle 1 4
Sum {getSum = 72}

The sequence can be reversed if the action type is commutative:

>>> Seq.reverse seq handle 0 4
>>> VU.map getSum <$> Seq.freeze seq handle
[40,12,20,0]

The sequence is dynamic and new elements can be inserted or deleted:

>>> -- [40, 12, 20, 0] -> [40, 33, 12, 20, 0]
>>> Seq.insert seq handle 1 (Sum 33)
>>> -- [40, 33, 12, 20, 0] -> [40, 33, 12, 0]
>>> Seq.delete seq handle 3
Sum {getSum = 20}
>>> VU.map getSum <$> Seq.freeze seq handle
[40,33,12,0]

The Seq storage can store multiple sequences:

>>> handle2 <- Seq.newSeq seq (VU.generate 2 Sum)
>>> VU.map getSum <$> Seq.freeze seq handle2
[0,1]

Merge/split operations are available. merge functions mutate the given handle to be the merged sequence handle:

>>> Seq.merge seq handle handle2
>>> VU.map getSum <$> Seq.freeze seq handle
[40,33,12,0,0,1]

split functions mutate the given handle to be the leftmost one and returns right sequence handles:

>>> (handleM, handleR) <- Seq.split3 seq handle 2 4
>>> VU.map getSum <$> Seq.freeze seq handle
[40,33]
>>> VU.map getSum <$> Seq.freeze seq handleM
[12,0]
>>> VU.map getSum <$> Seq.freeze seq handleR
[0,1]

Bisection methods are available for monoid values and their products:

>>> Seq.reset seq
>>> handle <- Seq.newSeq seq $ VU.generate 10 Sum
>>> Seq.ilowerBound seq handle (\_ x -> x < 5)
5
>>> Seq.ilowerBoundProd seq handle (\_ x -> x < 5)
3

Since: 1.2.0.0

Synopsis

Seq

data Seq s f a Source #

Storages of dynamic sequences of monoid values with monoid actions on them through the SegAct instance.

Since: 1.2.0.0

Constructors

Seq 

Fields

  • nSeq :: !Int

    The maximum number of elements.

    Since: 1.2.0.0

  • poolSeq :: !(Pool s ())

    Pool for free slot management.

    Since: 1.2.0.0

  • lSeq :: !(MVector s Index)

    Decomposed node data storage: left children.

    Since: 1.2.0.0

  • rSeq :: !(MVector s Index)

    Decomposed node data storage: right children.

    Since: 1.2.0.0

  • pSeq :: !(MVector s Index)

    Decomposed node data storage: parents.

    Since: 1.2.0.0

  • sSeq :: !(MVector s Int)

    Decomposed node data storage: subtree sizes.

    Since: 1.2.0.0

  • vSeq :: !(MVector s a)

    Decomposed node data storage: monoid values.

    Since: 1.2.0.0

  • prodSeq :: !(MVector s a)

    Decomposed node data storage: monoid products.

    Since: 1.2.0.0

  • revSeq :: !(MVector s Bit)

    Decomposed node data storage: reversed flag of children.

    Since: 1.2.0.0

  • lazySeq :: !(MVector s f)

    Decomposed node data storage: lazily propagated monoid action. Use () if you don't need monoid actions.

    Since: 1.2.0.0

newtype Handle s Source #

Handle for a sequence in Seq. It internally stores the root node and updates it following splaying operations, as Seq utilizes a splay tree structure.

Since: 1.2.0.0

Constructors

Handle 

Fields

newHandle :: PrimMonad m => Index -> m (Handle (PrimState m)) Source #

\(O(1)\) Creates a new sequence Handle from a root node index.

Since: 1.2.0.0

nullHandle :: PrimMonad m => Handle (PrimState m) -> m Bool Source #

\(O(1)\) Returns whether the sequence is empty.

Since: 1.2.0.0

invalidateHandle :: PrimMonad m => Handle (PrimState m) -> m () Source #

\(O(1)\) Invalidates a sequence handle. Note that it does not change or free the sequence.

Since: 1.2.0.0

Constructors

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

\(O(n)\) Creates a new Seq of length \(n\).

Since: 1.2.0.0

reset :: PrimMonad m => Seq (PrimState m) f a -> m () Source #

\(O(1)\) Clears the sequence storage. All the handles must not be used again.

Since: 1.2.0.0

free :: (PrimMonad m, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> m () Source #

\(O(n)\) Frees a sequence and invalidates the handle.

Since: 1.2.0.0

newNode :: (PrimMonad m, Monoid f, Unbox f, Unbox a) => Seq (PrimState m) f a -> a -> m (Handle (PrimState m)) Source #

\(O(1)\) Allocates a new sequence of length \(1\).

Since: 1.2.0.0

newSeq :: (PrimMonad m, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Vector a -> m (Handle (PrimState m)) Source #

\(O(n)\) Allocates a new sequence.

Since: 1.2.0.0

Merge/split

merge :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Handle (PrimState m) -> m () Source #

Amortized \(O(\log n)\). Merges two sequences \(l, r\) into one in the given order, ignoring empty sequences. The right sequence handle will be invalidated.

Since: 1.2.0.0

merge3 :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Handle (PrimState m) -> Handle (PrimState m) -> m () Source #

Amortized \(O(\log n)\). Merges three sequences \(l, m, r\) into one in the given order, ignoring empty sequences. All handles, except for the leftmost one, will be invalidated.

Since: 1.2.0.0

merge4 :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Handle (PrimState m) -> Handle (PrimState m) -> Handle (PrimState m) -> m () Source #

Amortized \(O(\log n)\). Merges four sequences \(a, b, c, d\) into one in the given order, ignoring empty sequences. All handles, except for the leftmost one, will be invalidated.

Constraints

  • The vertices must be roots.

Since: 1.2.0.0

split :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> m (Handle (PrimState m)) Source #

Amortized \(O(\log n)\). Splits a sequences into two: \([0, k), [k, n)\). The handle will point to the left sequence. Returns the right sequence handle.

Constraints

  • \(0 \le k \le n\).

Since: 1.2.0.0

split3 :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> Int -> m (Handle (PrimState m), Handle (PrimState m)) Source #

Amortized \(O(\log n)\). Splits a sequences into three: \([0, l), [l, r), [r, n)\). The handle will point to the leftmost sequence. Returns the middle and the right sequence handles.

Constraints

  • \(0 \le l \le r \le n\).

Since: 1.2.0.0

split4 :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> Int -> Int -> m (Handle (PrimState m), Handle (PrimState m), Handle (PrimState m)) Source #

Amortized \(O(\log n)\). Splits a sequences into four: \([0, i), [i, j), [j, k), [k, n)\). The handle will point to the leftmost sequence. Returns the non-leftmost sequence handles.

Constraints

  • \(0 \le i \le j \le k \le n\).

Since: 1.2.0.0

splitLr :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> m (Handle (PrimState m), Handle (PrimState m)) Source #

Amortized \(O(\log n)\). Splits a sequence into three: \([0, \mathrm{root}), \mathrm{root}, [\mathrm{root} + 1, n)\).

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

Read/write

read :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> m a Source #

Amortized \(O(\log n)\). Reads the \(k\)-th node's monoid value.

Constraints

  • \(0 \le k \lt n\)

Since: 1.2.0.0

readMaybe :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> m (Maybe a) Source #

Amortized \(O(\log n)\). Reads the \(k\)-th node's monoid value.

Since: 1.2.0.0

write :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> a -> m () Source #

Amortized \(O(\log n)\). Writes to the \(k\)-th node's monoid value.

Constraints

  • \(0 \le k \lt n\)

Since: 1.2.0.0

modify :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> (a -> a) -> Int -> m () Source #

Amortized \(O(\log n)\). Modifies the \(k\)-th node's monoid value.

Constraints

  • \(0 \le k \lt n\)

Since: 1.2.0.0

exchange :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> a -> m a Source #

Amortized \(O(\log n)\). Exchanges the \(k\)-th node's monoid value.

Constraints

  • \(0 \le k \lt n\)

Since: 1.2.0.0

Products

prod :: (HasCallStack, Show a, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> Int -> m a Source #

Amortized \(O(\log n)\). Returns the monoid product in an interval \([l, r)\).

Constraints

  • \(0 \le l \le r \le n\)

Since: 1.2.0.0

prodMaybe :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> Int -> m (Maybe a) Source #

Amortized \(O(\log n)\). Returns the monoid product in an interval \([l, r)\). Returns Nothing if an invalid interval is given.

Since: 1.2.0.0

prodAll :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> m a Source #

Amortized \(O(\log n)\). Returns the monoid product of the whole sequence.

Since: 1.2.0.0

Applications

applyIn :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> Int -> f -> m () Source #

Amortized \(O(\log n)\). Given an interval \([l, r)\), applies a monoid action \(f\).

Constraints

  • \(0 \le l \le r \le n\)

Since: 1.2.0.0

applyToRoot :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> f -> m () Source #

\(O(1)\) Applies a monoid action \(f\) to the root of a sequence.

Since: 1.2.0.0

reverse :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> Int -> m () Source #

Amortized \(O(\log n)\). Reverses the sequence in \([l, r)\).

Constraints

  • The monoid action \(f\) must be commutative.
  • The monoid value \(v\) must be commutative.

Since: 1.2.0.0

Insert/delete

insert :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> a -> m () Source #

Amortized \(O(\log n)\). Inserts a new node at \(k\) with initial monoid value \(v\). This function works for an empty sequence handle.

Constraints

  • \(0 \le k \le n\)

Since: 1.2.0.0

delete :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> m a Source #

Amortized \(O(\log n)\). Frees the \(k\)-th node and returns the monoid value of it.

Constraints

  • \(0 \le k \lt n\)

Since: 1.2.0.0

delete_ :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> m () Source #

Amortized \(O(\log n)\). Frees the \(k\)-th node.

Constraints

  • \(0 \le k \lt n\)

Since: 1.2.0.0

detach :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> Int -> m (Handle (PrimState m)) Source #

Amortized \(O(\log n)\). Detaches the \(k\)-th node and returns a handle for it.

Constraints

  • \(0 \le k \lt n\)

Since: 1.2.0.0

Bisection methods

C++-like

ilowerBound Source #

Arguments

:: (PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq (PrimState m) f a

Sequence storage

-> Handle (PrimState m)

Sequence handle

-> (Int -> a -> Bool)

User predicate \(f(i, v_i)\) that takes the index and the monoid value

-> m Int

Maximum \(r\), where \(f(i, v_i)\) holds for \(i \in [0, r)\)

Amortized \(O(\log n)\).

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

ilowerBoundM Source #

Arguments

:: (PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq (PrimState m) f a

Sequence storage

-> Handle (PrimState m)

Sequence handle

-> (Int -> a -> m Bool)

User predicate \(f(i, v_i)\) that takes the index and the monoid value

-> m Int

Maximum \(r\), where \(f(i, v_i)\) holds for \(i \in [0, r)\)

Amortized \(O(\log n)\).

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

ilowerBoundProd Source #

Arguments

:: (PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq (PrimState m) f a

Sequence storage

-> Handle (PrimState m)

Sequence handle

-> (Int -> a -> Bool)

User predicate \(f(i, v_0 \dots v_i)\) that takes the index and the monoid product

-> m Int

Maximum \(r\), where \(f(i, v_0 \dots v_i)\) holds for \(i \in [0, r)\)

Amortized \(O(\log n)\).

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

ilowerBoundProdM Source #

Arguments

:: (PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq (PrimState m) f a

Sequence storage

-> Handle (PrimState m)

Sequence handle

-> (Int -> a -> m Bool)

User predicate \(f(i, v_0 \dots v_i)\) that takes the index and the monoid product

-> m Int

Maximum \(r\), where \(f(i, v_0 \dots v_i)\) holds for \(i \in [0, r)\)

Amortized \(O(\log n)\).

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

Splits

isplitMaxRight Source #

Arguments

:: (PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq (PrimState m) f a

Sequence storage

-> Handle (PrimState m)

Sequence handle

-> (Int -> a -> Bool)

User predicate \(f(i, v_i)\) that takes the index and the monoid value

-> m (Handle (PrimState m))

Handle of the right sequence \([r, n)\), where \(r\) is the maximum \(r\) such that \(f(i, v_i)\) holds for \(i \in [0, r)\)

Amortized \(O(\log n)\). Splits a sequence into two with the user predicate and returns the right sequence handle.

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

isplitMaxRightM Source #

Arguments

:: (PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq (PrimState m) f a

Sequence storage

-> Handle (PrimState m)

Sequence handle

-> (Int -> a -> m Bool)

User predicate \(f(i, v_i)\) that takes the index and the monoid value

-> m (Handle (PrimState m))

Handle of the right sequence \([r, n)\), where \(r\) is the maximum \(r\) such that \(f(i, v_i)\) holds for \(i \in [0, r)\)

Amortized \(O(\log n)\). Splits a sequence into two with the user predicate and returns the right sequence handle.

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

isplitMaxRightProd Source #

Arguments

:: (PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq (PrimState m) f a

Sequence storage

-> Handle (PrimState m)

Sequence handle

-> (Int -> a -> Bool)

User predicate \(f(i, v_0 \dots v_i)\) that takes the index and the monoid value

-> m (Handle (PrimState m))

Handle of the right sequence \([r, n)\), where \(r\) is the maximum \(r\) such that \(f(i, v_0 \dots v_i)\) holds for \(i \in [0, r)\)

Amortized \(O(\log n)\). Splits a sequence into two with the user predicate and returns the right sequence handle.

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

isplitMaxRightProdM Source #

Arguments

:: (PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq (PrimState m) f a

Sequence storage

-> Handle (PrimState m)

Sequence handle

-> (Int -> a -> m Bool)

User predicate \(f(i, v_0 \dots v_i)\) that takes the index and the monoid value

-> m (Handle (PrimState m))

Handle of the right sequence \([r, n)\), where \(r\) is the maximum \(r\) such that \(f(i, v_0 \dots v_i)\) holds for \(i \in [0, r)\)

Amortized \(O(\log n)\). Splits a sequence into two with the user predicate and returns the right sequence handle.

Constraints

  • The sequence must be non-empty.

Since: 1.2.0.0

Conversions

freeze :: (HasCallStack, PrimMonad m, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq (PrimState m) f a -> Handle (PrimState m) -> m (Vector a) Source #

Amortized \(O(n)\). Returns the sequence of monoid values.

Since: 1.2.0.0