#6130: Weak pointer to MVar is finalized, even though MVar is still accessible
-----------------------------------------+----------------------------------
Reporter: jmillikin | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.4.1 | Keywords:
Os: Unknown/Multiple | Architecture: Unknown/Multiple
Failure: Incorrect result at runtime | Testcase:
Blockedby: | Blocking:
Related: |
-----------------------------------------+----------------------------------
I'm seeing a problem mixing MVar and Weak: even though the MVar is still
accessible from a function's scope (and the main thread is blocking on
it), the Weak thinks it should be finalized.
Only seems to happen when compiled with -O2.
Platform: 64-bit Linux
Reproduced with GHC versions: 6.10.4, 6.12.3, 7.0.4, 7.2.2, 7.4.1
{{{
module Main (main) where
import Control.Concurrent
import Control.Monad (forever, forM_)
import Data.IORef
import System.Mem
import System.Mem.Weak
dispatchPendingCalls :: IORef [Weak (MVar ())] -> IO ()
dispatchPendingCalls ref = forever $ do
threadDelay 100000
pending <- atomicModifyIORef ref (\p -> ([], p))
forM_ pending (\weak -> do
maybeMVar <- deRefWeak weak
case maybeMVar of
Just mvar -> putMVar mvar ()
Nothing -> putStrLn "dispatchReply: weak mvar is
Nothing")
call :: IORef [Weak (MVar ())] -> IO ()
call ref = do
mvar <- newEmptyMVar
weak <- mkWeakPtr mvar (Just (putStrLn "call: finalising weak"))
putStrLn "call: about to insert weak into list"
atomicModifyIORef ref (\p -> (weak : p, ()))
putStrLn "call: inserted weak into list"
performGC
takeMVar mvar
putStrLn "call: took from mvar"
main :: IO ()
main = do
pendingCalls <- newIORef []
_ <- forkIO (dispatchPendingCalls pendingCalls)
call pendingCalls
}}}
Expected output:
{{{
$ ghc --make WeakVar.hs
$ ./WeakMvar
call: about to insert weak into list
call: inserted weak into list
call: took from mvar
}}}
Actual output:
{{{
$ ghc --make -O2 WeakVar.hs
$ ./WeakMvar
call: about to insert weak into list
call: inserted weak into list
call: finalizing weak
dispatchReply: weak mvar is Nothing
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/6130>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs