@@ -199,8 +199,10 @@ import Data.Coerce (coerce)
199
199
------------------------------------------------------------------------
200
200
201
201
-- | Convenience function. Compute a hash value for the given value.
202
- hash :: H. Hashable a => Integer -> a -> Hash
203
- hash salt = fromIntegral . H. hashWithSalt (fromIntegral salt)
202
+ hash :: forall a (salt :: Nat ) . H. Hashable a => Proxy salt -> a -> Hash
203
+ hash proxy = fromIntegral . H. hashWithSalt (fromIntegral salt)
204
+ where
205
+ salt = natVal proxy -- TODO ensure is unboxed, ensure is a Word
204
206
205
207
data Leaf k v = L ! k v
206
208
deriving (Eq )
@@ -223,6 +225,9 @@ instance NF.NFData2 Leaf where
223
225
224
226
225
227
#if WORD_SIZE_IN_BITS == 64
228
+ -- TODO figure out the Natural representation
229
+ -- (I think this negative value causes issues because the underlying type is Word)
230
+ -- there is a (golden) test in hashable to ensure we salt by default correctly
226
231
type DefaultSalt = - 2578643520546668380 -- 0xdc36d1615b7400a4
227
232
#else
228
233
type DefaultSalt = 0x087fc72c
@@ -601,9 +606,7 @@ singleton :: (Hashable k) => k -> v -> HashMapT salt k v
601
606
singleton = singleton'
602
607
603
608
singleton' :: forall k v salt . (Hashable k ) => k -> v -> HashMapT salt k v
604
- singleton' k v = Leaf (hash salt k) (L k v)
605
- where
606
- salt = natVal (Proxy :: Proxy salt )
609
+ singleton' k v = Leaf (hash (Proxy :: Proxy salt ) k) (L k v)
607
610
608
611
------------------------------------------------------------------------
609
612
-- * Basic interface
@@ -644,9 +647,7 @@ lookup k m = case lookup# k m of
644
647
{-# INLINE lookup #-}
645
648
646
649
lookup # :: (Eq k , Hashable k ) => k -> HashMapT salt k v -> (# (# # ) | v # )
647
- lookup # k m = lookupCont (\ _ -> (# (# # ) | # )) (\ v _i -> (# | v # )) (hash salt k) k 0 m
648
- where
649
- salt = natVal (Proxy :: Proxy salt )
650
+ lookup # k m = lookupCont (\ _ -> (# (# # ) | # )) (\ v _i -> (# | v # )) (hash (Proxy :: Proxy salt ) k) k 0 m
650
651
{-# INLINABLE lookup# #-}
651
652
652
653
#else
@@ -828,9 +829,7 @@ bitmapIndexedOrFull b ary
828
829
-- key in this map. If this map previously contained a mapping for
829
830
-- the key, the old value is replaced.
830
831
insert :: forall k v salt . (Eq k , Hashable k ) => k -> v -> HashMapT salt k v -> HashMapT salt k v
831
- insert k v m = insert' (hash salt k) k v m
832
- where
833
- salt = natVal (Proxy :: Proxy salt )
832
+ insert k v m = insert' (hash (Proxy :: Proxy salt ) k) k v m
834
833
{-# INLINABLE insert #-}
835
834
836
835
insert' :: forall k v salt . Eq k => Hash -> k -> v -> HashMapT salt k v -> HashMapT salt k v
@@ -961,7 +960,7 @@ setAtPosition i k x ary = A.update ary i (L k x)
961
960
unsafeInsert :: (Eq k ) => k -> v -> HashMapT salt k v -> HashMapT salt k v
962
961
unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0)
963
962
where
964
- h0 = hash k0
963
+ h0 = hash ( Proxy :: Proxy salt ) k0
965
964
go ! h ! k x ! _ Empty = return $! Leaf h (L k x)
966
965
go h k x s t@ (Leaf hy l@ (L ky y))
967
966
| hy == h = if ky == k
@@ -1043,7 +1042,7 @@ insertModifying :: (Eq k, Hashable k) => v -> (v -> (# v #)) -> k -> HashMapT sa
1043
1042
-> HashMapT salt k v
1044
1043
insertModifying x f k0 m0 = go h0 k0 0 m0
1045
1044
where
1046
- ! h0 = hash k0
1045
+ ! h0 = hash ( Proxy :: Proxy salt ) k0
1047
1046
go ! h ! k ! _ Empty = Leaf h (L k x)
1048
1047
go h k s t@ (Leaf hy l@ (L ky y))
1049
1048
| hy == h = if ky == k
@@ -1114,7 +1113,7 @@ unsafeInsertWithKey :: forall k v salt. (Eq k, Hashable k)
1114
1113
-> HashMapT salt k v
1115
1114
unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
1116
1115
where
1117
- h0 = hash k0
1116
+ h0 = hash ( Proxy :: Proxy salt ) k0
1118
1117
go :: Hash -> k -> v -> Shift -> HashMapT salt k v -> ST s (HashMapT salt k v )
1119
1118
go ! h ! k x ! _ Empty = return $! Leaf h (L k x)
1120
1119
go h k x s t@ (Leaf hy l@ (L ky y))
@@ -1147,7 +1146,7 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
1147
1146
-- | /O(log n)/ Remove the mapping for the specified key from this map
1148
1147
-- if present.
1149
1148
delete :: (Eq k , Hashable k ) => k -> HashMapT salt k v -> HashMapT salt k v
1150
- delete k m = delete' (hash k) k m
1149
+ delete k m = delete' (hash ( Proxy :: Proxy salt ) k) k m
1151
1150
{-# INLINABLE delete #-}
1152
1151
1153
1152
delete' :: Eq k => Hash -> k -> HashMapT salt k v -> HashMapT salt k v
@@ -1268,7 +1267,7 @@ adjust f k m = adjust# (\v -> (# f v #)) k m
1268
1267
adjust# :: (Eq k , Hashable k ) => (v -> (# v # )) -> k -> HashMapT salt k v -> HashMapT salt k v
1269
1268
adjust# f k0 m0 = go h0 k0 0 m0
1270
1269
where
1271
- h0 = hash k0
1270
+ h0 = hash ( Proxy :: Proxy salt ) k0
1272
1271
go ! _ ! _ ! _ Empty = Empty
1273
1272
go h k _ t@ (Leaf hy (L ky y))
1274
1273
| hy == h && ky == k = case f y of
@@ -1343,7 +1342,7 @@ alterF :: (Functor f, Eq k, Hashable k)
1343
1342
-- @f@ and a functor that is similar to Const but not actually Const.
1344
1343
alterF f = \ ! k ! m ->
1345
1344
let
1346
- ! h = hash k
1345
+ ! h = hash ( Proxy :: Proxy salt ) k
1347
1346
mv = lookup' h k m
1348
1347
in (<$> f mv) $ \ fres ->
1349
1348
case fres of
0 commit comments