{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Array.Accelerate.Data.Hashable (
Hashable(..),
hashUsing, defaultHashWithSalt,
) where
import Data.Array.Accelerate
import Data.Array.Accelerate.Data.Bits
import Data.Array.Accelerate.Data.Complex
import Data.Array.Accelerate.Data.Either
import Data.Array.Accelerate.Data.Maybe
import Data.Array.Accelerate.Data.Monoid
import Data.Array.Accelerate.Data.Ratio
import Data.Array.Accelerate.Data.Semigroup
import Prelude ( (<$>), id, concat )
import Control.Monad ( mapM )
import Language.Haskell.TH hiding ( Exp, match )
import qualified Prelude as P
import qualified Data.Bits as P
import qualified Data.List as P
#include "MachDeps.h"
infixl 0 `hashWithSalt`
class Elt a => Hashable a where
hashWithSalt :: Exp Int -> Exp a -> Exp Int
hash :: Exp a -> Exp Int
hash = hashWithSalt defaultSalt
hashUsing
:: Hashable b
=> (Exp a -> Exp b)
-> Exp Int
-> Exp a
-> Exp Int
hashUsing f salt x = hashWithSalt salt (f x)
defaultSalt :: Exp Int
#if WORD_SIZE_IN_BITS == 64
defaultSalt = -2578643520546668380
#else
defaultSalt = 0x087fc72c
#endif
defaultHashWithSalt :: Hashable a => Exp Int -> Exp a -> Exp Int
defaultHashWithSalt salt x = salt `combine` hash x
combine :: Exp Int -> Exp Int -> Exp Int
combine h1 h2 = (h1 * 16777619) `xor` h2
instance Hashable Int where
hash = id
hashWithSalt = defaultHashWithSalt
instance Hashable Int8 where
hash = fromIntegral
hashWithSalt = defaultHashWithSalt
instance Hashable Int16 where
hash = fromIntegral
hashWithSalt = defaultHashWithSalt
instance Hashable Int32 where
hash = fromIntegral
hashWithSalt = defaultHashWithSalt
instance Hashable Int64 where
hash x
| P.finiteBitSize (undefined :: Int) P.== 64 = fromIntegral x
| otherwise = fromIntegral (fromIntegral x `xor`
(fromIntegral x `shiftR` 32 :: Exp Word64))
hashWithSalt = defaultHashWithSalt
instance Hashable Word where
hash = fromIntegral
hashWithSalt = defaultHashWithSalt
instance Hashable Word8 where
hash = fromIntegral
hashWithSalt = defaultHashWithSalt
instance Hashable Word16 where
hash = fromIntegral
hashWithSalt = defaultHashWithSalt
instance Hashable Word32 where
hash = fromIntegral
hashWithSalt = defaultHashWithSalt
instance Hashable Word64 where
hash x
| P.finiteBitSize (undefined :: Int) P.== 64 = fromIntegral x
| otherwise = fromIntegral (x `xor` (x `shiftR` 32))
hashWithSalt = defaultHashWithSalt
instance Hashable () where
hash _ = constant (P.fromEnum ())
hashWithSalt = defaultHashWithSalt
instance Hashable Bool where
hash = boolToInt
hashWithSalt = defaultHashWithSalt
instance Hashable Char where
hash = ord
hashWithSalt = defaultHashWithSalt
instance Hashable Half where
hash x =
if x == 0.0 || x == -0.0
then 0
else hash (bitcast x :: Exp Word16)
hashWithSalt = defaultHashWithSalt
instance Hashable Float where
hash x =
if x == 0.0 || x == -0.0
then 0
else hash (bitcast x :: Exp Word32)
hashWithSalt = defaultHashWithSalt
instance Hashable Double where
hash x =
if x == 0.0 || x == -0.0
then 0
else hash (bitcast x :: Exp Word64)
hashWithSalt = defaultHashWithSalt
instance Hashable a => Hashable (Complex a) where
hash (r ::+ i) = hash r `hashWithSalt` i
hashWithSalt s (r ::+ i) = s `hashWithSalt` r `hashWithSalt` i
instance Hashable a => Hashable (Ratio a) where
hash a = hash (numerator a) `hashWithSalt` denominator a
hashWithSalt s a = s `hashWithSalt` numerator a `hashWithSalt` denominator a
distinguisher :: Exp Int
distinguisher = fromIntegral $ (maxBound :: Exp Word) `quot` 3
instance Hashable a => Hashable (Maybe a) where
hash = match \case
Nothing_ -> 0
Just_ x -> distinguisher `hashWithSalt` x
hashWithSalt = defaultHashWithSalt
instance (Hashable a, Hashable b) => Hashable (Either a b) where
hash = match \case
Left_ x -> 0 `hashWithSalt` x
Right_ x -> distinguisher `hashWithSalt` x
hashWithSalt = defaultHashWithSalt
instance Hashable a => Hashable (Min a) where
hashWithSalt s (Min_ a) = hashWithSalt s a
instance Hashable a => Hashable (Max a) where
hashWithSalt s (Max_ a) = hashWithSalt s a
instance Hashable a => Hashable (Sum a) where
hashWithSalt s (Sum_ a) = hashWithSalt s a
instance Hashable a => Hashable (Product a) where
hashWithSalt s (Product_ a) = hashWithSalt s a
$(runQ $
let
tupT :: [TypeQ] -> TypeQ
tupT tup =
let n = P.length tup
in P.foldl' (\ts t -> [t| $ts $t |]) (tupleT n) tup
mkTup :: Int -> Q [Dec]
mkTup n =
let
xs = [ mkName ('x':P.show i) | i <- [0 .. n-1] ]
ctx = tupT (P.map (\x -> [t| Hashable $(varT x) |]) xs)
res = tupT (P.map varT xs)
pat = conP (mkName ('T':P.show n)) (P.map varP xs)
in
[d| instance $ctx => Hashable $res where
hash $pat = $(P.foldl' (\vs v -> [| $vs `hashWithSalt` $v |]) [| hash $(varE (P.head xs))|] (P.map varE (P.tail xs)))
hashWithSalt = defaultHashWithSalt
|]
in
concat <$> mapM mkTup [2..16]
)