{-# LANGUAGE TypeSynonymInstances #-} ----------------------------------------------------------------------------- -- | -- Module : Hashable -- Copyright : (c) Milan Straka 2010, Grzegorz Chrupala 2010 -- License : BSD3 -- Stability : provisional -- Portability : portable -- -- 'Hashable' class for hashable types, with instances for basic types. The only -- function of this class is -- -- @ -- 'hash' :: (Bits b, Hashable h) => h -> b -- @ -- -- Adapted from Milan Straka's code by Grzegorz Chrupala: -- Removed FFI and C dependency -- Use Bits b instead of hardcoded Int as a result type of 'hash' ----------------------------------------------------------------------------- module Hashable ( Hashable(..) , combine ) where import Data.Bits import Data.Int import Data.Word import Data.List (foldl') import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL import qualified Helper.Text as Text -- | The class containing a function 'hash' which computes the hash values of -- given value. class Hashable a where -- | The computed 'hash' value should be as collision-free as possible, the -- probability of @'hash' a == 'hash' b@ should ideally be 1 over the -- number of representable values in the result type. hash :: Bits b => a -> b -- | Combines two given hash values. combine :: (Bits b) => b -> b -> b combine h1 h2 = (h1 + h1 `shiftL` 5) `xor` h2 hashAndCombine :: (Bits b,Hashable h) => b -> h -> b hashAndCombine acc h = acc `combine` hash h instance Hashable () where hash _ = 0 instance Hashable Bool where hash x = case x of { True -> 1; False -> 0 } instance Hashable Int where hash = fromIntegral instance Hashable Int8 where hash = fromIntegral instance Hashable Int16 where hash = fromIntegral instance Hashable Int32 where hash = fromIntegral instance Hashable Int64 where hash = fromIntegral instance Hashable Word where hash = fromIntegral instance Hashable Word8 where hash = fromIntegral instance Hashable Word16 where hash = fromIntegral instance Hashable Word32 where hash = fromIntegral instance Hashable Word64 where hash = fromIntegral instance Hashable Char where hash = fromIntegral . fromEnum instance Hashable a => Hashable (Maybe a) where hash Nothing = 0 hash (Just a) = 42 `combine` hash a instance (Hashable a1, Hashable a2) => Hashable (a1, a2) where hash (a1, a2) = hash a1 `combine` hash a2 instance (Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) where hash (a1, a2, a3) = hash a1 `combine` hash a2 `combine` hash a3 instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4) where hash (a1, a2, a3, a4) = hash a1 `combine` hash a2 `combine` hash a3 `combine` hash a4 instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5) => Hashable (a1, a2, a3, a4, a5) where hash (a1, a2, a3, a4, a5) = hash a1 `combine` hash a2 `combine` hash a3 `combine` hash a4 `combine` hash a5 instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6) => Hashable (a1, a2, a3, a4, a5, a6) where hash (a1, a2, a3, a4, a5, a6) = hash a1 `combine` hash a2 `combine` hash a3 `combine` hash a4 `combine` hash a5 `combine` hash a6 instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7) => Hashable (a1, a2, a3, a4, a5, a6, a7) where hash (a1, a2, a3, a4, a5, a6, a7) = hash a1 `combine` hash a2 `combine` hash a3 `combine` hash a4 `combine` hash a5 `combine` hash a6 `combine` hash a7 instance Hashable a => Hashable [a] where {-# SPECIALIZE instance Hashable [Char] #-} hash = foldl' hashAndCombine 0 instance Hashable B.ByteString where hash = B.foldl' (\z b -> (z * 33) `xor` fromIntegral b) 0 instance Hashable BL.ByteString where hash = BL.foldl' (\z b -> (z * 33) `xor` fromIntegral b) 0 -- BLInt.foldlChunks hashAndCombine 0 instance Hashable Text.Txt where hash = hash . Text.encodeUtf8