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

AtCoder.Extra.DynSegTree.Persistent

Description

A dynamic, persistent segment tree that covers a half-open interval [l0,r0). Nodes are instantinated as needed, with the required capacity being approximately 4qlog2L, where q is the number of mutable operations and L is the length of the interval.

Example

Expand
>>> import AtCoder.Extra.DynSegTree.Persistent qualified as Seg
>>> import Data.Semigroup (Sum (..))
>>> import Data.Vector.Unboxed qualified as VU

Create a DynSegTree over [0,4) with some initial capacity:

>>> let len = 4; q = 2
>>> seg <- Seg.new @_ @(Sum Int) (Seg.recommendedCapacity len q) 0 4

Different from the SegTree module, it requires explicit root handle:

>>> -- [0, 0, 0, 0]
>>> root <- Seg.newRoot seg
>>> root1 <- Seg.write seg root 1 $ Sum 10
>>> root2 <- Seg.write seg root1 2 $ Sum 20
>>> -- [0, 10, 20, 0]
>>> Seg.prod seg root2 0 3
Sum {getSum = 30}
>>> Seg.maxRight seg root2 (< (Sum 30))
2

Since: 1.2.1.0

Synopsis

Dynamic segment tree

data DynSegTree s a Source #

A dynamic segment tree that covers a half-open interval [l0,r0). Is is dynamic in that the nodes are instantinated as needed.

Since: 1.2.1.0

Constructors

DynSegTree 

Fields

  • capacityDst :: !Int

    The maximum number of nodes allocated

    Since: 1.2.1.0

  • isPersistentDst :: !Bool

    Whether the data is persistent or not

    Since: 1.2.1.0

  • l0Dst :: !Int

    Left index boundary (inclusive)

    Since: 1.2.1.0

  • r0Dst :: !Int

    Right index boundary (exclusive)

    Since: 1.2.1.0

  • initialProdDst :: !(Int -> Int -> a)

    Initial monoid value assignment g:(l,r)a

    Since: 1.2.1.0

  • poolDst :: !(Pool s ())

    Pool for free slot management.

    Since: 1.2.1.0

  • lDst :: !(MVector s Index)

    Decomposed node storage: left children

    Since: 1.2.1.0

  • rDst :: !(MVector s Index)

    Decomposed node storage: right children

    Since: 1.2.1.0

  • xDst :: !(MVector s a)

    Decomposed node storage: monoid value

    Since: 1.2.1.0

Re-exports

newtype Index Source #

Strongly typed index of pool items. User has to explicitly corece on raw index use.

Constructors

Index 

Fields

Instances

Instances details
Show Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

Eq Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

Methods

(==) :: Index -> Index -> Bool #

(/=) :: Index -> Index -> Bool #

Ord Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

Methods

compare :: Index -> Index -> Ordering #

(<) :: Index -> Index -> Bool #

(<=) :: Index -> Index -> Bool #

(>) :: Index -> Index -> Bool #

(>=) :: Index -> Index -> Bool #

max :: Index -> Index -> Index #

min :: Index -> Index -> Index #

Prim Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

Unbox Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

Vector Vector Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

MVector MVector Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

newtype Vector Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

newtype Vector Index = V_Index (Vector Index)
newtype MVector s Index Source # 
Instance details

Defined in AtCoder.Extra.Pool

newtype MVector s Index = MV_Index (MVector s Index)

Constructors

new Source #

Arguments

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

Capacity n

-> Int

Left index boundary l0

-> Int

Right index boundary r0

-> m (DynSegTree (PrimState m) a)

Dynamic, persistent segment tree

O(n) Creates a DynSegTree of capacity n for interval [l0,r0) with mempty as initial leaf values.

Since: 1.2.1.0

buildWith Source #

Arguments

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

Capacity n

-> Int

Left index boundary l0)

-> Int

Right index boundary r0)

-> (Int -> Int -> a)

Initial monoid value assignment g:(l,r)a

-> m (DynSegTree (PrimState m) a)

Dynamic, persistent segment tree

O(n) Creates a DynSegTree of capacity n for interval [l0,r0) with initial value assignment g(l,r).

Since: 1.2.1.0

recommendedCapacity :: Int -> Int -> Int Source #

O(1) Returns recommended capacity for L and q: 2qlog2L.

Since: 1.2.1.0

newRoot :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> m Index Source #

O(1) Creates a new root in [l0,r0).

Since: 1.2.1.0

newSeq :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Vector a -> m Index Source #

O(L) Creates a new root node with contiguous leaf values. User would want to use a strict segment tree instead.

Constraints

  • [l0,r0)=[0,L): The index boundary of the segment tree must match the sequence.

Since: 1.2.1.0

Accessing elements

write :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Index -> Int -> a -> m Index Source #

O(logL) Writes to the monoid value of the node at i.

Constraints

  • l0i<r0

Since: 1.2.1.0

modify :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Index -> (a -> a) -> Int -> m Index Source #

O(logL) Modifies the monoid value of the node at i.

Constraints

  • l0i<r0

Since: 1.2.1.0

modifyM :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Index -> (a -> m a) -> Int -> m Index Source #

O(logL) Modifies the monoid value of the node at i.

Constraints

  • l0i<r0

Since: 1.2.1.0

Products

prod :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Index -> Int -> Int -> m a Source #

O(logL) Returns the monoid product in [l,r).

Constraints

  • l0lrr0

Since: 1.2.1.0

allProd :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Index -> m a Source #

O(logL) Returns the monoid product in [l0,r0).

Since: 1.2.1.0

Tree operations

resetInterval :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Index -> Int -> Int -> m Index Source #

O(logL) Resets an interval [l,r) to initial monoid values.

Constraints

  • l0lrr0

Since: 1.2.1.0

Binary searches

maxRight :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Index -> (a -> Bool) -> m Int Source #

O(logL) Returns the maximum r[l0,r0) where f(al0al0+1ar1) holds.

Since: 1.2.1.0

maxRightM :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => DynSegTree (PrimState m) a -> Index -> (a -> m Bool) -> m Int Source #

O(logL) Returns the maximum r[l0,r0) where f(al0al0+1ar1) holds.

Since: 1.2.1.0

Clear

clear :: PrimMonad m => DynSegTree (PrimState m) a -> m () Source #

O(logL) Claers all the nodes from the storage.

Since: 1.2.2.0