module Data.Hashable
(
Hashable(..)
, hashPtr
, hashPtrWithSalt
#if defined(__GLASGOW_HASKELL__)
, hashByteArray
, hashByteArrayWithSalt
#endif
, combine
) where
import Control.Exception (assert)
import Data.Bits (bitSize, shiftL, shiftR, xor)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Word (Word, Word8, Word16, Word32, Word64)
import Data.List (foldl')
import Data.Ratio (Ratio, denominator, numerator)
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as B
import qualified Data.ByteString.Unsafe as B
import qualified Data.ByteString.Lazy as BL
#if !MIN_VERSION_bytestring(0,10,0)
import qualified Data.ByteString.Lazy.Internal as BL
#endif
#if defined(__GLASGOW_HASKELL__)
import qualified Data.Text as T
import qualified Data.Text.Array as TA
import qualified Data.Text.Internal as T
import qualified Data.Text.Lazy as LT
#endif
import Foreign.C (CString)
#if __GLASGOW_HASKELL__ >= 703
import Foreign.C (CLong(..))
#else
import Foreign.C (CLong)
#endif
import Foreign.Marshal.Utils (with)
import Foreign.Ptr (Ptr, castPtr)
import Foreign.Storable (alignment, peek, sizeOf)
import System.IO.Unsafe (unsafePerformIO)
#if defined(__GLASGOW_HASKELL__)
import GHC.Base (ByteArray#)
# ifdef VERSION_integer_gmp
import GHC.Exts (Int(..))
import GHC.Integer.GMP.Internals (Integer(..))
# endif
#endif
#if defined(__GLASGOW_HASKELL__)
import GHC.Conc (ThreadId(..))
import GHC.Prim (ThreadId#)
# if __GLASGOW_HASKELL__ >= 703
import Foreign.C.Types (CInt(..))
# else
import Foreign.C.Types (CInt)
# endif
#else
import Control.Concurrent (ThreadId)
#endif
#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
import System.Mem.StableName
#endif
import Data.Typeable
#if __GLASGOW_HASKELL__ >= 702
import GHC.Fingerprint.Type(Fingerprint(..))
import Data.Typeable.Internal(TypeRep(..))
#endif
#include "MachDeps.h"
infixl 0 `combine`, `hashWithSalt`
defaultSalt :: Int
defaultSalt = 2166136261
class Hashable a where
hash :: a -> Int
hash = hashWithSalt defaultSalt
hashWithSalt :: Int -> a -> Int
hashWithSalt salt x = salt `combine` hash x
instance Hashable () where hash _ = 0
instance Hashable Bool where hash x = case x of { True -> 1; False -> 0 }
instance Hashable Int where hash = id
instance Hashable Int8 where hash = fromIntegral
instance Hashable Int16 where hash = fromIntegral
instance Hashable Int32 where hash = fromIntegral
instance Hashable Int64 where
hash n
| bitSize (undefined :: Int) == 64 = fromIntegral n
| otherwise = fromIntegral (fromIntegral n `xor`
(fromIntegral n `shiftR` 32 :: Word64))
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 n
| bitSize (undefined :: Int) == 64 = fromIntegral n
| otherwise = fromIntegral (n `xor` (n `shiftR` 32))
instance Hashable Integer where
#if defined(__GLASGOW_HASKELL__) && defined(VERSION_integer_gmp)
hash (S# int) = I# int
hash n@(J# size byteArray) | n >= fromIntegral (minBound :: Int) && n <= fromIntegral (maxBound :: Int) = fromInteger n
| otherwise = hashByteArrayWithSalt byteArray 0 (SIZEOF_HSWORD * (I# size)) 0
hashWithSalt salt (S# int) = salt `combine` I# int
hashWithSalt salt n@(J# size byteArray) | n >= fromIntegral (minBound :: Int) && n <= fromIntegral (maxBound :: Int) = salt `combine` fromInteger n
| otherwise = hashByteArrayWithSalt byteArray 0 (SIZEOF_HSWORD * (I# size)) salt
#else
hashWithSalt salt = foldl' hashWithSalt salt . go
where
go n | inBounds n = [fromIntegral n :: Int]
| otherwise = fromIntegral n : go (n `shiftR` WORD_SIZE_IN_BITS)
maxInt = fromIntegral (maxBound :: Int)
inBounds x = x >= fromIntegral (minBound :: Int) && x <= maxInt
#endif
instance (Integral a, Hashable a) => Hashable (Ratio a) where
hash a = hash (numerator a) `hashWithSalt` denominator a
hashWithSalt s a = s `hashWithSalt` numerator a `hashWithSalt` denominator a
instance Hashable Float where
hash x
| isIEEE x =
assert (sizeOf x >= sizeOf (0::Word32) &&
alignment x >= alignment (0::Word32)) $
hash ((unsafePerformIO $ with x $ peek . castPtr) :: Word32)
| otherwise = hash (show x)
instance Hashable Double where
hash x
| isIEEE x =
assert (sizeOf x >= sizeOf (0::Word64) &&
alignment x >= alignment (0::Word64)) $
hash ((unsafePerformIO $ with x $ peek . castPtr) :: Word64)
| otherwise = hash (show x)
instance Hashable Char where hash = fromEnum
distinguisher :: Int
distinguisher = fromIntegral $ (maxBound :: Word) `quot` 3
instance Hashable a => Hashable (Maybe a) where
hash Nothing = 0
hash (Just a) = distinguisher `hashWithSalt` a
hashWithSalt s Nothing = s `combine` 0
hashWithSalt s (Just a) = s `combine` distinguisher `hashWithSalt` a
instance (Hashable a, Hashable b) => Hashable (Either a b) where
hash (Left a) = 0 `hashWithSalt` a
hash (Right b) = distinguisher `hashWithSalt` b
hashWithSalt s (Left a) = s `combine` 0 `hashWithSalt` a
hashWithSalt s (Right b) = s `combine` distinguisher `hashWithSalt` b
instance (Hashable a1, Hashable a2) => Hashable (a1, a2) where
hash (a1, a2) = hash a1 `hashWithSalt` a2
hashWithSalt s (a1, a2) = s `hashWithSalt` a1 `hashWithSalt` a2
instance (Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) where
hash (a1, a2, a3) = hash a1 `hashWithSalt` a2 `hashWithSalt` a3
hashWithSalt s (a1, a2, a3) = s `hashWithSalt` a1 `hashWithSalt` a2
`hashWithSalt` a3
instance (Hashable a1, Hashable a2, Hashable a3, Hashable a4) =>
Hashable (a1, a2, a3, a4) where
hash (a1, a2, a3, a4) = hash a1 `hashWithSalt` a2
`hashWithSalt` a3 `hashWithSalt` a4
hashWithSalt s (a1, a2, a3, a4) = s `hashWithSalt` a1 `hashWithSalt` a2
`hashWithSalt` a3 `hashWithSalt` 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 `hashWithSalt` a2 `hashWithSalt` a3
`hashWithSalt` a4 `hashWithSalt` a5
hashWithSalt s (a1, a2, a3, a4, a5) =
s `hashWithSalt` a1 `hashWithSalt` a2 `hashWithSalt` a3
`hashWithSalt` a4 `hashWithSalt` 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 `hashWithSalt` a2 `hashWithSalt` a3
`hashWithSalt` a4 `hashWithSalt` a5 `hashWithSalt` a6
hashWithSalt s (a1, a2, a3, a4, a5, a6) =
s `hashWithSalt` a1 `hashWithSalt` a2 `hashWithSalt` a3
`hashWithSalt` a4 `hashWithSalt` a5 `hashWithSalt` 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 `hashWithSalt` a2 `hashWithSalt` a3
`hashWithSalt` a4 `hashWithSalt` a5 `hashWithSalt` a6 `hashWithSalt` a7
hashWithSalt s (a1, a2, a3, a4, a5, a6, a7) =
s `hashWithSalt` a1 `hashWithSalt` a2 `hashWithSalt` a3
`hashWithSalt` a4 `hashWithSalt` a5 `hashWithSalt` a6 `hashWithSalt` a7
#if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
instance Hashable (StableName a) where
hash = hashStableName
#endif
instance Hashable a => Hashable [a] where
hashWithSalt = foldl' hashWithSalt
instance Hashable B.ByteString where
hashWithSalt salt bs = B.inlinePerformIO $
B.unsafeUseAsCStringLen bs $ \(p, len) ->
hashPtrWithSalt p (fromIntegral len) salt
instance Hashable BL.ByteString where
hashWithSalt salt = BL.foldlChunks hashWithSalt salt
#if defined(__GLASGOW_HASKELL__)
instance Hashable T.Text where
hashWithSalt salt (T.Text arr off len) =
hashByteArrayWithSalt (TA.aBA arr) (off `shiftL` 1) (len `shiftL` 1)
salt
instance Hashable LT.Text where
hashWithSalt salt = LT.foldlChunks hashWithSalt salt
#endif
hashThreadId :: ThreadId -> Int
#if defined(__GLASGOW_HASKELL__)
hashThreadId (ThreadId t) = hash (fromIntegral (getThreadId t) :: Int)
foreign import ccall unsafe "rts_getThreadId" getThreadId :: ThreadId# -> CInt
#else
hashThreadId = hash . show
#endif
instance Hashable ThreadId where
hash = hashThreadId
hashTypeRep :: TypeRep -> Int
#if __GLASGOW_HASKELL__ >= 702
hashTypeRep (TypeRep (Fingerprint x _) _ _) = fromIntegral x
#elif __GLASGOW_HASKELL__ >= 606
hashTypeRep = B.inlinePerformIO . typeRepKey
#else
hashTypeRep = hash . show
#endif
instance Hashable TypeRep where
hash = hashTypeRep
hashPtr :: Ptr a
-> Int
-> IO Int
hashPtr p len = hashPtrWithSalt p len defaultSalt
hashPtrWithSalt :: Ptr a
-> Int
-> Int
-> IO Int
hashPtrWithSalt p len salt =
fromIntegral `fmap` c_hashCString (castPtr p) (fromIntegral len)
(fromIntegral salt)
foreign import ccall unsafe "hashable_fnv_hash" c_hashCString
:: CString -> CLong -> CLong -> IO CLong
#if defined(__GLASGOW_HASKELL__)
hashByteArray :: ByteArray#
-> Int
-> Int
-> Int
hashByteArray ba0 off len = hashByteArrayWithSalt ba0 off len defaultSalt
hashByteArrayWithSalt
:: ByteArray#
-> Int
-> Int
-> Int
-> Int
hashByteArrayWithSalt ba !off !len !h0 =
fromIntegral $ c_hashByteArray ba (fromIntegral off) (fromIntegral len)
(fromIntegral h0)
foreign import ccall unsafe "hashable_fnv_hash_offset" c_hashByteArray
:: ByteArray# -> CLong -> CLong -> CLong -> CLong
#endif
combine :: Int -> Int -> Int
combine h1 h2 = (h1 * 16777619) `xor` h2