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

AtCoder.Extra.IntervalMap

Description

Dense map covering \([0, n)\) that manages non-overlapping intervals \([l, r)\) within it. Each interval has an associated value \(v\). Use onAdd and onDel hooks to track interval state changes during buildM, insertM and deleteM operations.

Invariant

Each interval is operated as a whole, similar to a persistant data structure. When part of an inerval is modified, the whole interval is deleted first, and the subintervals are re-inserted. It's important for tracking non-linear interval information with the onAdd and onDel hooks (callbacks).

Example

Expand

Create an IntervalMap that covers a half-open interval \([0, n)\):

>>> import AtCoder.Extra.IntervalMap qualified as ITM
>>> import Data.Vector.Unboxed qualified as VU
>>> import Data.Vector.Unboxed.Mutable qualified as VUM
>>> itm <- ITM.new @_ @Int 4

It handles range set queries in amortized \(O(\log n)\) time:

>>> ITM.insert itm 0 4 0 -- 0 0 0 0
>>> ITM.insert itm 1 3 1 -- 0 1 1 0
>>> ITM.freeze itm
[(0,(1,0)),(1,(3,1)),(3,(4,0))]

Track interval informations with the onAdd and onDel hooks:

>>> import Debug.Trace (traceShow)
>>> itm <- ITM.new @_ @Int 4
>>> let onAdd l r x = print ("onAdd", l, r, x)
>>> let onDel l r x = print ("onDel", l, r, x)
>>> ITM.insertM itm 0 4 0 onAdd onDel -- 0 0 0 0
("onAdd",0,4,0)
>>> ITM.insertM itm 1 3 1 onAdd onDel -- 0 1 1 0
("onDel",0,4,0)
("onAdd",0,1,0)
("onAdd",3,4,0)
("onAdd",1,3,1)
>>> ITM.deleteM itm 0 4 onAdd onDel
("onDel",0,1,0)
("onDel",1,3,1)
("onDel",3,4,0)

Since: 1.1.0.0

Synopsis

IntervalMap

data IntervalMap s a Source #

Dense map covering \([0, n)\) that manages non-overlapping intervals \((l, r)\) within it. Each interval has an associated value \(x\). Use onAdd and onDel hooks to track interval state changes during buildM, insertM and deleteM operations.

Since: 1.1.0.0

Constructors

new :: (PrimMonad m, Unbox a) => Int -> m (IntervalMap (PrimState m) a) Source #

\(O(n)\) Creates an empty IntervalMap.

Since: 1.1.0.0

build :: (PrimMonad m, Eq a, Unbox a) => Vector a -> m (IntervalMap (PrimState m) a) Source #

\(O(n + m \log n)\) Creates an IntervalMap by combining consecutive equal values into one interval.

Example

Expand
>>> itm <- build @_ @Int (VU.fromList [10,10,11,11,12,12])
>>> freeze itm
[(0,(2,10)),(2,(4,11)),(4,(6,12))]

Since: 1.1.0.0

buildM Source #

Arguments

:: (PrimMonad m, Eq a, Unbox a) 
=> Vector a

Input values

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

onAdd hook that take an interval \([l, r)\) with associated value \(v\)

-> m (IntervalMap (PrimState m) a)

The map

\(O(n + m \log n)\) Creates an IntervalMap by combining consecutive equal values into one interval, while performing onAdd hook for each interval.

Since: 1.1.0.0

Metadata

capacity :: IntervalMap s a -> Int Source #

\(O(1)\) Returns the capacity \(n\), where the interval \([0, n)\) is managed by the map.

Since: 1.1.0.0

Lookups

contains :: (PrimMonad m, Unbox a) => IntervalMap (PrimState m) a -> Int -> m Bool Source #

\(O(\log n)\) Returns whether a point \(x\) is contained within any of the intervals.

Since: 1.1.0.0

intersects :: (PrimMonad m, Unbox a) => IntervalMap (PrimState m) a -> Int -> Int -> m Bool Source #

