Skip to content

Commit 19bf8b6

Browse files
committed
Refactor two
* Use the "shifted hash" approach. * Create a variant `two'` that can be used to address #468.
1 parent 4c2f48c commit 19bf8b6

File tree

1 file changed

+17
-7
lines changed

1 file changed

+17
-7
lines changed

Data/HashMap/Internal.hs

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -965,29 +965,39 @@ unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0)
965965
-- because it's already in WHNF (having just been matched) and we
966966
-- just put it directly in an array.
967967
two :: Shift -> Hash -> k -> v -> Hash -> HashMap k v -> ST s (HashMap k v)
968-
two = go
968+
two s h1 k1 v1 = two' s h1 (Leaf h1 (L k1 v1))
969+
{-# INLINE two #-}
970+
971+
two' :: Shift -> Hash -> HashMap k v -> Hash -> HashMap k v -> ST s (HashMap k v)
972+
two' s h1 lc1 h2 lc2 = go (shiftHash h1 s) lc1 (shiftHash h2 s) lc2
969973
where
970-
go s h1 k1 v1 h2 t2
974+
go !sh1 t1 !sh2 t2
971975
| bp1 == bp2 = do
972-
st <- go (nextShift s) h1 k1 v1 h2 t2
976+
st <- go (shiftHash sh1 bitsPerSubkey) t1 (shiftHash sh2 bitsPerSubkey) t2
973977
ary <- A.singletonM st
974978
return $ BitmapIndexed bp1 ary
975979
| otherwise = do
976-
mary <- A.new 2 $! Leaf h1 (L k1 v1)
980+
mary <- A.new 2 t1
977981
A.write mary idx2 t2
978982
ary <- A.unsafeFreeze mary
979983
return $ BitmapIndexed (bp1 .|. bp2) ary
980984
where
981-
!bp1@(W# bp1#) = mask h1 s
982-
!bp2@(W# bp2#) = mask h2 s
985+
!bp1@(W# bp1#) = mask' sh1
986+
!bp2@(W# bp2#) = mask' sh2
983987
idx2 = I# (bp1# `Exts.ltWord#` bp2#)
984988
-- This way of computing idx2 saves us a branch compared to the previous approach:
985989
--
986990
-- idx2 | index h1 s < index h2 s = 1
987991
-- | otherwise = 0
988992
--
989993
-- See https://github.com/haskell-unordered-containers/unordered-containers/issues/75#issuecomment-1128419337
990-
{-# INLINE two #-}
994+
995+
shiftHash :: Hash -> Shift -> Word -- type ShiftedHash
996+
shiftHash h n = h `unsafeShiftR` n
997+
998+
mask' :: Word -> Bitmap
999+
mask' w = 1 `unsafeShiftL` fromIntegral (w .&. subkeyMask)
1000+
{-# INLINE two' #-} -- Really?!
9911001

9921002
-- | \(O(\log n)\) Associate the value with the key in this map. If
9931003
-- this map previously contained a mapping for the key, the old value

0 commit comments

Comments
 (0)