Re: Is this a concurrency bug in base?

Hi, the Eq instance of TypeRep shows the same non-deterministic behavior: import Control.Concurrent import Control.Exception import Control.Monad import Data.Typeable main :: IO () main = do { fin1 <- newEmptyMVar ; fin2 <- newEmptyMVar ; forkIO $ return (typeOf ()) >>= evaluate >>= putMVar fin1 ; forkIO $ return (typeOf ()) >>= evaluate >>= putMVar fin2 ; t1 <- takeMVar fin1 ; t2 <- takeMVar fin2 ; when (t1 /= t2) $ putStrLn $ "typeOf " ++ show t1 ++ " /= typeOf " ++ show t2 } $ ghc-7.0.3 -threaded -rtsopts TypeRepEq.hs <snip> $ while true ; do ./TypeRepEq +RTS -N ; done typeOf () /= typeOf () typeOf () /= typeOf () ^C^C $ On 09.10.2011, at 16:04, David Brown wrote:
The program below will occasionally print "1 /= 0" or "0 /= 1" on x86_64 linux with the Debian testing 7.0.4 ghc.
$ ghc bug -rtsopts -threaded $ while true; do ./bug +RTS -N; done
module Main where import Control.Monad import Control.Concurrent import Data.Typeable main :: IO () main = do fin1 <- newEmptyMVar fin2 <- newEmptyMVar forkIO $ child fin1 forkIO $ child fin2 a <- takeMVar fin1 b <- takeMVar fin2 when (a /= b) $ putStrLn $ show a ++ " /= " ++ show b child :: MVar Int -> IO () child var = do key <- typeRepKey (typeOf ()) putMVar var key
Thanks again for reproducing it. Jean
participants (1)
-
Jean-Marie Gaillourdet