Skip to content

Commit e7fa67b

Browse files
committed
Speed up difference and differenceWith
Context: #364
1 parent 1029038 commit e7fa67b

File tree

1 file changed

+69
-7
lines changed

1 file changed

+69
-7
lines changed

Data/HashMap/Internal.hs

Lines changed: 69 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -920,6 +920,34 @@ setAtPosition :: Int -> k -> v -> A.Array (Leaf k v) -> A.Array (Leaf k v)
920920
setAtPosition i k x ary = A.update ary i (L k x)
921921
{-# INLINE setAtPosition #-}
922922

923+
unsafeInsertNewLeaf :: Hash -> HashMap k v -> HashMap k v -> HashMap k v
924+
unsafeInsertNewLeaf h0 l0 m0 = runST (go h0 l0 0 m0)
925+
where
926+
go !_ !l !_ Empty = return l
927+
go h l@(Leaf _ lx) s t@(Leaf hy ly)
928+
| hy == h = return $! collision h lx ly
929+
| otherwise = two' s h l hy t
930+
go h l s t@(BitmapIndexed b ary)
931+
| b .&. m == 0 = do
932+
ary' <- A.insertM ary i l
933+
return $! bitmapIndexedOrFull (b .|. m) ary'
934+
| otherwise = do
935+
st <- A.indexM ary i
936+
st' <- go h l (nextShift s) st
937+
A.unsafeUpdateM ary i st'
938+
return t
939+
where m = mask h s
940+
i = sparseIndex b m
941+
go h l s t@(Full ary) = do
942+
st <- A.indexM ary i
943+
st' <- go h l (nextShift s) st
944+
A.unsafeUpdateM ary i st'
945+
return t
946+
where i = index h s
947+
go h l@(Leaf _ lx) s t@(Collision hy v)
948+
| h == hy = return $! Collision h (A.snoc v lx)
949+
| otherwise = go h l s $ BitmapIndexed (mask hy s) (A.singleton t)
950+
go _ _ _ _ = error "unsafeInsertNewLeaf"
923951

924952
-- | In-place update version of insert
925953
unsafeInsert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v
@@ -991,6 +1019,27 @@ two = go
9911019
-- See https://github.com/haskell-unordered-containers/unordered-containers/issues/75#issuecomment-1128419337
9921020
{-# INLINE two #-}
9931021

1022+
two' :: Shift -> Hash -> HashMap k v -> Hash -> HashMap k v -> ST s (HashMap k v)
1023+
two' = go
1024+
where
1025+
go s h1 t1 h2 t2
1026+
| bp1 == bp2 = do
1027+
st <- go (nextShift s) h1 t1 h2 t2
1028+
ary <- A.singletonM st
1029+
return $ BitmapIndexed bp1 ary
1030+
| otherwise = do
1031+
mary <- A.new 2 t1
1032+
A.write mary idx2 t2
1033+
ary <- A.unsafeFreeze mary
1034+
return $ BitmapIndexed (bp1 .|. bp2) ary
1035+
where
1036+
bp1 = mask h1 s
1037+
bp2 = mask h2 s
1038+
!(I# i1) = index h1 s
1039+
!(I# i2) = index h2 s
1040+
idx2 = I# (i1 Exts.<# i2)
1041+
{-# INLINE two' #-}
1042+
9941043
-- | \(O(\log n)\) Associate the value with the key in this map. If
9951044
-- this map previously contained a mapping for the key, the old value
9961045
-- is replaced by the result of applying the given function to the new
@@ -1809,13 +1858,26 @@ mapKeys f = fromList . foldrWithKey (\k x xs -> (f k, x) : xs) []
18091858
------------------------------------------------------------------------
18101859
-- * Difference and intersection
18111860

1861+
-- | A helper function to increase sharing of 'Leaf' nodes.
1862+
--
1863+
-- All 'HashMap' nodes supplied to accumulating function are 'Leaf' nodes.
1864+
-- 'Collision's are handled by creating a 'Leaf' node for each element.
1865+
foldlLeaves' :: (a -> Hash -> Leaf k v -> HashMap k v -> a) -> a -> HashMap k v -> a
1866+
foldlLeaves' f = go
1867+
where
1868+
go !z Empty = z
1869+
go z m@(Leaf h l) = f z h l m
1870+
go z (BitmapIndexed _ ary) = A.foldl' go z ary
1871+
go z (Full ary) = A.foldl' go z ary
1872+
go z (Collision h ary) = A.foldl' (\ z' l -> f z' h l (Leaf h l)) z ary
1873+
18121874
-- | \(O(n \log m)\) Difference of two maps. Return elements of the first map
18131875
-- not existing in the second.
18141876
difference :: (Eq k, Hashable k) => HashMap k v -> HashMap k w -> HashMap k v
1815-
difference a b = foldlWithKey' go empty a
1877+
difference a b = foldlLeaves' go empty a
18161878
where
1817-
go m k v = case lookup k b of
1818-
Nothing -> unsafeInsert k v m
1879+
go m h (L k _) l = case lookup' h k b of
1880+
Nothing -> unsafeInsertNewLeaf h l m
18191881
_ -> m
18201882
{-# INLINABLE difference #-}
18211883

@@ -1824,11 +1886,11 @@ difference a b = foldlWithKey' go empty a
18241886
-- If it returns 'Nothing', the element is discarded (proper set difference). If
18251887
-- it returns (@'Just' y@), the element is updated with a new value @y@.
18261888
differenceWith :: (Eq k, Hashable k) => (v -> w -> Maybe v) -> HashMap k v -> HashMap k w -> HashMap k v
1827-
differenceWith f a b = foldlWithKey' go empty a
1889+
differenceWith f a b = foldlLeaves' go empty a
18281890
where
1829-
go m k v = case lookup k b of
1830-
Nothing -> unsafeInsert k v m
1831-
Just w -> maybe m (\y -> unsafeInsert k y m) (f v w)
1891+
go m h (L k v) l = case lookup' h k b of
1892+
Nothing -> unsafeInsertNewLeaf h l m
1893+
Just w -> maybe m (\y -> unsafeInsertNewLeaf h (Leaf h (L k y)) m) (f v w)
18321894
{-# INLINABLE differenceWith #-}
18331895

18341896
-- | \(O(n \log m)\) Intersection of two maps. Return elements of the first

0 commit comments

Comments
 (0)