Loading [MathJax]/jax/output/HTML-CSS/jax.js
ac-library-hs-1.2.1.0: Data structures and algorithms
Safe HaskellSafe-Inferred
LanguageGHC2021

AtCoder.Extra.Seq.Raw

Description

Base module for implementing dynamic sequences. It internaly uses a splay tree and user has to track the root node change.

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

Constructors

newST :: (Monoid f, Unbox f, Monoid a, Unbox a) => Int -> ST s (Seq s f a) Source #

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

Since: 1.2.0.0

resetST :: Seq s f a -> ST s () Source #

O(1) Clears the sequence storage.

Since: 1.2.0.0

newNodeST :: (HasCallStack, Monoid f, Unbox f, Unbox a) => Seq s f a -> a -> ST s Index Source #

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

Since: 1.2.0.0

newSeqST :: (HasCallStack, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Vector a -> ST s Index Source #

O(n) Allocates a new sequence.

Since: 1.2.0.0

freeNodeST :: Seq s v a -> Index -> ST s () Source #

O(1) Frees a node.

Since: 1.2.0.0

freeSubtreeST :: Unbox a => Seq s f a -> Index -> ST s () Source #

O(n) Frees a subtree.

Since: 1.2.0.0

Metadata

capacity :: Seq s f a -> Int Source #

O(1) Returns the capacity of the sequence storage.

Since: 1.2.1.0

lengthST :: Seq s f a -> Index -> ST s Int Source #

O(1) Returns the length of a sequence or a subtree.

Since: 1.2.1.0

Merge/split

mergeST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Index -> ST s Index Source #

Amortized O(logn). Merges two sequences l,r into one in the given order, ignoring empty sequences.

Constraints

  • The vertices must be either null or a root.

Since: 1.2.0.0

merge3ST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Index -> Index -> ST s Index Source #

Amortized O(logn). Merges three sequences l,m,r into one in the given order, ignoring empty sequences.

Constraints

  • The vertices must be either null or a root.

Since: 1.2.0.0

merge4ST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Index -> Index -> Index -> ST s Index Source #

Amortized O(logn). Merges four sequences l,b,c,d,m,r into one in the given order, ignoring empty sequences.

Constraints

  • The vertices must be either null or a root.

Since: 1.2.0.0

splitST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> ST s (Index, Index) Source #

Amortized O(logn). Splits a sequences into two: [0,k),[k,n).

Constraints

  • The node must be null or a root.
  • 0kn.

Since: 1.2.0.0

split3ST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> Int -> ST s (Index, Index, Index) Source #

Amortized O(logn). Splits a sequences into three: [0,l),[l,r),[r,n).

Constraints

  • The node must be null or a root.
  • 0lrn.

Since: 1.2.0.0

split4ST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> Int -> Int -> ST s (Index, Index, Index, Index) Source #

Amortized O(logn). Splits a sequences into four: [0,i),[i,j),[j,k),[k,n).

Constraints

  • The node must be null or a root.
  • 0ijkn.

Since: 1.2.0.0

splitLrST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> ST s (Index, Index, Index) Source #

Amortized O(logn). Splits a sequence into three: [0,root),root,[root+1,n).

Constraints

  • The node must be a root.

Since: 1.2.0.0

sliceST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> Int -> ST s Index Source #

Amortized O(logn). Captures the root of a subtree of [l,r). Splay the new root after call.

Constraints

  • 0≤<rn. Note that the interval must have positive length.

Since: 1.2.0.0

Read/write

readST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> ST s (a, Index) Source #

Amortized O(logn). Reads the k-th node's monoid value.

Constraints

  • 0k<n

Since: 1.2.0.0

readMaybeST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> ST s (Maybe (a, Index)) Source #

Amortized O(logn). Reads the k-th node's monoid value.

Constraints

  • The root must be empty or a root.

Since: 1.2.0.0

writeST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> a -> ST s Index Source #

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

Constraints

  • The node must be a root.
  • 0k<n

Since: 1.2.0.0

modifyST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> (a -> a) -> Int -> ST s Index Source #

Amortized O(logn). Modifies the k-th node's monoid value.

Constraints

  • The node must be a root.
  • 0k<n

Since: 1.2.0.0

exchangeST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> a -> ST s (a, Index) Source #

Amortized O(logn). Exchanges the k-th node's monoid value.

Constraints

  • The node must be a root.
  • 0k<n

Since: 1.2.0.0

Products

prodST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> Int -> ST s (a, Index) Source #

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

Constraints

  • The node must be a root
  • 0lrn

Since: 1.2.0.0

prodMaybeST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> Int -> ST s (Maybe (a, Index)) Source #

Amortized O(logn). Returns the monoid product in an interval [l,r). Returns Nothing if an invalid interval is given or for an empty sequence.

Since: 1.2.0.0

prodAllST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> ST s a Source #

Amortized O(logn). Returns the monoid product of the whole sequence. Returns mempty for an empty sequence.

Constraint

  • The node must be null or a root.

Since: 1.2.0.0

Applications

applyInST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> Int -> f -> ST s Index Source #

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

Constraints

  • 0lrn

Since: 1.2.0.0

applyToRootST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> f -> ST s () Source #

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

Since: 1.2.0.0

reverseST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> Int -> ST s Index Source #

Amortized O(logn). 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

insertST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> a -> ST s Index Source #

Amortized O(logn). Inserts a new node at k with initial monoid value v. This functions for an empty index.

Constraints

  • The node must be null or a root.
  • 0kn

Since: 1.2.0.0

deleteST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> ST s (a, Index) Source #

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

Constraints

  • The node must be null or a root.
  • 0k<n

Since: 1.2.0.0

deleteST_ :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> ST s Index Source #

Amortized O(logn). Frees the k-th node.

Constraints

  • The node must be null or a root.
  • 0k<n

Since: 1.2.0.0

detachST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> ST s Index Source #

Amortized O(logn). Detaches the k-th node and returns the new root of the original sequence.

Constraints

  • The node must be null or a root.
  • 0k<n

Since: 1.2.0.0

Balancing

rotateST :: HasCallStack => Seq s v a -> Index -> ST s () Source #

Amortized O(logn). Rotates a child node.

Constraints

  • 0i<n

Since: 1.2.0.0

splayST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Bool -> ST s () Source #

Amortized O(logn). Moves up a node to be a root.

Since: 1.2.0.0

splayKthST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> Int -> ST s Index Source #

Amortized O(logn). Finds k-th node and splays it. Returns the new root.

Constraints

  • 0k<n

Since: 1.2.0.0

Bisection methods

C++-like

ilowerBoundST Source #

Arguments

:: (SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq s f a

Sequence storage

-> Index

Root node

-> (Int -> a -> Bool)

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

-> ST s (Int, Index)

(r, root)

Amortized O(logn).

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

-> Index

Root node

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

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

-> m (Int, Index)

(r, root)

Amortized O(logn).

Since: 1.2.0.0

ilowerBoundProdST Source #

Arguments

:: (SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq s f a

Sequence storage

-> Index

Root node

-> (Int -> a -> Bool)

User predicate f(i,v0vi) that takes the index and the monoid product

-> ST s (Int, Index)

(r, root)

Amortized O(logn).

Constraints

  • The node must be a root.

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

-> Index

Root node

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

User predicate f(i,v0vi) that takes the index and the monoid product

-> m (Int, Index)

(r, root)

Amortized O(logn).

Constraints

  • The node must be a root.

Since: 1.2.0.0

Splits

isplitMaxRightST Source #

Arguments

:: (SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq s f a

Sequence storage

-> Index

Root node

-> (Int -> a -> Bool)

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

-> ST s (Index, Index)

(left, right) sequences where f holds for the left

Amortized O(logn). Given a monotonious sequence, returns the rightmost node vk where f(v) holds for every [0,i)(0i<k).

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

-> Index

Root node

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

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

-> m (Index, Index)

(left, right) sequences where f holds for the left

Amortized O(logn). Given a monotonious sequence, returns the rightmost node vk where f(v) holds for every [0,i)(0i<k).

Since: 1.2.0.0

isplitMaxRightProdST Source #

Arguments

:: (SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq s f a

Sequence storage

-> Index

Root node

-> (Int -> a -> Bool)

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

-> ST s (Index, Index)

(left, right) sequences where f holds for the left

Amortized O(logn). Given a monotonious sequence, returns the rightmost node vk where f(v) holds for every [0,i)(0i<k).

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

-> Index

Root node

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

User predicate f(i,vi) that takes the index and the monoid value | r

-> m (Index, Index)

(left, right) sequences where f holds for the left

Amortized O(logn). Given a monotonious sequence, returns the rightmost node vk where f(v) holds for every [0,i)(0i<k).

Since: 1.2.0.0

Max right

imaxRightST Source #

Arguments

:: (SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq s f a

Sequence storage

-> Index

Root node

-> (Int -> a -> Bool)

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

-> ST s (Int, Index, Index)

(r, left, right)

Amortized O(logn). Given a monotonious sequence, returns the rightmost node v where f(v) holds for every vi(0i<k). Note that f works for a single node, not a monoid product.

Constraints

  • The node must be a root.

Since: 1.2.0.0

imaxRightM Source #

Arguments

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

Sequence storage

-> Index

Root node

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

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

-> m (Int, Index, Index)

(r, left, right)

Amortized O(logn). Given a monotonious sequence, returns the rightmost node vk where f(v) holds for every vi(0ik). Note that f works for a single node, not a monoid product.

Constraints

  • The node must be a root.

Since: 1.2.0.0

imaxRightProdST Source #

Arguments

:: (SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq s f a

Sequence storage

-> Index

Root node

-> (Int -> a -> Bool)

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

-> ST s (Int, Index, Index)

(ilowerBound, rightmost node, new root)

Amortized O(logn). Given a monotonious sequence, returns the rightmost node vk where f(v) holds for every [0,i)(0i<k).

Constraints

  • The node must be a root.

Since: 1.2.0.0

imaxRightProdM Source #

Arguments

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

Sequence storage

-> Index

Root node

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

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

-> m (Int, Index, Index)

(ilowerBound, rightmost node, new root)

Amortized O(logn). Given a monotonious sequence, returns the rightmost node vk where f(v) holds for every [0,i)(0i<k).

Constraints

  • The node must be a root.

Since: 1.2.0.0

Conversions

freezeST :: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> ST s (Vector a) Source #

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

Since: 1.2.0.0

Internals

These functions are exported primarily for Map implementations.

splitMaxRightWithST Source #

Arguments

:: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq s f a

Sequence storage

-> Index

Root node

-> (Index -> ST s Bool)

User predicate f(i)

-> ST s (Index, Index)

(left, right) sequences where f holds for the left

Amortized O(logn).

Since: 1.2.1.0

maxRightWithST Source #

Arguments

:: (HasCallStack, SegAct f a, Eq f, Monoid f, Unbox f, Monoid a, Unbox a) 
=> Seq s f a

Sequence storage

-> Index

Root node

-> (Index -> ST s Bool)

User predicate

-> ST s (Index, Index)

(rightmost node, new root)

Amortized O(logn). Given a monotonious sequence, returns the rightmost node vk where f(v) holds for every [0,i)(0i<k).

Constraints

  • The node must be a root.

Since: 1.2.1.0

updateNodeST :: (Monoid a, Unbox a) => Seq s f a -> Index -> ST s () Source #

O(1) Recomputes the node size and the monoid product.

Since: 1.2.1.0

writeNodeST :: (Monoid a, Unbox a) => Seq s f a -> Index -> a -> ST s () Source #

O(1) Writes to the monoid value of a node.

Since: 1.2.1.0

modifyNodeST :: (HasCallStack, Monoid a, Unbox a) => Seq s f a -> (a -> a) -> Index -> ST s () Source #

O(1) Modifies the monoid value of a node.

Since: 1.2.1.0

exchangeNodeST :: (HasCallStack, Monoid a, Unbox a) => Seq s f a -> Index -> a -> ST s a Source #

O(1) Exchanges the monoid value of a node.

Since: 1.2.1.0

propNodeST :: (HasCallStack, SegAct f a, Eq f, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> ST s () Source #

Amortized O(logn). Propgates the lazily propagated values on a node.

Since: 1.2.1.0

applyNodeST :: (HasCallStack, SegAct f a, Unbox f, Monoid a, Unbox a) => Seq s f a -> Index -> f -> ST s () Source #

Amortized O(logn). Propgates at a node.

Since: 1.2.1.0