Skip to content

Commit 1a3cd85

Browse files
committed
Optimize updateOrConcatWithKey
Fixes #403.
1 parent 19674b5 commit 1a3cd85

File tree

1 file changed

+63
-45
lines changed

1 file changed

+63
-45
lines changed

Data/HashMap/Internal.hs

Lines changed: 63 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -1907,30 +1907,32 @@ intersectionCollisions f h1 h2 ary1 ary2
19071907
1 -> Leaf h1 <$> A.read mary 0
19081908
_ -> Collision h1 <$> (A.unsafeFreeze =<< A.shrink mary len)
19091909
| otherwise = Empty
1910+
where
1911+
-- Say we have
1912+
-- @
1913+
-- 1 2 3 4
1914+
-- @
1915+
-- and we search for @3@. Then we can mutate the array to
1916+
-- @
1917+
-- undefined 2 1 4
1918+
-- @
1919+
-- We don't actually need to write undefined, we just have to make sure that
1920+
-- the next search starts 1 after the current one.
1921+
searchSwap :: Eq k => k -> Int -> A.MArray s (Leaf k v) -> ST s (Maybe (Leaf k v))
1922+
searchSwap toFind start = go start toFind start
1923+
where
1924+
go i0 k i mary
1925+
| i >= A.lengthM mary = pure Nothing
1926+
| otherwise = do
1927+
l@(L k' _v) <- A.read mary i
1928+
if k == k'
1929+
then do
1930+
A.write mary i =<< A.read mary i0
1931+
pure $ Just l
1932+
else go i0 k (i + 1) mary
1933+
{-# INLINE searchSwap #-}
19101934
{-# INLINE intersectionCollisions #-}
19111935

1912-
-- | Say we have
1913-
-- @
1914-
-- 1 2 3 4
1915-
-- @
1916-
-- and we search for @3@. Then we can mutate the array to
1917-
-- @
1918-
-- undefined 2 1 4
1919-
-- @
1920-
-- We don't actually need to write undefined, we just have to make sure that the next search starts 1 after the current one.
1921-
searchSwap :: Eq k => k -> Int -> A.MArray s (Leaf k v) -> ST s (Maybe (Leaf k v))
1922-
searchSwap toFind start = go start toFind start
1923-
where
1924-
go i0 k i mary
1925-
| i >= A.lengthM mary = pure Nothing
1926-
| otherwise = do
1927-
l@(L k' _v) <- A.read mary i
1928-
if k == k'
1929-
then do
1930-
A.write mary i =<< A.read mary i0
1931-
pure $ Just l
1932-
else go i0 k (i + 1) mary
1933-
{-# INLINE searchSwap #-}
19341936

19351937
------------------------------------------------------------------------
19361938
-- * Folds
@@ -2306,33 +2308,49 @@ updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0)
23062308

23072309
updateOrConcatWithKey :: Eq k => (k -> v -> v -> (# v #)) -> A.Array (Leaf k v) -> A.Array (Leaf k v) -> A.Array (Leaf k v)
23082310
updateOrConcatWithKey f ary1 ary2 = A.run $ do
2309-
-- TODO: instead of mapping and then folding, should we traverse?
2310-
-- We'll have to be careful to avoid allocating pairs or similar.
2311-
2312-
-- first: look up the position of each element of ary2 in ary1
2313-
let indices = A.map' (\(L k _) -> indexOf k ary1) ary2
2314-
-- that tells us how large the overlap is:
2315-
-- count number of Nothing constructors
2316-
let nOnly2 = A.foldl' (\n -> maybe (n+1) (const n)) 0 indices
23172311
let n1 = A.length ary1
23182312
let n2 = A.length ary2
2313+
mary <- A.new (n1 + n2) (A.index ary1 1)
23192314
-- copy over all elements from ary1
2320-
mary <- A.new_ (n1 + nOnly2)
2321-
A.copy ary1 0 mary 0 n1
2315+
A.copy ary1 1 mary 1 (n1-1)
23222316
-- append or update all elements from ary2
2323-
let go !iEnd !i2
2324-
| i2 >= n2 = return ()
2325-
| otherwise = case A.index indices i2 of
2326-
Just i1 -> do -- key occurs in both arrays, store combination in position i1
2327-
L k v1 <- A.indexM ary1 i1
2328-
L _ v2 <- A.indexM ary2 i2
2329-
case f k v1 v2 of (# v3 #) -> A.write mary i1 (L k v3)
2330-
go iEnd (i2+1)
2331-
Nothing -> do -- key is only in ary2, append to end
2332-
A.write mary iEnd =<< A.indexM ary2 i2
2333-
go (iEnd+1) (i2+1)
2334-
go n1 0
2335-
return mary
2317+
let go !iEnd !i2 !iMut
2318+
| i2 >= n2 = return iEnd
2319+
| otherwise = do
2320+
l@(L k v2) <- A.indexM ary2 i2
2321+
res <- searchSwap k iMut n2 mary
2322+
case res of
2323+
Just (L _ v1) -> do -- key occurs in both arrays, store combination in position iMut
2324+
case f k v1 v2 of (# v3 #) -> A.write mary iMut (L k v3)
2325+
go iEnd (i2+1) (iMut+1)
2326+
Nothing -> do -- key is only in ary2, append to end
2327+
A.write mary iEnd l
2328+
go (iEnd+1) (i2+1) iMut
2329+
n <- go n1 0 0
2330+
A.shrink mary n
2331+
where
2332+
-- Say we have
2333+
-- @
2334+
-- 1 2 3 4
2335+
-- @
2336+
-- and we search for @3@. Then we can mutate the array to
2337+
-- @
2338+
-- 3 2 1 4
2339+
-- @
2340+
searchSwap :: Eq k => k -> Int -> Int -> A.MArray s (Leaf k v) -> ST s (Maybe (Leaf k v))
2341+
searchSwap toFind start end = go start toFind start
2342+
where
2343+
go i0 k i mary
2344+
| i >= end = pure Nothing
2345+
| otherwise = do
2346+
l@(L k' _v) <- A.read mary i
2347+
if k == k'
2348+
then do
2349+
A.write mary i =<< A.read mary i0
2350+
A.write mary i0 l
2351+
pure $ Just l
2352+
else go i0 k (i + 1) mary
2353+
{-# INLINE searchSwap #-}
23362354
{-# INLINABLE updateOrConcatWithKey #-}
23372355

23382356
-- | \(O(n*m)\) Check if the first array is a subset of the second array.

0 commit comments

Comments
 (0)