module Data.Hash.Rolling (
RollingHash,
rollingHash, addAndRoll,
currentHash, lastHashes, windowSize
)
where
import Data.Hash.Base
import Data.Hash.Instances
import Data.Bits
import qualified Data.Sequence as S
import Data.Foldable
import Text.Show.Functions ()
data RollingHash a = RH {
currentHash :: Hash
,windowSize :: Int
,hseq :: S.Seq Hash
,addHashImpl :: RollingHash a -> Hash -> RollingHash a
} deriving Show
rollingHash :: Int -> RollingHash a
rollingHash n
| n == 0 = error $ "rollingHash: invalid window size " ++ show n
| otherwise = RH {
currentHash = initial_hash
,windowSize = n
,hseq = S.singleton initial_hash
,addHashImpl = accumulateNext (n 1)
}
where initial_hash = hash () `combine` hash n
defaultAddHash :: RollingHash a -> Hash -> RollingHash a
defaultAddHash rh hv = rh { currentHash = (currentHash rh) `combine` (Hash $ rotate c1 k `xor` ck)
, hseq = (S.drop 1 $ hseq rh) S.|> hv
}
where ck = asWord64 hv
c1 = asWord64 $ S.index (hseq rh) 0
k = S.length $ hseq rh
addAndRoll :: Hashable a => RollingHash a -> a -> RollingHash a
addAndRoll r a = (addHashImpl r) r (hash a)
accumulateNext :: Int -> RollingHash a -> Hash -> RollingHash a
accumulateNext n | n > 0 = \rh h -> rh {
currentHash = currentHash rh `combine` h,
hseq = (hseq rh) S.|> h,
addHashImpl = accumulateNext (n 1)
}
| otherwise = defaultAddHash
lastHashes :: RollingHash a -> [Hash]
lastHashes = toList . hseq