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

AtCoder.Extra.DynSegTree.Raw

Description

Base module of a dynamic segment tree.

Since: 1.2.1.0

Synopsis

Dynamic segment tree

data DynSegTree s a Source #

A dynamic segment tree that covers a half-open interval \([l_0, r_0)\). 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) \rightarrow 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

newST :: (HasCallStack, Unbox a) => Bool -> Int -> Int -> Int -> (Int -> Int -> a) -> ST s (DynSegTree s a) Source #

\(O(n)\)

Since: 1.2.1.0

newRootST :: (HasCallStack, Monoid a, Unbox a) => DynSegTree s a -> ST s Index Source #

\(O(1)\)

Since: 1.2.1.0

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

\(O(1)\)

Since: 1.2.1.0

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

\(O(L)\)

Since: 1.2.1.0

Accessing elements

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

\(O(\log L)\)

Since: 1.2.1.0

Products

prodST :: forall a s. (HasCallStack, Monoid a, Unbox a) => DynSegTree s a -> Index -> Int -> Int -> ST s a Source #

\(O(\log L)\)

Since: 1.2.1.0

Tree operations

resetIntervalST :: forall a s. (HasCallStack, Monoid a, Unbox a) => DynSegTree s a -> Index -> Int -> Int -> ST s Index Source #

\(O(\log L)\) Resets an interval \([l, r)\) to initial monoid values.

Since: 1.2.1.0

Binary searches

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

\(O(\log L)\)

Since: 1.2.1.0