1+ {-# LANGUAGE ScopedTypeVariables #-}
2+ {-# LANGUAGE MagicHash #-}
3+ {-# LANGUAGE UnboxedTuples #-}
14module Main where
25
36import Control.Applicative ((<$>) )
7+ import Control.Exception (evaluate )
48import Control.Monad (replicateM )
9+ import Data.Hashable (Hashable (.. ))
510import qualified Data.HashMap.Strict as HM
11+ import qualified Data.HashMap.Lazy as HML
612import Data.List (delete )
713import 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 )
819import Test.HUnit (Assertion , assert )
920import Test.Framework (Test , defaultMain )
1021import Test.Framework.Providers.HUnit (testCase )
@@ -71,6 +82,48 @@ propEqAfterDelete (Keys keys) =
7182mapFromKeys :: [Int ] -> HM. HashMap Int ()
7283mapFromKeys 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------------------------------------------------------------------------
0 commit comments