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

AtCoder.Extra.Monoid.RollingHash

Description

Rolling hash algorithm implemented as a monoid, typically stored in a segment tree. The type parameters \(b\) and \(p\) represent the B-adic base and the modulus, respectively.

Combining RollingHash with SegTree enables \(O(\log |s|)\) string slice creation and \(O(1)\) slice comparison.

Since: 1.1.0.0

Synopsis

Rolling hash

data RollingHash b p Source #

Rolling hash algorithm implemented as a monoid, typically stored in a segment tree. The type parameters \(b\) and \(p\) represent the B-adic base and the modulus, respectively.

Combining RollingHash with SegTree enables \(O(\log |s|)\) string slice creation and \(O(1)\) slice comparison.

Example

Expand

It's convenient to define a type alias of RollingHash:

>>> import AtCoder.Extra.Monoid.RollingHash qualified as RH
>>> import AtCoder.SegTree qualified as ST
>>> import Data.Char (ord)
>>> import Data.Semigroup (Dual (..))
>>> type RH = RH.RollingHash 100 998244353

Let's test whether "abcba" is a palindrome:

>>> seg <- ST.build @_ @RH . VU.map (RH.unsafeNew . ord) $ VU.fromList "abcba"
>>> seg' <- ST.build @_ @(Dual RH) . VU.map (Dual . RH.unsafeNew . ord) $ VU.fromList "abcba"
>>> hash1 <- ST.prod seg 2 5       --   cba  (left to right)
>>> Dual hash2 <- ST.prod seg' 0 3 -- abc    (right to lett)
>>> hash1 == hash2
True

Since: 1.1.0.0

Constructors

RollingHash 

Fields

Instances

Instances details
Vector Vector (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

Methods

basicUnsafeFreeze :: Mutable Vector s (RollingHash b p) -> ST s (Vector (RollingHash b p))

basicUnsafeThaw :: Vector (RollingHash b p) -> ST s (Mutable Vector s (RollingHash b p))

basicLength :: Vector (RollingHash b p) -> Int

basicUnsafeSlice :: Int -> Int -> Vector (RollingHash b p) -> Vector (RollingHash b p)

basicUnsafeIndexM :: Vector (RollingHash b p) -> Int -> Box (RollingHash b p)

basicUnsafeCopy :: Mutable Vector s (RollingHash b p) -> Vector (RollingHash b p) -> ST s ()

elemseq :: Vector (RollingHash b p) -> RollingHash b p -> b0 -> b0

MVector MVector (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

(KnownNat b, KnownNat p) => Monoid (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

Methods

mempty :: RollingHash b p #

mappend :: RollingHash b p -> RollingHash b p -> RollingHash b p #

mconcat :: [RollingHash b p] -> RollingHash b p #

(KnownNat b, KnownNat p) => Semigroup (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

Methods

(<>) :: RollingHash b p -> RollingHash b p -> RollingHash b p #

sconcat :: NonEmpty (RollingHash b p) -> RollingHash b p #

stimes :: Integral b0 => b0 -> RollingHash b p -> RollingHash b p #

Show (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

Methods

showsPrec :: Int -> RollingHash b p -> ShowS #

show :: RollingHash b p -> String #

showList :: [RollingHash b p] -> ShowS #

Eq (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

Methods

(==) :: RollingHash b p -> RollingHash b p -> Bool #

(/=) :: RollingHash b p -> RollingHash b p -> Bool #

Unbox (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

newtype MVector s (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

newtype MVector s (RollingHash b p) = MV_RH (MVector s RHRepr)
newtype Vector (RollingHash b p) Source #

Since: 1.1.0.0

Instance details

Defined in AtCoder.Extra.Monoid.RollingHash

newtype Vector (RollingHash b p) = V_RH (Vector RHRepr)

Constructors

new :: forall b p. (KnownNat b, KnownNat p) => Int -> RollingHash b p Source #

\(O(1)\) Creates a one-length RollingHash from an integer.

Since: 1.1.0.0

unsafeNew :: forall b p. (KnownNat b, KnownNat p) => Int -> RollingHash b p Source #

\(O(1)\) Creates a one-length RollingHash from an integer without taking the mod.

Since: 1.1.0.0