Skip to content

Commit c4c671f

Browse files
authored
Merge pull request #258 from ndmitchell/patch-1
* #254, avoid space leak with collisions * Add a regression test
2 parents f1a53e2 + c8ff7b4 commit c4c671f

File tree

3 files changed

+69
-10
lines changed

3 files changed

+69
-10
lines changed

Data/HashMap/Base.hs

Lines changed: 13 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -757,7 +757,7 @@ insert' h0 k0 v0 m0 = go h0 k0 v0 0 m0
757757
else Full (update16 ary i st')
758758
where i = index h s
759759
go h k x s t@(Collision hy v)
760-
| h == hy = Collision h (updateOrSnocWith const k x v)
760+
| h == hy = Collision h (updateOrSnocWith (\a _ -> (# a #)) k x v)
761761
| otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t)
762762
{-# INLINABLE insert' #-}
763763

@@ -880,7 +880,7 @@ unsafeInsert k0 v0 m0 = runST (go h0 k0 v0 0 m0)
880880
return t
881881
where i = index h s
882882
go h k x s t@(Collision hy v)
883-
| h == hy = return $! Collision h (updateOrSnocWith const k x v)
883+
| h == hy = return $! Collision h (updateOrSnocWith (\a _ -> (# a #)) k x v)
884884
| otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t)
885885
{-# INLINABLE unsafeInsert #-}
886886

@@ -1026,7 +1026,7 @@ unsafeInsertWith f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
10261026
return t
10271027
where i = index h s
10281028
go h k x s t@(Collision hy v)
1029-
| h == hy = return $! Collision h (updateOrSnocWith f k x v)
1029+
| h == hy = return $! Collision h (updateOrSnocWith (\a b -> (# f a b #)) k x v)
10301030
| otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t)
10311031
{-# INLINABLE unsafeInsertWith #-}
10321032

@@ -1394,10 +1394,10 @@ unionWithKey f = go 0
13941394
else collision h1 l1 l2
13951395
| otherwise = goDifferentHash s h1 h2 t1 t2
13961396
go s t1@(Leaf h1 (L k1 v1)) t2@(Collision h2 ls2)
1397-
| h1 == h2 = Collision h1 (updateOrSnocWithKey f k1 v1 ls2)
1397+
| h1 == h2 = Collision h1 (updateOrSnocWithKey (\k a b -> (# f k a b #)) k1 v1 ls2)
13981398
| otherwise = goDifferentHash s h1 h2 t1 t2
13991399
go s t1@(Collision h1 ls1) t2@(Leaf h2 (L k2 v2))
1400-
| h1 == h2 = Collision h1 (updateOrSnocWithKey (flip . f) k2 v2 ls1)
1400+
| h1 == h2 = Collision h1 (updateOrSnocWithKey (\k a b -> (# f k b a #)) k2 v2 ls1)
14011401
| otherwise = goDifferentHash s h1 h2 t1 t2
14021402
go s t1@(Collision h1 ls1) t2@(Collision h2 ls2)
14031403
| h1 == h2 = Collision h1 (updateOrConcatWithKey f ls1 ls2)
@@ -1932,12 +1932,12 @@ updateWith# f k0 ary0 = go k0 ary0 0 (A.length ary0)
19321932
| otherwise -> go k ary (i+1) n
19331933
{-# INLINABLE updateWith# #-}
19341934

1935-
updateOrSnocWith :: Eq k => (v -> v -> v) -> k -> v -> A.Array (Leaf k v)
1935+
updateOrSnocWith :: Eq k => (v -> v -> (# v #)) -> k -> v -> A.Array (Leaf k v)
19361936
-> A.Array (Leaf k v)
19371937
updateOrSnocWith f = updateOrSnocWithKey (const f)
19381938
{-# INLINABLE updateOrSnocWith #-}
19391939

1940-
updateOrSnocWithKey :: Eq k => (k -> v -> v -> v) -> k -> v -> A.Array (Leaf k v)
1940+
updateOrSnocWithKey :: Eq k => (k -> v -> v -> (# v #)) -> k -> v -> A.Array (Leaf k v)
19411941
-> A.Array (Leaf k v)
19421942
updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0)
19431943
where
@@ -1948,9 +1948,12 @@ updateOrSnocWithKey f k0 v0 ary0 = go k0 v0 ary0 0 (A.length ary0)
19481948
A.copy ary 0 mary 0 n
19491949
A.write mary n (L k v)
19501950
return mary
1951-
| otherwise = case A.index ary i of
1952-
(L kx y) | k == kx -> A.update ary i (L k (f k v y))
1953-
| otherwise -> go k v ary (i+1) n
1951+
| L kx y <- A.index ary i
1952+
, k == kx
1953+
, (# v2 #) <- f k v y
1954+
= A.update ary i (L k v2)
1955+
| otherwise
1956+
= go k v ary (i+1) n
19541957
{-# INLINABLE updateOrSnocWithKey #-}
19551958

19561959
updateOrConcatWith :: Eq k => (v -> v -> v) -> A.Array (Leaf k v) -> A.Array (Leaf k v) -> A.Array (Leaf k v)

tests/Regressions.hs

Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,21 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
2+
{-# LANGUAGE MagicHash #-}
3+
{-# LANGUAGE UnboxedTuples #-}
14
module Main where
25

36
import Control.Applicative ((<$>))
7+
import Control.Exception (evaluate)
48
import Control.Monad (replicateM)
9+
import Data.Hashable (Hashable(..))
510
import qualified Data.HashMap.Strict as HM
11+
import qualified Data.HashMap.Lazy as HML
612
import Data.List (delete)
713
import Data.Maybe
14+
import GHC.Exts (touch#)
15+
import GHC.IO (IO (..))
16+
import System.Mem (performGC)
17+
import System.Mem.Weak (mkWeakPtr, deRefWeak)
18+
import System.Random (randomIO)
819
import Test.HUnit (Assertion, assert)
920
import Test.Framework (Test, defaultMain)
1021
import Test.Framework.Providers.HUnit (testCase)
@@ -71,6 +82,48 @@ propEqAfterDelete (Keys keys) =
7182
mapFromKeys :: [Int] -> HM.HashMap Int ()
7283
mapFromKeys keys = HM.fromList (zip keys (repeat ()))
7384

85+
------------------------------------------------------------------------
86+
-- Issue #254
87+
88+
-- Key type that always collides.
89+
newtype KC = KC Int
90+
deriving (Eq, Ord, Show)
91+
instance Hashable KC where
92+
hashWithSalt salt _ = salt
93+
94+
touch :: a -> IO ()
95+
touch a = IO (\s -> (# touch# a s, () #))
96+
97+
-- We want to make sure that old values in the HashMap are evicted when new values are inserted,
98+
-- even if they aren't evaluated. To do that, we use the WeakPtr trick described at
99+
-- http://simonmar.github.io/posts/2018-06-20-Finding-fixing-space-leaks.html.
100+
-- We insert a value named oldV into the HashMap, then insert over it, checking oldV is no longer reachable.
101+
--
102+
-- To make the test robust, it's important that oldV isn't hoisted up to the top or shared.
103+
-- To do that, we generate it randomly.
104+
issue254Lazy :: Assertion
105+
issue254Lazy = do
106+
i :: Int <- randomIO
107+
let oldV = error $ "Should not be evaluated: " ++ show i
108+
weakV <- mkWeakPtr oldV Nothing -- add the ability to test whether oldV is alive
109+
mp <- evaluate $ HML.insert (KC 1) (error "Should not be evaluated") $ HML.fromList [(KC 0, "1"), (KC 1, oldV)]
110+
performGC
111+
res <- deRefWeak weakV -- gives Just if oldV is still alive
112+
touch mp -- makes sure that we didn't GC away the whole HashMap, just oldV
113+
assert $ isNothing res
114+
115+
-- Like issue254Lazy, but using strict HashMap
116+
issue254Strict :: Assertion
117+
issue254Strict = do
118+
i :: Int <- randomIO
119+
let oldV = show i
120+
weakV <- mkWeakPtr oldV Nothing
121+
mp <- evaluate $ HM.insert (KC 1) "3" $ HM.fromList [(KC 0, "1"), (KC 1, oldV)]
122+
performGC
123+
res <- deRefWeak weakV
124+
touch mp
125+
assert $ isNothing res
126+
74127
------------------------------------------------------------------------
75128
-- * Test list
76129

@@ -80,6 +133,8 @@ tests =
80133
testCase "issue32" issue32
81134
, testCase "issue39a" issue39
82135
, testProperty "issue39b" propEqAfterDelete
136+
, testCase "issue254 lazy" issue254Lazy
137+
, testCase "issue254 strict" issue254Strict
83138
]
84139

85140
------------------------------------------------------------------------

unordered-containers.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -155,6 +155,7 @@ test-suite regressions
155155
hashable >= 1.0.1.1,
156156
HUnit,
157157
QuickCheck >= 2.4.0.1,
158+
random,
158159
test-framework >= 0.3.3,
159160
test-framework-hunit,
160161
test-framework-quickcheck2,

0 commit comments

Comments
 (0)