{-# OPTIONS_HADDOCK prune #-} -- | Implements the specialized hash function for -- this perfect hashing algorithm. module Data.PerfectHash.Hashing where import Data.Bits (xor, (.&.)) import Data.Char (ord) -- | This choice of prime number was taken from the Python implementation -- on . primeFNV = 0x01000193 mask32bits = 0xffffffff -- | A Foldable of any data type may be hashed, so long as it implements -- an instance of this class. class ToNumeric a where toNum :: a -> Int -- | The numeric value of a character is simply its ordinal value. instance ToNumeric Char where toNum = ord instance ToNumeric Int where toNum = id hashToSlot :: (Foldable f, ToNumeric a) => Int -- ^ nonce -> f a -- ^ key -> Int -- ^ array size -> Int hashToSlot nonce key size = hash nonce key `mod` size -- | Uses the \"FNV-1a\" algorithm from the -- : -- -- > hash = offset_basis -- > for each octet_of_data to be hashed -- > hash = hash xor octet_of_data -- > hash = hash * FNV_prime -- > return hash -- -- The interface is comparable to the -- -- function from the @hashable@ package. hash :: (Foldable f, ToNumeric a) => Int -> f a -> Int hash nonce = foldl combine d -- NOTE: This must be 'foldl', not 'foldr' where d = if nonce == 0 then primeFNV else nonce combine acc = (.&. mask32bits) . (* primeFNV) . xor acc . toNum