Skip to content

Commit 261ba6d

Browse files
committed
differenceWith[Key]: Get the function argument to inline
This makes the overlapping case significantly faster.
1 parent 0c0d1f0 commit 261ba6d

File tree

2 files changed

+32
-32
lines changed

2 files changed

+32
-32
lines changed

Data/HashMap/Internal.hs

Lines changed: 30 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -1920,26 +1920,26 @@ differenceCollisions !h1 !ary1 t1 !h2 !ary2
19201920
-- it returns (@'Just' y@), the element is updated with a new value @y@.
19211921
differenceWith :: Eq k => (v -> w -> Maybe v) -> HashMap k v -> HashMap k w -> HashMap k v
19221922
differenceWith f = differenceWithKey (const f)
1923-
{-# INLINABLE differenceWith #-}
1923+
{-# INLINE differenceWith #-}
19241924

19251925
-- | \(O(n \log m)\) Difference with a combining function. When two equal keys are
19261926
-- encountered, the combining function is applied to the values of these keys.
19271927
-- If it returns 'Nothing', the element is discarded (proper set difference). If
19281928
-- it returns (@'Just' y@), the element is updated with a new value @y@.
19291929
differenceWithKey :: Eq k => (k -> v -> w -> Maybe v) -> HashMap k v -> HashMap k w -> HashMap k v
1930-
differenceWithKey = go_differenceWithKey 0
1930+
differenceWithKey f = go_differenceWithKey 0
19311931
where
1932-
go_differenceWithKey !_s _f Empty _tB = Empty
1933-
go_differenceWithKey _s _f a Empty = a
1934-
go_differenceWithKey s f a@(Leaf hA (L kA vA)) b
1932+
go_differenceWithKey !_s Empty _tB = Empty
1933+
go_differenceWithKey _s a Empty = a
1934+
go_differenceWithKey s a@(Leaf hA (L kA vA)) b
19351935
= lookupCont
19361936
(\_ -> a)
19371937
(\vB _ -> case f kA vA vB of
19381938
Nothing -> Empty
19391939
Just v | v `ptrEq` vA -> a
19401940
| otherwise -> Leaf hA (L kA v))
19411941
hA kA s b
1942-
go_differenceWithKey _s f a@(Collision hA aryA) (Leaf hB (L kB vB))
1942+
go_differenceWithKey _s a@(Collision hA aryA) (Leaf hB (L kB vB))
19431943
| hA == hB
19441944
= lookupInArrayCont
19451945
(\_ -> a)
@@ -1952,10 +1952,10 @@ differenceWithKey = go_differenceWithKey 0
19521952
| otherwise -> Collision hA (A.update aryA i (L kB v)))
19531953
kB aryA
19541954
| otherwise = a
1955-
go_differenceWithKey s f a@(BitmapIndexed bA aryA) b@(Leaf hB _)
1955+
go_differenceWithKey s a@(BitmapIndexed bA aryA) b@(Leaf hB _)
19561956
| bA .&. m == 0 = a
19571957
| otherwise = case A.index# aryA i of
1958-
(# !stA #) -> case go_differenceWithKey (nextShift s) f stA b of
1958+
(# !stA #) -> case go_differenceWithKey (nextShift s) stA b of
19591959
Empty | A.length aryA == 2
19601960
, (# l #) <- A.index# aryA (otherOfOneOrZero i)
19611961
, isLeafOrCollision l
@@ -1968,11 +1968,11 @@ differenceWithKey = go_differenceWithKey 0
19681968
where
19691969
m = mask hB s
19701970
i = sparseIndex bA m
1971-
go_differenceWithKey s f a@(BitmapIndexed bA aryA) b@(Collision hB _)
1971+
go_differenceWithKey s a@(BitmapIndexed bA aryA) b@(Collision hB _)
19721972
| bA .&. m == 0 = a
19731973
| otherwise =
19741974
case A.index# aryA i of
1975-
(# !st #) -> case go_differenceWithKey (nextShift s) f st b of
1975+
(# !st #) -> case go_differenceWithKey (nextShift s) st b of
19761976
Empty | A.length aryA == 2
19771977
, (# l #) <- A.index# aryA (otherOfOneOrZero i)
19781978
, isLeafOrCollision l
@@ -1985,47 +1985,47 @@ differenceWithKey = go_differenceWithKey 0
19851985
where
19861986
m = mask hB s
19871987
i = sparseIndex bA m
1988-
go_differenceWithKey s f a@(Full aryA) b@(Leaf hB _)
1988+
go_differenceWithKey s a@(Full aryA) b@(Leaf hB _)
19891989
= case A.index# aryA i of
1990-
(# !stA #) -> case go_differenceWithKey (nextShift s) f stA b of
1990+
(# !stA #) -> case go_differenceWithKey (nextShift s) stA b of
19911991
Empty ->
19921992
let aryA' = A.delete aryA i
19931993
bm = fullBitmap .&. complement (1 `unsafeShiftL` i)
19941994
in BitmapIndexed bm aryA'
19951995
stA' | stA `ptrEq` stA' -> a
19961996
| otherwise -> Full (updateFullArray aryA i stA')
19971997
where i = index hB s
1998-
go_differenceWithKey s f a@(Full aryA) b@(Collision hB _)
1998+
go_differenceWithKey s a@(Full aryA) b@(Collision hB _)
19991999
= case A.index# aryA i of
2000-
(# !stA #) -> case go_differenceWithKey (nextShift s) f stA b of
2000+
(# !stA #) -> case go_differenceWithKey (nextShift s) stA b of
20012001
Empty ->
20022002
let aryA' = A.delete aryA i
20032003
bm = fullBitmap .&. complement (1 `unsafeShiftL` i)
20042004
in BitmapIndexed bm aryA'
20052005
stA' | stA `ptrEq` stA' -> a
20062006
| otherwise -> Full (updateFullArray aryA i stA')
20072007
where i = index hB s
2008-
go_differenceWithKey s f a@(Collision hA _) (BitmapIndexed bB aryB)
2008+
go_differenceWithKey s a@(Collision hA _) (BitmapIndexed bB aryB)
20092009
| bB .&. m == 0 = a
20102010
| otherwise =
20112011
case A.index# aryB (sparseIndex bB m) of
2012-
(# stB #) -> go_differenceWithKey (nextShift s) f a stB
2012+
(# stB #) -> go_differenceWithKey (nextShift s) a stB
20132013
where m = mask hA s
2014-
go_differenceWithKey s f a@(Collision hA _) (Full aryB)
2014+
go_differenceWithKey s a@(Collision hA _) (Full aryB)
20152015
= case A.index# aryB (index hA s) of
2016-
(# stB #) -> go_differenceWithKey (nextShift s) f a stB
2017-
go_differenceWithKey s f a@(BitmapIndexed bA aryA) (BitmapIndexed bB aryB)
2018-
= differenceWithKey_Arrays s f bA aryA a bB aryB
2019-
go_differenceWithKey s f a@(Full aryA) (BitmapIndexed bB aryB)
2020-
= differenceWithKey_Arrays s f fullBitmap aryA a bB aryB
2021-
go_differenceWithKey s f a@(BitmapIndexed bA aryA) (Full aryB)
2022-
= differenceWithKey_Arrays s f bA aryA a fullBitmap aryB
2023-
go_differenceWithKey s f a@(Full aryA) (Full aryB)
2024-
= differenceWithKey_Arrays s f fullBitmap aryA a fullBitmap aryB
2025-
go_differenceWithKey _s f a@(Collision hA aryA) (Collision hB aryB)
2016+
(# stB #) -> go_differenceWithKey (nextShift s) a stB
2017+
go_differenceWithKey s a@(BitmapIndexed bA aryA) (BitmapIndexed bB aryB)
2018+
= differenceWithKey_Arrays s bA aryA a bB aryB
2019+
go_differenceWithKey s a@(Full aryA) (BitmapIndexed bB aryB)
2020+
= differenceWithKey_Arrays s fullBitmap aryA a bB aryB
2021+
go_differenceWithKey s a@(BitmapIndexed bA aryA) (Full aryB)
2022+
= differenceWithKey_Arrays s bA aryA a fullBitmap aryB
2023+
go_differenceWithKey s a@(Full aryA) (Full aryB)
2024+
= differenceWithKey_Arrays s fullBitmap aryA a fullBitmap aryB
2025+
go_differenceWithKey _s a@(Collision hA aryA) (Collision hB aryB)
20262026
= differenceWithKey_Collisions f hA aryA a hB aryB
20272027

2028-
differenceWithKey_Arrays !s f !bA !aryA tA !bB !aryB
2028+
differenceWithKey_Arrays !s !bA !aryA tA !bB !aryB
20292029
| bA .&. bB == 0 = tA
20302030
| otherwise = runST $ do
20312031
mary <- A.new_ $ A.length aryA
@@ -2042,7 +2042,7 @@ differenceWithKey = go_differenceWithKey 0
20422042
go_dWKA (i + 1) (iA + 1) nextBA' (bResult .|. m) nChanges
20432043
_ -> do
20442044
!stB <- A.indexM aryB (sparseIndex bB m)
2045-
case go_differenceWithKey (nextShift s) f stA stB of
2045+
case go_differenceWithKey (nextShift s) stA stB of
20462046
Empty -> go_dWKA i (iA + 1) nextBA' bResult (nChanges + 1)
20472047
st -> do
20482048
A.write mary i st
@@ -2064,7 +2064,7 @@ differenceWithKey = go_differenceWithKey 0
20642064
then pure l
20652065
else BitmapIndexed bResult <$> (A.unsafeFreeze =<< A.shrink mary 1)
20662066
n -> bitmapIndexedOrFull bResult <$> (A.unsafeFreeze =<< A.shrink mary n)
2067-
{-# INLINABLE differenceWithKey #-}
2067+
{-# INLINE differenceWithKey #-}
20682068

20692069
-- TODO: This could be faster if we would keep track of which elements of ary2
20702070
-- we've already matched. Those could be skipped when we check the following

Data/HashMap/Internal/Strict.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -622,14 +622,14 @@ differenceWith f = HM.differenceWithKey $
622622
\_k vA vB -> case f vA vB of
623623
Nothing -> Nothing
624624
x@(Just !_v) -> x
625-
{-# INLINABLE differenceWith #-}
625+
{-# INLINE differenceWith #-}
626626

627627
differenceWithKey :: Eq k => (k -> v -> w -> Maybe v) -> HashMap k v -> HashMap k w -> HashMap k v
628628
differenceWithKey f = HM.differenceWithKey $
629629
\k vA vB -> case f k vA vB of
630630
Nothing -> Nothing
631631
x@(Just !_v) -> x
632-
{-# INLINABLE differenceWithKey #-}
632+
{-# INLINE differenceWithKey #-}
633633

634634
-- | \(O(n+m)\) Intersection of two maps. If a key occurs in both maps
635635
-- the provided function is used to combine the values from the two

0 commit comments

Comments
 (0)