@@ -1908,30 +1908,32 @@ intersectionCollisions f h1 h2 ary1 ary2
19081908 1 -> Leaf h1 <$> A. read mary 0
19091909 _ -> Collision h1 <$> (A. unsafeFreeze =<< A. shrink mary len)
19101910 | otherwise = Empty
1911+ where
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
1921+ -- the next search starts 1 after the current one.
1922+ searchSwap :: Eq k => k -> Int -> A. MArray s (Leaf k v ) -> ST s (Maybe (Leaf k v ))
1923+ searchSwap toFind start = go start toFind start
1924+ where
1925+ go i0 k i mary
1926+ | i >= A. lengthM mary = pure Nothing
1927+ | otherwise = do
1928+ l@ (L k' _v) <- A. read mary i
1929+ if k == k'
1930+ then do
1931+ A. write mary i =<< A. read mary i0
1932+ pure $ Just l
1933+ else go i0 k (i + 1 ) mary
1934+ {-# INLINE searchSwap #-}
19111935{-# INLINE intersectionCollisions #-}
19121936
1913- -- | Say we have
1914- -- @
1915- -- 1 2 3 4
1916- -- @
1917- -- and we search for @3@. Then we can mutate the array to
1918- -- @
1919- -- undefined 2 1 4
1920- -- @
1921- -- We don't actually need to write undefined, we just have to make sure that the next search starts 1 after the current one.
1922- searchSwap :: Eq k => k -> Int -> A. MArray s (Leaf k v ) -> ST s (Maybe (Leaf k v ))
1923- searchSwap toFind start = go start toFind start
1924- where
1925- go i0 k i mary
1926- | i >= A. lengthM mary = pure Nothing
1927- | otherwise = do
1928- l@ (L k' _v) <- A. read mary i
1929- if k == k'
1930- then do
1931- A. write mary i =<< A. read mary i0
1932- pure $ Just l
1933- else go i0 k (i + 1 ) mary
1934- {-# INLINE searchSwap #-}
19351937
19361938------------------------------------------------------------------------
19371939-- * Folds
@@ -2307,33 +2309,49 @@ updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0)
23072309
23082310updateOrConcatWithKey :: Eq k => (k -> v -> v -> (# v # )) -> A. Array (Leaf k v ) -> A. Array (Leaf k v ) -> A. Array (Leaf k v )
23092311updateOrConcatWithKey f ary1 ary2 = A. run $ do
2310- -- TODO: instead of mapping and then folding, should we traverse?
2311- -- We'll have to be careful to avoid allocating pairs or similar.
2312-
2313- -- first: look up the position of each element of ary2 in ary1
2314- let indices = A. map' (\ (L k _) -> indexOf k ary1) ary2
2315- -- that tells us how large the overlap is:
2316- -- count number of Nothing constructors
2317- let nOnly2 = A. foldl' (\ n -> maybe (n+ 1 ) (const n)) 0 indices
23182312 let n1 = A. length ary1
23192313 let n2 = A. length ary2
2314+ mary <- A. new (n1 + n2) (A. index ary1 1 )
23202315 -- copy over all elements from ary1
2321- mary <- A. new_ (n1 + nOnly2)
2322- A. copy ary1 0 mary 0 n1
2316+ A. copy ary1 1 mary 1 (n1- 1 )
23232317 -- append or update all elements from ary2
2324- let go ! iEnd ! i2
2325- | i2 >= n2 = return ()
2326- | otherwise = case A. index indices i2 of
2327- Just i1 -> do -- key occurs in both arrays, store combination in position i1
2328- L k v1 <- A. indexM ary1 i1
2329- L _ v2 <- A. indexM ary2 i2
2330- case f k v1 v2 of (# v3 # ) -> A. write mary i1 (L k v3)
2331- go iEnd (i2+ 1 )
2332- Nothing -> do -- key is only in ary2, append to end
2333- A. write mary iEnd =<< A. indexM ary2 i2
2334- go (iEnd+ 1 ) (i2+ 1 )
2335- go n1 0
2336- return mary
2318+ let go ! iEnd ! i2 ! iMut
2319+ | i2 >= n2 = return iEnd
2320+ | otherwise = do
2321+ l@ (L k v2) <- A. indexM ary2 i2
2322+ res <- searchSwap k iMut n2 mary
2323+ case res of
2324+ Just (L _ v1) -> do -- key occurs in both arrays, store combination in position iMut
2325+ case f k v1 v2 of (# v3 # ) -> A. write mary iMut (L k v3)
2326+ go iEnd (i2+ 1 ) (iMut+ 1 )
2327+ Nothing -> do -- key is only in ary2, append to end
2328+ A. write mary iEnd l
2329+ go (iEnd+ 1 ) (i2+ 1 ) iMut
2330+ n <- go n1 0 0
2331+ A. shrink mary n
2332+ where
2333+ -- Say we have
2334+ -- @
2335+ -- 1 2 3 4
2336+ -- @
2337+ -- and we search for @3@. Then we can mutate the array to
2338+ -- @
2339+ -- 3 2 1 4
2340+ -- @
2341+ searchSwap :: Eq k => k -> Int -> Int -> A. MArray s (Leaf k v ) -> ST s (Maybe (Leaf k v ))
2342+ searchSwap toFind start end = go start toFind start
2343+ where
2344+ go i0 k i mary
2345+ | i >= end = pure Nothing
2346+ | otherwise = do
2347+ l@ (L k' _v) <- A. read mary i
2348+ if k == k'
2349+ then do
2350+ A. write mary i =<< A. read mary i0
2351+ A. write mary i0 l
2352+ pure $ Just l
2353+ else go i0 k (i + 1 ) mary
2354+ {-# INLINE searchSwap #-}
23372355{-# INLINABLE updateOrConcatWithKey #-}
23382356
23392357-- | \(O(n*m)\) Check if the first array is a subset of the second array.
0 commit comments