\(O(\log n)\) Returns whether an interval \([l, r)\) is fully contained within any of the intervals.

Since: 1.1.0.0

lookup :: (PrimMonad m, Unbox a) => IntervalMap (PrimState m) a -> Int -> Int -> m (Maybe (Int, Int, a)) Source #

\(O(\log n)\) Looks up an interval that fully contains \([l, r)\).

Since: 1.1.0.0

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

\(O(\log n)\) Looks up an interval that fully contains \([l, r)\) and reads out the value. Throws an error if no such interval exists.

Since: 1.1.0.0

readMaybe :: (PrimMonad m, Unbox a) => IntervalMap (PrimState m) a -> Int -> Int -> m (Maybe a) Source #

\(O(\log n)\) Looks up an interval that fully contains \([l, r)\) and reads out the value. Returns Nothing if no such interval exists.

Since: 1.1.0.0

Modifications

Insertions

insert :: (PrimMonad m, Eq a, Unbox a) => IntervalMap (PrimState m) a -> Int -> Int -> a -> m () Source #

Amortized \(O(\log n)\) Inserts an interval \([l, r)\) with associated value \(v\) into the map. Overwrites any overlapping intervals.

Since: 1.1.0.0

insertM Source #

Arguments

:: (PrimMonad m, Eq a, Unbox a) 
=> IntervalMap (PrimState m) a

The map

-> Int

\(l\)

-> Int

\(r\)

-> a

\(v\)

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

onAdd hook that take an interval \([l, r)\) with associated value \(v\)

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

onDel hook that take an interval \([l, r)\) with associated value \(v\)

-> m () 

Amortized \(O(\log n)\) Inserts an interval \([l, r)\) with associated value \(v\) into the map. Overwrites any overlapping intervals. Tracks interval state changes via onAdd and onDel hooks.

Since: 1.1.0.0

Deletions

delete :: (PrimMonad m, Unbox a) => IntervalMap (PrimState m) a -> Int -> Int -> m () Source #

Amortized \(O(\log n)\) Deletes an interval \([l, r)\) from the map.

Since: 1.1.0.0

deleteM Source #

Arguments

:: (PrimMonad m, Unbox a) 
=> IntervalMap (PrimState m) a

The map

-> Int

\(l\)

-> Int

\(r\)

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

onAdd hook that take an interval \([l, r)\) with associated value \(v\)

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

onDel hook that take an interval \([l, r)\) with associated value \(v\)

-> m () 

Amortized \(O(\log n)\) Deletes an interval \([l, r)\) from the map. Tracks interval state changes via onAdd and onDel hooks.

Since: 1.1.0.0

Overwrites

overwrite :: (PrimMonad m, Eq a, Unbox a) => IntervalMap (PrimState m) a -> Int -> Int -> a -> m () Source #

\(O(\log n)\) Shorthand for overwriting the value of an interval that contains \([l, r)\).

Since: 1.1.0.0

overwriteM Source #

Arguments

:: (PrimMonad m, Eq a, Unbox a) 
=> IntervalMap (PrimState m) a

The map

-> Int

\(l\)

-> Int

\(r\)

-> a

\(v\)

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

onAdd hook that take an interval \([l, r)\) with associated value \(v\)

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

onDel hook that take an interval \([l, r)\) with associated value \(v\)

-> m () 

\(O(\log n)\). Shorthand for overwriting the value of an interval that contains \([l, r)\). Tracks interval state changes via onAdd and onDel hooks.

Since: 1.1.0.0

Conversions

freeze :: (PrimMonad m, Unbox a) => IntervalMap (PrimState m) a -> m (Vector (Int, (Int, a))) Source #

\(O(n \log n)\) Enumerates the intervals and the associated values as \((l, (r, x))\) tuples, where \([l, r)\) is the interval and \(x\) is the associated value.

Since: 1.1.0.0