Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
AtCoder.SegTree
Description
It is the data structure for monoids (S,⋅:S×S→S,e∈S), i.e., the algebraic structure that satisfies the following properties.
- associativity: (a⋅b)⋅c = a⋅(b⋅c) for all a,b,c∈S
- existence of the identity element: a⋅e = e⋅a = a for all a∈S
Given an array S of length N, it processes the following queries in O(logN) time (see Appendix for further details).
- Updating an element
- Calculating the product of the elements of an interval
For simplicity, in this document, we assume that the oracles op
and e
work in constant time.
If these oracles work in O(T) time, each time complexity appear in this document is
multipled by O(T).
Example
Create a SegTree
of
:Sum
Int
>>>
import AtCoder.SegTree qualified as ST
>>>
import Data.Vector.Unboxed qualified as VU
>>>
import Data.Monoid (Sum(..))
>>>
seg <- ST.new @_ @(Sum Int) 4
Modify the vertex values:
>>>
ST.write seg 1 $ Sum 1
>>>
ST.modify seg (+ Sum 2) 2
>>>
ST.write seg 3 $ Sum 3 -- [0, 1, 2, 3]
>>>
ST.read seg 1
Sum {getSum = 1}
Get product of the monoids:
>>>
ST.prod seg 0 3
Sum {getSum = 3}
>>>
ST.allProd seg
Sum {getSum = 6}
Binary searches:
>>>
ST.maxRight seg 0 (< (Sum 5)) -- sum [0, 3) = 2 < 5
3
>>>
ST.minLeft seg 4 (< (Sum 5)) -- sum [3, 4) = 3 < 5
3
Inspect all the values in O(n) with freeze
or in O(1) with unsafeFreeze
:
>>>
VU.map getSum <$> ST.freeze seg
[0,1,2,3]
Tips
prod
returns al⋅al+1⋅..⋅ar−1. If you need ar−1⋅ar−2⋅..⋅al, wrap your monoid inDual
.- If you ever need to store boxed types to
LazySegTree
, wrap it inData.Vector.Unboxed.DoNotUnboxStrict
or the like.
Major changes from the original ac-library
- The implementation is
Monoid
based, not function objects. get
andset
are renamed toread
andwrite
.modify
,modifyM
,exchange
,freeze
andunsafeFreeze
are added.
Since: 1.0.0.0
Synopsis
- data SegTree s a
- new :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Int -> m (SegTree (PrimState m) a)
- build :: (PrimMonad m, Monoid a, Unbox a) => Vector a -> m (SegTree (PrimState m) a)
- write :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> a -> m ()
- modify :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> (a -> a) -> Int -> m ()
- modifyM :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> (a -> m a) -> Int -> m ()
- exchange :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> a -> m a
- read :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> m a
- prod :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> Int -> m a
- prodMaybe :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> Int -> m (Maybe a)
- allProd :: (PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> m a
- minLeft :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> (a -> Bool) -> m Int
- minLeftM :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> (a -> m Bool) -> m Int
- maxRight :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> (a -> Bool) -> m Int
- maxRightM :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> (a -> m Bool) -> m Int
- freeze :: (PrimMonad m, Unbox a) => SegTree (PrimState m) a -> m (Vector a)
- unsafeFreeze :: (PrimMonad m, Unbox a) => SegTree (PrimState m) a -> m (Vector a)
Segment tree
Constructors
new :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => Int -> m (SegTree (PrimState m) a) Source #
Creates an array a of length n. All the elements are initialized to mempty
.
Constraints
- 0≤n
Complexity
- O(n)
Since: 1.0.0.0
build :: (PrimMonad m, Monoid a, Unbox a) => Vector a -> m (SegTree (PrimState m) a) Source #
Creates an array with initial values.
Complexity
- O(n)
Since: 1.0.0.0
Accessing elements
write :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> a -> m () Source #
Writes p-th value of the array to x.
Constraints
- 0≤p<n
Complexity
- O(logn)
Since: 1.0.0.0
modify :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> (a -> a) -> Int -> m () Source #
(Extra API) Modifies p-th value with a function f.
Constraints
- 0≤p<n
Complexity
- O(logn)
Since: 1.0.0.0
modifyM :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> (a -> m a) -> Int -> m () Source #
(Extra API) Modifies p-th value with a monadic function f.
Constraints
- 0≤p<n
Complexity
- O(logn)
Since: 1.0.0.0
exchange :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> a -> m a Source #
(Extra API) Writes p-th value of the array to x and returns the old value.
Constraints
- 0≤p<n
Complexity
- O(logn)
Since: 1.1.0.0
read :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> m a Source #
Returns p-th value of the array.
Constraints
- 0≤p<n
Complexity
- O(1)
Since: 1.0.0.0
Products
prod :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> Int -> m a Source #
Returns a[l]⋅...⋅a[r−1], assuming the properties of the monoid. It
returns mempty
if l=r.
Constraints
- 0≤l≤r≤n
Complexity
- O(logn)
Since: 1.0.0.0
prodMaybe :: (HasCallStack, PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> Int -> Int -> m (Maybe a) Source #
allProd :: (PrimMonad m, Monoid a, Unbox a) => SegTree (PrimState m) a -> m a Source #
Returns a[0] <> ... <> a[n - 1]
, assuming the properties of the monoid. It returns mempty
if n=0.
Complexity
- O(1)
Since: 1.0.0.0
Binary searches
Left binary searches
Arguments
:: (HasCallStack, PrimMonad m, Monoid a, Unbox a) | |
=> SegTree (PrimState m) a | The segment tree |
-> Int | r |
-> (a -> Bool) | p: user prediate |
-> m Int | l: p holds for [l,r) |
Applies a binary search on the segment tree. It returns an index l that satisfies both of the following.
If f is monotone, this is the minimum l that satisfies f(a[l]⋅a[l+1]⋅...⋅a[r−1]).
Constraints
- if f is called with the same argument, it returns the same value, i.e., f has no side effect.
f mempty == True
.- 0≤r≤n
Complexity
- O(logn)
Since: 1.0.0.0
Arguments
:: (HasCallStack, PrimMonad m, Monoid a, Unbox a) | |
=> SegTree (PrimState m) a | The segment tree |
-> Int | r |
-> (a -> m Bool) | p: user prediate |
-> m Int | l: p holds for [l,r) |
Monadic variant of minLeft
.
Constraints
- if f is called with the same argument, it returns the same value, i.e., f has no side effect.
f mempty == True
.- 0≤r≤n
Complexity
- O(logn)
Since: 1.0.0.0
Right binary searches
Arguments
:: (HasCallStack, PrimMonad m, Monoid a, Unbox a) | |
=> SegTree (PrimState m) a | The segment tree |
-> Int | l |
-> (a -> Bool) | p: user prediate |
-> m Int | r: p holds for [l,r) |
Applies a binary search on the segment tree. It returns an index r that satisfies both of the following.
If f is monotone, this is the maximum r that satisfies f(a[l]⋅a[l+1]⋅...⋅a[r−1]).
Constraints
- if f is called with the same argument, it returns the same value, i.e., f has no side effect.
f mempty == True
.- 0≤l≤n
Complexity
- O(logn)
Since: 1.0.0.0
Arguments
:: (HasCallStack, PrimMonad m, Monoid a, Unbox a) | |
=> SegTree (PrimState m) a | The segment tree |
-> Int | l |
-> (a -> m Bool) | p: user prediate |
-> m Int | r: p holds for [l,r) |
Moandic variant of maxRight
.
Constraints
- if f is called with the same argument, it returns the same value, i.e., f has no side effect.
f mempty == True
.- 0≤l≤n
Complexity
- O(logn)
Since: 1.0.0.0