#ifdef GENERICS
#endif
module Data.Hashable.Class
(
Hashable(hashWithSalt)
#ifdef GENERICS
, GHashable(..)
#endif
, hash
, hashUsing
, hashPtr
, hashPtrWithSalt
#if defined(__GLASGOW_HASKELL__)
, hashByteArray
, hashByteArrayWithSalt
#endif
) where
import Control.Exception (assert)
import Data.Bits (shiftL, 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 TL
# ifdef GENERICS
import GHC.Generics
# endif
#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(..))
# else
import Data.Bits (shiftR)
# 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
#ifndef FIXED_SALT
import Control.Exception (tryJust)
import Control.Monad (guard)
import Data.Hashable.RandomSource (getRandomBytes_)
import Foreign.Marshal.Alloc (alloca)
import System.Environment (getEnv)
import System.IO.Error (isDoesNotExistError)
#endif
#include "MachDeps.h"
infixl 0 `hashWithSalt`
defaultSalt, fixedSalt :: Int
fixedSalt = 0xdc36d1615b7400a4
#ifdef FIXED_SALT
defaultSalt = fixedSalt
#else
defaultSalt = unsafePerformIO $ do
let varName = "HASHABLE_SALT"
msalt <- tryJust (guard . isDoesNotExistError) $ getEnv varName
case msalt of
Right "random" -> alloca $ \p -> do
getRandomBytes_ "defaultSalt" p (sizeOf (undefined :: Int))
peek p
Right s -> case reads s of
[(salt, "")] -> return salt
_ -> fail $ "Fatal: cannot parse contents of " ++
varName ++ " environment variable"
Left _ -> return fixedSalt
#endif
class Hashable a where
hashWithSalt :: Int -> a -> Int
hashListWithSalt :: Int -> [a] -> Int
hashListWithSalt = foldl' hashWithSalt
#ifdef GENERICS
default hashWithSalt :: (Generic a, GHashable (Rep a)) => Int -> a -> Int
hashWithSalt salt = ghashWithSalt salt . from
class GHashable f where
ghashWithSalt :: Int -> f a -> Int
#endif
hash :: Hashable a => a -> Int
hash = hashWithSalt defaultSalt
hashUsing :: (Hashable b) =>
(a -> b)
-> Int
-> a
-> Int
hashUsing f salt x = hashWithSalt salt (f x)
instance Hashable Int where hashWithSalt = hashNative
instance Hashable Int16 where hashWithSalt = hashNative
instance Hashable Int32 where hashWithSalt = hashNative
instance Hashable Int64 where hashWithSalt = hash64
instance Hashable Word where hashWithSalt = hashNative
instance Hashable Word16 where hashWithSalt = hashNative
instance Hashable Word32 where hashWithSalt = hashNative
instance Hashable Word64 where hashWithSalt = hash64
instance Hashable () where hashWithSalt = hashUsing fromEnum
instance Hashable Bool where hashWithSalt = hashUsing fromEnum
instance Hashable Ordering where hashWithSalt = hashUsing fromEnum
instance Hashable Int8 where
hashWithSalt = hashNative
hashListWithSalt salt = hashUsing B.pack salt . map fromIntegral
instance Hashable Word8 where
hashWithSalt = hashNative
hashListWithSalt = hashUsing B.pack
instance Hashable Char where
hashWithSalt = hashUsing fromEnum
hashListWithSalt = hashUsing T.pack
hashNative :: (Integral a) => Int -> a -> Int
hashNative salt = fromIntegral . go . xor (fromIntegral salt) . fromIntegral
where
#if WORD_SIZE_IN_BITS == 32
go :: Word32 -> Word32
#else
go :: Word64 -> Word64
#endif
go = id
hash64 :: (Integral a) => Int -> a -> Int
hash64 salt = fromIntegral . go . xor (fromIntegral salt) . fromIntegral
where
go :: Word64 -> Word64
go = id
instance Hashable Integer where
#if defined(__GLASGOW_HASKELL__) && defined(VERSION_integer_gmp)
hashWithSalt salt (S# int) = hashWithSalt salt (I# int)
hashWithSalt salt n@(J# size# byteArray)
| n >= minInt && n <= maxInt = hashWithSalt salt (fromInteger n :: Int)
| otherwise = let size = I# size#
numBytes = SIZEOF_HSWORD * abs size
in hashByteArrayWithSalt byteArray 0 numBytes salt
`hashWithSalt` size
where minInt = fromIntegral (minBound :: Int)
maxInt = fromIntegral (maxBound :: Int)
#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
hashWithSalt s a = s `hashWithSalt` numerator a `hashWithSalt` denominator a
instance Hashable Float where
hashWithSalt salt x
| isIEEE x =
assert (sizeOf x >= sizeOf (0::Word32) &&
alignment x >= alignment (0::Word32)) $
hashWithSalt salt
((unsafePerformIO $ with x $ peek . castPtr) :: Word32)
| otherwise = hashWithSalt salt (show x)
instance Hashable Double where
hashWithSalt salt x
| isIEEE x =
assert (sizeOf x >= sizeOf (0::Word64) &&
alignment x >= alignment (0::Word64)) $
hashWithSalt salt
((unsafePerformIO $ with x $ peek . castPtr) :: Word64)
| otherwise = hashWithSalt salt (show x)
distinguisher :: Int
distinguisher = fromIntegral $ (maxBound :: Word) `quot` 3
instance Hashable a => Hashable (Maybe a) where
hashWithSalt s Nothing = hashWithSalt s (0::Int)
hashWithSalt s (Just a) = hashWithSalt s a `hashWithSalt` distinguisher
instance (Hashable a, Hashable b) => Hashable (Either a b) where
hashWithSalt s (Left a) = hashWithSalt s a
hashWithSalt s (Right b) = hashWithSalt s b `hashWithSalt` distinguisher
instance (Hashable a1, Hashable a2) => Hashable (a1, a2) where
hashWithSalt s (a1, a2) = s `hashWithSalt` a1 `hashWithSalt` a2
instance (Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3) where
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
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
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
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
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
hashWithSalt = hashUsing hashStableName
#endif
instance Hashable a => Hashable [a] where
hashWithSalt = hashListWithSalt
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 = BL.foldlChunks hashWithSalt
#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 TL.Text where
hashWithSalt = TL.foldlChunks hashWithSalt
#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
hashWithSalt = hashUsing hashThreadId
hashTypeRep :: Int -> TypeRep -> Int
#if __GLASGOW_HASKELL__ >= 702
hashTypeRep salt (TypeRep (Fingerprint x _) _ _) = hashWithSalt salt x
#elif __GLASGOW_HASKELL__ >= 606
hashTypeRep = hashUsing (B.inlinePerformIO . typeRepKey)
#else
hashTypeRep = hashUsing show
#endif
instance Hashable TypeRep where
hashWithSalt = 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 !h =
fromIntegral $ c_hashByteArray ba (fromIntegral off) (fromIntegral len)
(fromIntegral h)
foreign import ccall unsafe "hashable_fnv_hash_offset" c_hashByteArray
:: ByteArray# -> CLong -> CLong -> CLong -> CLong
#endif