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

AtCoder.Extra.WaveletMatrix2d

Description

A 2D, static wavelet matrix with segment tree, that can handle point add and rectangle sum queries. Points cannot be added after construction, but monoid values in each point can be modified later.

SegTree2d vs WaveletMatrix2d

They basically the same functionalities and performance, however, in ac-library-hs, SegTree2d has better API and even outperforms WaveletMatrix2d.

Example

Expand

Create a WaveletMatrix2d with initial vertex values:

>>> import AtCoder.Extra.WaveletMatrix2d qualified as WM
>>> import Data.Semigroup (Sum (..))
>>> import Data.Vector.Unboxed qualified as VU
>>> -- 8  9 10 11
>>> -- 4  5  6  7
>>> -- 0  1  2  3
>>> wm <- WM.build negate $ VU.generate 12 $ \i -> let (!y, !x) = i `divMod` 4 in (x, y, Sum i)

Read the value at x=2,y=1:

>>> WM.read wm (2, 1)
Sum {getSum = 6}

Other segment tree methods are also available, but in 2D:

>>> WM.allProd wm -- (0 + 11) * 12 / 2 = 66
Sum {getSum = 66}
>>> WM.prod wm {- x -} 1 3 {- y -} 0 3 -- 1 + 2 + 5 + 6 + 9 + 10
Sum {getSum = 33}
>>> WM.modify wm (+ 2) (1, 1)
>>> WM.prod wm {- x -} 1 3 {- y -} 0 3 -- 1 + 2 + 7 + 6 + 9 + 10
Sum {getSum = 35}
>>> WM.write wm (1, 1) $ Sum 0
>>> WM.prod wm {- x -} 1 3 {- y -} 0 3 -- 1 + 2 + 0 + 6 + 9 + 10
Sum {getSum = 28}

Since: 1.1.0.0

Synopsis

Wavelet matrix 2D

data WaveletMatrix2d s a Source #

Segment Tree on Wavelet Matrix: points on a 2D plane and rectangle products.

Since: 1.1.0.0

Constructors

WaveletMatrix2d 

Fields

  • rawWmWm2d :: !RawWaveletMatrix

    The wavelet matrix that represents points on a 2D plane.

    Since: 1.1.0.0

  • xyDictWm2d :: !(Vector (Int, Int))

    (x, y) index compression dictionary.

    Since: 1.1.0.0

  • yDictWm2d :: !(Vector Int)

    y index compression dictionary.

    Since: 1.1.0.0

  • segTreesWm2d :: !(Vector (SegTree s a))

    The segment tree of the weights of the points in the order of xyDictWm2d.

    Since: 1.1.0.0

  • invWm2d :: !(a -> a)

    The inverse operator of the interested monoid.

    Since: 1.1.0.0

Counstructor

new Source #

Arguments

:: (PrimMonad m, Monoid a, Unbox a) 
=> (a -> a)

Inverse operator of the monoid

-> Vector (Int, Int)

Input points

-> m (WaveletMatrix2d (PrimState m) a)

A 2D wavelet matrix

O(nlogn) Creates a WaveletMatrix2d with mempty as the initial monoid values for each point.

Since: 1.1.0.0

build Source #

Arguments

:: (PrimMonad m, Monoid a, Unbox a) 
=> (a -> a)

Inverse operator of the monoid

-> Vector (Int, Int, a)

Input points with initial values

-> m (WaveletMatrix2d (PrimState m) a)

A 2D wavelet matrix

O(nlogn) Creates a WaveletMatrix2d with wavelet matrix with segment tree with initial monoid values. Monoids on a duplicate point are accumulated with (<>).

Since: 1.1.0.0

Segment tree methods

read :: (HasCallStack, PrimMonad m, Unbox a, Monoid a) => WaveletMatrix2d (PrimState m) a -> (Int, Int) -> m a Source #

O(1) Returns the monoid value at (x,y).

Since: 1.1.0.0

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

O(log2n) Writes the monoid value at (x,y). Access to unknown points are undefined.

Since: 1.1.0.0

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

O(log2n) Modifies the monoid value at (x,y). Access to unknown points are undefined.

Since: 1.1.0.0

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

O(log2n) Returns monoid product Πp[x1,x2)×[y1,y2)ap.

Since: 1.1.0.0

prodMaybe :: (PrimMonad m, Unbox a, Monoid a) => WaveletMatrix2d (PrimState m) a -> Int -> Int -> Int -> Int -> m (Maybe a) Source #

O(log2n) Returns the monoid product in [x1,x2)×[y1,y2). Returns Nothing for invalid intervals.

Since: 1.1.0.0

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

O(log2n) Return the monoid product in [,)×[,).

Since: 1.1.0.0