| Safe Haskell | None | 
|---|---|
| Language | GHC2021 | 
AtCoder.Extra.Monoid.RollingHash
Contents
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.
Example
Import:
>>>import AtCoder.Extra.Monoid.RollingHash qualified as RH>>>import AtCoder.SegTree qualified as Seg>>>import Data.ByteString.Char8 qualified as BS>>>import Data.Char (ord)>>>import Data.Vector.Unboxed qualified as VU
Create a helper method for creating RollingHash for a specific base and a modulus:
>>>type RH = RH.RollingHash 100 998244353>>>:{newRH :: BS.ByteString -> VU.Vector RH newRH = VU.map (RH.new . ord) . VU.fromList . BS.unpack :}
Create a segment tree of rolling hash monoids:
>>>let s = BS.pack "ABC_ABC">>>seg <- Seg.build $ newRH s
Now, we can create string slices in \(O(\log n)\) and compare them in \(O(1)\) time:
>>>h1 <- Seg.prod seg 0 3 -- "ABC">>>h2 <- Seg.prod seg 1 4 -- "BC_">>>h3 <- Seg.prod seg 4 7 -- "ABC"
>>>h1 == h2False
>>>h1 == h3True
If you need more accurate result, you could use bigger prime, however, note that the performance gets worse (due to the internal implementation):
type RH = RH.RollingHash 100 2305843009213693951
Since: 1.1.0.0
Synopsis
- data RollingHash (b :: k) (p :: k1) = RollingHash {
- hashRH :: !Int
 - nextDigitRH :: !Int
 
 - new :: forall (b :: Nat) (p :: Nat). (KnownNat b, KnownNat p) => Int -> RollingHash b p
 - unsafeNew :: forall (b :: Nat) (p :: Nat). (KnownNat b, KnownNat p) => Int -> RollingHash b p
 
Rolling hash
data RollingHash (b :: k) (p :: k1) 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
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 2305843009213693951
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 left)>>>hash1 == hash2True
Since: 1.1.0.0
Constructors
| RollingHash | |
Fields 
  | |
Instances
Constructors
new :: forall (b :: Nat) (p :: Nat). (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 :: Nat) (p :: Nat). (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