@@ -835,7 +835,7 @@ insert' h0 k0 v0 m0 = go h0 k0 v0 0 m0
835835 where i = index h s
836836 go h k x s t@ (Collision hy v)
837837 | h == hy = Collision h (updateOrSnocWith (\ a _ -> (# a # )) k x v)
838- | otherwise = go h k x s $ BitmapIndexed (mask hy s) ( A. singleton t)
838+ | otherwise = runST $ two s h k x hy t
839839{-# INLINABLE insert' #-}
840840
841841-- | Insert optimized for the case when we know the key is not in the map.
@@ -1260,11 +1260,10 @@ adjust# f k0 m0 = go h0 k0 0 m0
12601260-- | \(O(\log n)\) The expression @('update' f k map)@ updates the value @x@ at @k@
12611261-- (if it is in the map). If @(f x)@ is 'Nothing', the element is deleted.
12621262-- If it is @('Just' y)@, the key @k@ is bound to the new value @y@.
1263- update :: (Eq k , Hashable k ) => (a -> Maybe a ) -> k -> HashMap k a -> HashMap k a
1264- update f = alter (>>= f)
1263+ update :: (Eq k , Hashable k , Show k , Show a ) => (a -> Maybe a ) -> k -> HashMap k a -> HashMap k a
1264+ update f = Exts. inline alter (>>= f)
12651265{-# INLINABLE update #-}
12661266
1267-
12681267-- | \(O(\log n)\) The expression @('alter' f k map)@ alters the value @x@ at @k@, or
12691268-- absence thereof.
12701269--
@@ -1273,27 +1272,89 @@ update f = alter (>>= f)
12731272-- @
12741273-- 'lookup' k ('alter' f k m) = f ('lookup' k m)
12751274-- @
1276- alter :: (Eq k , Hashable k ) => (Maybe v -> Maybe v ) -> k -> HashMap k v -> HashMap k v
1277- alter f k m =
1278- let ! h = hash k
1279- ! lookupRes = lookupRecordCollision h k m
1280- in case f (lookupResToMaybe lookupRes) of
1281- Nothing -> case lookupRes of
1282- Absent -> m
1283- Present _ collPos -> deleteKeyExists collPos h k m
1284- Just v' -> case lookupRes of
1285- Absent -> insertNewKey h k v' m
1286- Present v collPos ->
1287- if v `ptrEq` v'
1288- then m
1289- else insertKeyExists collPos h k v' m
1290- {-# INLINABLE alter #-}
1291-
1292- -- | \(O(\log n)\) The expression @('alterF' f k map)@ alters the value @x@ at
1293- -- @k@, or absence thereof.
1294- --
1295- -- 'alterF' can be used to insert, delete, or update a value in a map.
1296- --
1275+ alter :: (Eq k , Hashable k , Show k , Show v ) => (Maybe v -> Maybe v ) -> k -> HashMap k v -> HashMap k v
1276+ alter f k = alter' f (hash k) k
1277+ {-# INLINEABLE alter #-}
1278+
1279+ alter' :: (Eq k , Show v ) => (Maybe v -> Maybe v ) -> Hash -> k -> HashMap k v -> HashMap k v
1280+ alter' f h0 k0 m0 = go h0 k0 0 m0
1281+ where
1282+ go ! h ! k ! _ Empty = case f Nothing of
1283+ Nothing -> Empty
1284+ Just v -> Leaf h $ L k v
1285+ go h k s t@ (Leaf hy l@ (L ky v))
1286+ | hy == h =
1287+ if ky == k
1288+ then case f $ Just v of
1289+ Nothing -> Empty
1290+ Just v'
1291+ | v `ptrEq` v' -> t
1292+ | otherwise -> Leaf h $ L k v'
1293+ else do
1294+ case f Nothing of
1295+ Nothing -> t
1296+ Just v' -> collision h l $ L k v'
1297+ | otherwise = case f Nothing of
1298+ Nothing -> t
1299+ Just v' -> runST $ two s h k v' hy t
1300+ go h k s t@ (BitmapIndexed b ary)
1301+ | b .&. m == 0 = case f Nothing of
1302+ Nothing -> t
1303+ Just v' -> bitmapIndexedOrFull (b .|. m) $! A. insert ary i $! Leaf h $! L k v'
1304+ | otherwise = do
1305+ let ! st = A. index ary i
1306+ ! st' = go h k (nextShift s) st
1307+ if st' `ptrEq` st
1308+ then t
1309+ else case st' of
1310+ Empty
1311+ | A. length ary == 1 -> Empty
1312+ | A. length ary == 2 ->
1313+ case (i, A. index ary 0 , A. index ary 1 ) of
1314+ (0 , _, l) | isLeafOrCollision l -> l
1315+ (1 , l, _) | isLeafOrCollision l -> l
1316+ _ -> bIndexed
1317+ | otherwise -> bIndexed
1318+ where
1319+ bIndexed = BitmapIndexed (b .&. complement m) (A. delete ary i)
1320+ l | isLeafOrCollision l && A. length ary == 1 -> l
1321+ _ -> BitmapIndexed b (A. update ary i st')
1322+ where
1323+ m = mask h s
1324+ i = sparseIndex b m
1325+ go h k s t@ (Full ary) = do
1326+ let ! st = A. index ary i
1327+ ! st' = go h k (nextShift s) st
1328+ if st' `ptrEq` st
1329+ then t
1330+ else case st' of
1331+ Empty ->
1332+ let ary' = A. delete ary i
1333+ bm = fullBitmap .&. complement (1 `unsafeShiftL` i)
1334+ in BitmapIndexed bm ary'
1335+ _ -> Full (A. update ary i st')
1336+ where
1337+ i = index h s
1338+ go h k s t@ (Collision hy ls)
1339+ | h == hy = case indexOf k ls of
1340+ Just i -> do
1341+ let (# L _ v # ) = A. index# ls i
1342+ case f $ Just v of
1343+ Nothing
1344+ | A. length ls == 2 ->
1345+ if i == 0
1346+ then Leaf h (A. index ls 1 )
1347+ else Leaf h (A. index ls 0 )
1348+ | otherwise -> Collision hy (A. delete ls i)
1349+ Just v' -> Collision hy $ A. update ls i $ L k v'
1350+ Nothing -> case f Nothing of
1351+ Nothing -> t
1352+ Just v' -> Collision hy $ A. snoc ls $ L k v'
1353+ | otherwise = case f Nothing of
1354+ Nothing -> t
1355+ Just v' -> runST $ two s h k v' hy t
1356+ {-# INLINE alter' #-}
1357+
12971358-- Note: 'alterF' is a flipped version of the 'at' combinator from
12981359-- <https://hackage.haskell.org/package/lens/docs/Control-Lens-At.html#v:at Control.Lens.At>.
12991360--
0 commit comments