@@ -884,33 +884,19 @@ insertKeyExists !collPos0 !h0 !k0 x0 !m0 = go collPos0 h0 k0 x0 m0
884884 = Leaf h (L k x)
885885 go collPos shiftedHash k x (BitmapIndexed b ary) =
886886 let ! st = A. index ary i
887- ! st' = go collPos (shiftHash shiftedHash) k x st
887+ ! st' = go collPos (nextSH shiftedHash) k x st
888888 in BitmapIndexed b (A. update ary i st')
889- where m = mask' shiftedHash
889+ where m = maskSH shiftedHash
890890 i = sparseIndex b m
891891 go collPos shiftedHash k x (Full ary) =
892892 let ! st = A. index ary i
893- ! st' = go collPos (shiftHash shiftedHash) k x st
893+ ! st' = go collPos (nextSH shiftedHash) k x st
894894 in Full (updateFullArray ary i st')
895- where i = index' shiftedHash
895+ where i = indexSH shiftedHash
896896 go collPos _shiftedHash k x (Collision h v)
897897 | collPos >= 0 = Collision h (setAtPosition collPos k x v)
898898 | otherwise = Empty -- error "Internal error: go {collPos negative}"
899899 go _ _ _ _ Empty = Empty -- error "Internal error: go Empty"
900-
901- -- Customized version of 'index' that doesn't require a 'Shift'.
902- index' :: Hash -> Int
903- index' w = fromIntegral $ w .&. subkeyMask
904- {-# INLINE index' #-}
905-
906- -- Customized version of 'mask' that doesn't require a 'Shift'.
907- mask' :: Word -> Bitmap
908- mask' w = 1 `unsafeShiftL` index' w
909- {-# INLINE mask' #-}
910-
911- shiftHash h = h `unsafeShiftR` bitsPerSubkey
912- {-# INLINE shiftHash #-}
913-
914900{-# NOINLINE insertKeyExists #-}
915901
916902-- | Replace the ith Leaf with Leaf k v.
@@ -1178,11 +1164,11 @@ delete' h0 k0 m0 = go h0 k0 0 m0
11781164deleteKeyExists :: Int -> Hash -> k -> HashMap k v -> HashMap k v
11791165deleteKeyExists ! collPos0 ! h0 ! k0 ! m0 = go collPos0 h0 k0 m0
11801166 where
1181- go :: Int -> Word -> k -> HashMap k v -> HashMap k v
1167+ go :: Int -> ShiftedHash -> k -> HashMap k v -> HashMap k v
11821168 go ! _collPos ! _shiftedHash ! _k (Leaf _ _) = Empty
11831169 go collPos shiftedHash k (BitmapIndexed b ary) =
11841170 let ! st = A. index ary i
1185- ! st' = go collPos (shiftHash shiftedHash) k st
1171+ ! st' = go collPos (nextSH shiftedHash) k st
11861172 in case st' of
11871173 Empty | A. length ary == 1 -> Empty
11881174 | A. length ary == 2 ->
@@ -1195,39 +1181,25 @@ deleteKeyExists !collPos0 !h0 !k0 !m0 = go collPos0 h0 k0 m0
11951181 bIndexed = BitmapIndexed (b .&. complement m) (A. delete ary i)
11961182 l | isLeafOrCollision l && A. length ary == 1 -> l
11971183 _ -> BitmapIndexed b (A. update ary i st')
1198- where m = mask' shiftedHash
1184+ where m = maskSH shiftedHash
11991185 i = sparseIndex b m
12001186 go collPos shiftedHash k (Full ary) =
12011187 let ! st = A. index ary i
1202- ! st' = go collPos (shiftHash shiftedHash) k st
1188+ ! st' = go collPos (nextSH shiftedHash) k st
12031189 in case st' of
12041190 Empty ->
12051191 let ary' = A. delete ary i
12061192 bm = fullBitmap .&. complement (1 `unsafeShiftL` i)
12071193 in BitmapIndexed bm ary'
12081194 _ -> Full (A. update ary i st')
1209- where i = index' shiftedHash
1195+ where i = indexSH shiftedHash
12101196 go collPos _shiftedHash _k (Collision h v)
12111197 | A. length v == 2
12121198 = if collPos == 0
12131199 then Leaf h (A. index v 1 )
12141200 else Leaf h (A. index v 0 )
12151201 | otherwise = Collision h (A. delete v collPos)
12161202 go ! _ ! _ ! _ Empty = Empty -- error "Internal error: deleteKeyExists empty"
1217-
1218- -- Customized version of 'index' that doesn't require a 'Shift'.
1219- index' :: Hash -> Int
1220- index' w = fromIntegral $ w .&. subkeyMask
1221- {-# INLINE index' #-}
1222-
1223- -- Customized version of 'mask' that doesn't require a 'Shift'.
1224- mask' :: Word -> Bitmap
1225- mask' w = 1 `unsafeShiftL` index' w
1226- {-# INLINE mask' #-}
1227-
1228- shiftHash h = h `unsafeShiftR` bitsPerSubkey
1229- {-# INLINE shiftHash #-}
1230-
12311203{-# NOINLINE deleteKeyExists #-}
12321204
12331205-- | \(O(\log n)\) Adjust the value tied to a given key in this map only
@@ -2510,6 +2482,35 @@ nextShift :: Shift -> Shift
25102482nextShift s = s + bitsPerSubkey
25112483{-# INLINE nextShift #-}
25122484
2485+ ------------------------------------------------------------------------
2486+ -- ShiftedHash
2487+
2488+ -- | Sometimes it's more efficient to right-shift the hashes directly instead
2489+ -- of keeping track of an additional 'Shift' value.
2490+ type ShiftedHash = Hash
2491+
2492+ {-
2493+ -- | Construct a 'ShiftedHash' from a 'Shift' and a 'Hash'.
2494+ shiftHash :: Shift -> Hash -> ShiftedHash
2495+ shiftHash s h = h `unsafeShiftR` s
2496+ {- # INLINE shiftHash #-}
2497+ -}
2498+
2499+ -- | Update a 'ShiftedHash' for the next level of the tree.
2500+ nextSH :: ShiftedHash -> ShiftedHash
2501+ nextSH sh = sh `unsafeShiftR` bitsPerSubkey
2502+ {-# INLINE nextSH #-}
2503+
2504+ -- | Version of 'index' for use with @'ShiftedHash'es@.
2505+ indexSH :: ShiftedHash -> Int
2506+ indexSH sh = fromIntegral $ sh .&. subkeyMask
2507+ {-# INLINE indexSH #-}
2508+
2509+ -- | Version of 'mask' for use with @'ShiftedHash'es@.
2510+ maskSH :: ShiftedHash -> Bitmap
2511+ maskSH sh = 1 `unsafeShiftL` indexSH sh
2512+ {-# INLINE maskSH #-}
2513+
25132514------------------------------------------------------------------------
25142515-- Pointer equality
25152516
0 commit comments