@@ -622,6 +622,11 @@ lookup' h k m = lookupCont (\_ -> Nothing) (\v _i -> Just v) h k m
622622-- If a collision did not occur then it will have the Int value (-1).
623623data LookupRes a = Absent | Present a ! Int
624624
625+ lookupResToMaybe :: LookupRes a -> Maybe a
626+ lookupResToMaybe Absent = Nothing
627+ lookupResToMaybe (Present x _) = Just x
628+ {-# INLINE lookupResToMaybe #-}
629+
625630-- Internal helper for lookup. This version takes the precomputed hash so
626631-- that functions that make multiple calls to lookup and related functions
627632-- (insert, delete) only need to calculate the hash once.
@@ -1279,11 +1284,16 @@ alterF :: (Functor f, Eq k, Hashable k)
12791284alterF f = \ ! k ! m ->
12801285 let
12811286 ! h = hash k
1282- mv = lookup' h k m
1287+ lookupRes = lookupRecordCollision h k m
1288+ mv = lookupResToMaybe lookupRes
12831289 in (<$> f mv) $ \ fres ->
12841290 case fres of
1285- Nothing -> maybe m (const (delete' h k m)) mv
1286- Just v' -> insert' h k v' m
1291+ Nothing -> case lookupRes of
1292+ Absent -> m
1293+ Present _ i -> deleteKeyExists i h k m
1294+ Just v' -> case lookupRes of
1295+ Absent -> insertNewKey h k v' m
1296+ Present _ i -> insertKeyExists i h k v' m
12871297
12881298-- We unconditionally rewrite alterF in RULES, but we expose an
12891299-- unfolding just in case it's used in some way that prevents the
@@ -1403,9 +1413,7 @@ alterFEager f !k m = (<$> f mv) $ \fres ->
14031413
14041414 where ! h = hash k
14051415 ! lookupRes = lookupRecordCollision h k m
1406- ! mv = case lookupRes of
1407- Absent -> Nothing
1408- Present v _ -> Just v
1416+ ! mv = lookupResToMaybe lookupRes
14091417{-# INLINABLE alterFEager #-}
14101418#endif
14111419
0 commit comments