On Sun, Oct 09, 2011 at 03:30:20PM +0200, Jean-Marie Gaillourdet wrote:
Hi Daniel,

On 09.10.2011, at 14:45, Daniel Fischer wrote:

On Sunday 09 October 2011, 13:52:47, Jean-Marie Gaillourdet wrote:
This seems to be a Heisenbug as it is extremely fragile, when adding a
"| grep 1" to the while loop it seems to disappears. At least on my
computers.

Still produces 1s here with a grep.

Well, it may have been bad luck on my site.

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

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to