11{-# LANGUAGE DeriveAnyClass #-}
22{-# LANGUAGE DeriveGeneric #-}
3+ {-# LANGUAGE MagicHash #-}
34{-# LANGUAGE TypeApplications #-}
45
56module Util.Key (Key (.. ), keyToInt , incKey , collisionAtHash ) where
67
78import Data.Bits (bit , (.&.) )
89import Data.Hashable (Hashable (hashWithSalt ))
910import Data.Word (Word16 )
11+ import GHC.Exts (Int (.. ), bitReverse #, int2Word #, word2Int #)
1012import GHC.Generics (Generic )
1113import Test.QuickCheck (Arbitrary (.. ), CoArbitrary (.. ), Function , Gen , Large )
1214
@@ -51,8 +53,8 @@ arbitraryHash = do
5153 , (1 , QC. elements [- 1 , 0xFF , 0xFFF ])
5254 ]
5355 i <- QC. frequency gens
54- moreCollisions' <- QC. elements [moreCollisions, id ]
55- pure (moreCollisions' i)
56+ transform <- QC. elements [id , moreCollisions, bitReverse ]
57+ pure (transform i)
5658
5759-- | Mask out most bits to produce more collisions
5860moreCollisions :: Int -> Int
@@ -62,6 +64,11 @@ moreCollisions w = fromIntegral (w .&. moreCollisionsMask)
6264moreCollisionsMask :: Int
6365moreCollisionsMask = sum [bit n | n <- [0 , 3 , 8 , 14 , 61 ]]
6466
67+ -- | Reverse order of bits, in order to generate variation in the
68+ -- high bits, resulting in HashMap trees of greater height.
69+ bitReverse :: Int -> Int
70+ bitReverse (I # i) = I # (word2Int# (bitReverse# (int2Word# i)))
71+
6572keyToInt :: Key -> Int
6673keyToInt (K h x) = h * fromEnum x
6774
0 commit comments