Is this a concurrency bug in base?

Hi, I am working on a library I'd like to release to hackage very soon, but I've found a problem with supporting GHC 6.12 and GHC 7.0. Consider the following program: import Control.Concurrent import Data.Typeable main :: IO () main = do { fin1 <- newEmptyMVar ; fin2 <- newEmptyMVar ; forkIO $ typeRepKey (typeOf ()) >>= print >> putMVar fin1 () ; forkIO $ typeRepKey (typeOf ()) >>= print >> putMVar fin2 () ; () <- takeMVar fin1 ; () <- takeMVar fin2 ; putStrLn "---" ; return () } When compiled with GHC 7.0.x or GHC 6.12.x, it should print two identical numbers. Sometimes it does not. To reproduce this compile and execute as follows: $ ghc-7.0.3 -rtsopts -threaded TypeRepKey.hs -o TypeRepKey $ while true ; do ./TypeRepKey +RTS -N ; done 0 0 --- 0 0 --- 0 0 --- 0 1 --- 0 0 --- … Ideally you should get an infinite number of zeros but once in a while you have a single(!) one in between. The two numbers of one program run should be identical, but their values may be arbitrary. But it should not be possible to have single outliers. This only happens when executed with more than one thread. I've also a somewhat larger program which seems to indicate that fromDynamic fails occasionally. I can post it as well if it helps. 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. All this was done on several Macs running the latest OS X Lion with ghc 7.0.3 from the binary distribution on the GHC download page. Actually, I am trying to find a method to use a "type" as key in a map which works before GHC 7.2. I'd be glad to get any ideas on how to achieve that, given that typeRepKey seems to buggy. I'd be happy to get any comments on this matter. Regards, Jean

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.
All this was done on several Macs running the latest OS X Lion with ghc 7.0.3 from the binary distribution on the GHC download page.
linux x86_64, ghc-7.0.4, 7.0.2 and 6.12.3. Indeed 6.12.3 goes so far to sometimes produce 0 0 --- 10 --- 0 0 --- 01 --- i.e. it switches threads during print.

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.
All this was done on several Macs running the latest OS X Lion with ghc 7.0.3 from the binary distribution on the GHC download page.
linux x86_64, ghc-7.0.4, 7.0.2 and 6.12.3. Indeed 6.12.3 goes so far to sometimes produce 0 0 --- 10
--- 0 0 --- 01
---
i.e. it switches threads during print.
Thanks, for reproducing it. I failed to see it on Linux so far. So I guess a bug report is in order? Or are bug reports to old versions not welcome? Jean

On Sunday 09 October 2011, 15:30:20, 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.
Or maybe Macs behave differently.
Thanks, for reproducing it. I failed to see it on Linux so far. So I guess a bug report is in order?
I'd think so. Although due to the changes in 7.2 there's nothing to fix here anymore, it might point to something still to be fixed.
Or are bug reports to old versions not welcome?
Within reason. Reporting bugs against 5.* would be rather pointless now, but >= 6.10 should be okay. If the behaviour has been fixed as a by-product of some other change, at least a test could be made to prevent regression. If, like here, the directly concerned code has been changed, probably nothing is to be done, but the bug may have been caused by something else which still needs to be fixed, so better report one bug too many.

Hi Daniel, On 09.10.2011, at 16:24, Daniel Fischer wrote:
On Sunday 09 October 2011, 15:30:20, 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.
Or maybe Macs behave differently.
Thanks, for reproducing it. I failed to see it on Linux so far. So I guess a bug report is in order?
I'd think so. Although due to the changes in 7.2 there's nothing to fix here anymore, it might point to something still to be fixed.
Or are bug reports to old versions not welcome?
Within reason. Reporting bugs against 5.* would be rather pointless now, but >= 6.10 should be okay. If the behaviour has been fixed as a by-product of some other change, at least a test could be made to prevent regression. If, like here, the directly concerned code has been changed, probably nothing is to be done, but the bug may have been caused by something else which still needs to be fixed, so better report one bug too many.
I've been chasing the source of the non-deterministic of my library for quite some time now. And at several points in time I had the impression that modifyMVar would not always be atomic. (Of course under the assumption that no other code touches the MVar). But in that case as well as in the case here it is only reproducible by looping the execution of the binary. Moving the loop into the Haskell program will show the bug in the first iteration or never. I will report a bug. Jean

On 09.10.2011, at 16:40, Jean-Marie Gaillourdet wrote:
I will report a bug.

Jean-Marie Gaillourdet:
the Eq instance of TypeRep shows the same non-deterministic behavior:
Of course, equality on TypeReps is implemented by comparison of the Keys. On Sunday 09 October 2011, 16:40:13, Jean-Marie Gaillourdet wrote:
Hi Daniel,
I've been chasing the source of the non-deterministic of my library for quite some time now. And at several points in time I had the impression that modifyMVar would not always be atomic.
It isn't: "MVars offer more flexibility than IORefs, but less flexibility than STM. They are appropriate for building synchronization primitives and performing simple interthread communication; however they are very simple and susceptible to race conditions, deadlocks or uncaught exceptions. Do not use them if you need perform larger atomic operations such as reading from multiple variables: use STM instead. In particular, the bigger functions in this module (readMVar, swapMVar, withMVar, modifyMVar_ and modifyMVar) are simply the composition of a takeMVar followed by a putMVar with exception safety. These only have atomicity guarantees if all other threads perform a takeMVar before a putMVar as well; otherwise, they may block." But I don't think that's the problem here.
(Of course under the assumption that no other code touches the MVar). But in that case as well as in the case here it is only reproducible by looping the execution of the binary. Moving the loop into the Haskell program will show the bug in the first iteration or never.
That's what I expect. I think what happens is: -- from Data.Typeable cache = unsafePerformIO $ ... mkTyConKey :: String -> Key mkTyConKey str = unsafePerformIO $ do let Cache {next_key = kloc, tc_tbl = tbl} = cache mb_k <- HT.lookup tbl str case mb_k of Just k -> return k Nothing -> do { k <- newKey kloc ; HT.insert tbl str k ; return k } occasionally, the second thread gets to perform the lookup before the first has updated the cache, so both threads create a new entry and update the cache. If you loop in the Haskell programme, after the first round each thread definitely finds an entry for "()", so the cache isn't updated anymore.
I will report a bug.
Jean

Hi, On 09.10.2011, at 17:27, Daniel Fischer wrote:
Jean-Marie Gaillourdet:
the Eq instance of TypeRep shows the same non-deterministic behavior:
Of course, equality on TypeReps is implemented by comparison of the Keys.
On Sunday 09 October 2011, 16:40:13, Jean-Marie Gaillourdet wrote:
Hi Daniel,
I've been chasing the source of the non-deterministic of my library for quite some time now. And at several points in time I had the impression that modifyMVar would not always be atomic.
It isn't:
"MVars offer more flexibility than IORefs, but less flexibility than STM. They are appropriate for building synchronization primitives and performing simple interthread communication; however they are very simple and susceptible to race conditions, deadlocks or uncaught exceptions. Do not use them if you need perform larger atomic operations such as reading from multiple variables: use STM instead.
In particular, the bigger functions in this module (readMVar, swapMVar, withMVar, modifyMVar_ and modifyMVar) are simply the composition of a takeMVar followed by a putMVar with exception safety. These only have atomicity guarantees if all other threads perform a takeMVar before a putMVar as well; otherwise, they may block."
But I don't think that's the problem here.
(Of course under the assumption that no other code touches the MVar). This sentence referred to what you explained above. Although, my reference was quite cryptic.
But in that case as well as in the case here it is only reproducible by looping the execution of the binary. Moving the loop into the Haskell program will show the bug in the first iteration or never.
That's what I expect. I think what happens is:
-- from Data.Typeable
cache = unsafePerformIO $ ...
mkTyConKey :: String -> Key mkTyConKey str = unsafePerformIO $ do let Cache {next_key = kloc, tc_tbl = tbl} = cache mb_k <- HT.lookup tbl str case mb_k of Just k -> return k Nothing -> do { k <- newKey kloc ; HT.insert tbl str k ; return k }
occasionally, the second thread gets to perform the lookup before the first has updated the cache, so both threads create a new entry and update the cache.
If you loop in the Haskell programme, after the first round each thread definitely finds an entry for "()", so the cache isn't updated anymore.
That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating typeOf? Jean

Hi, On 09.10.2011, at 17:37, Jean-Marie Gaillourdet wrote:
Hi,
On 09.10.2011, at 17:27, Daniel Fischer wrote:
That's what I expect. I think what happens is:
-- from Data.Typeable
cache = unsafePerformIO $ ...
mkTyConKey :: String -> Key mkTyConKey str = unsafePerformIO $ do let Cache {next_key = kloc, tc_tbl = tbl} = cache mb_k <- HT.lookup tbl str case mb_k of Just k -> return k Nothing -> do { k <- newKey kloc ; HT.insert tbl str k ; return k }
occasionally, the second thread gets to perform the lookup before the first has updated the cache, so both threads create a new entry and update the cache.
If you loop in the Haskell programme, after the first round each thread definitely finds an entry for "()", so the cache isn't updated anymore.
That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating typeOf? typeOf' seems to be a working workaround:
typeOf' val | t1 == t2 = t1 | otherwise = typeOf' val where t1 = typeOf'' val t2 = typeOf''' val {-# NOINLINE typeOf' #-} typeOf'' x = typeOf x {-# NOINLINE typeOf'' #-} typeOf''' x = typeOf x {-# NOINLINE typeOf''' #-} Jean

On Sunday 09 October 2011, 17:51:06, Jean-Marie Gaillourdet wrote:
That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating typeOf?
typeOf' seems to be a working workaround:
typeOf' val | t1 == t2 = t1 | otherwise = typeOf' val where t1 = typeOf'' val t2 = typeOf''' val {-# NOINLINE typeOf' #-}
typeOf'' x = typeOf x {-# NOINLINE typeOf'' #-} typeOf''' x = typeOf x {-# NOINLINE typeOf''' #-}
That'll make it very improbable to get bad results, but not impossible. Thread1: typeOf' (); typeOf'' (), lookup, not there Thread2: typeOf' (); typeOf'' (), lookup, not there Thread1: create and insert; typeOf''' (), entry present, use ~> Key 0 Thread2: create and insert, overwites entry with Key 0, new entry has Key 1; typeOf''' (), entry present, use ~> Key 1 It will probably take a long time until it bites, but when it does, it will hurt. A proper fix would need a lock to ensure only one thread at a time can access the cache.

On 09.10.2011, at 18:13, Daniel Fischer wrote:
On Sunday 09 October 2011, 17:51:06, Jean-Marie Gaillourdet wrote:
That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating typeOf?
typeOf' seems to be a working workaround:
typeOf' val | t1 == t2 = t1 | otherwise = typeOf' val where t1 = typeOf'' val t2 = typeOf''' val {-# NOINLINE typeOf' #-}
typeOf'' x = typeOf x {-# NOINLINE typeOf'' #-} typeOf''' x = typeOf x {-# NOINLINE typeOf''' #-}
That'll make it very improbable to get bad results, but not impossible.
Thread1: typeOf' (); typeOf'' (), lookup, not there Thread2: typeOf' (); typeOf'' (), lookup, not there Thread1: create and insert; typeOf''' (), entry present, use ~> Key 0 Thread2: create and insert, overwites entry with Key 0, new entry has Key 1; typeOf''' (), entry present, use ~> Key 1
It will probably take a long time until it bites, but when it does, it will hurt. A proper fix would need a lock to ensure only one thread at a time can access the cache. Ok, you're right. I tried to avoid the IO monad, but there seems to be no way around it.

Quoting Jean-Marie Gaillourdet
That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating typeOf?
If there's a concurrency bug, surely the workaround is to protect calls to the non-thread-safe function with a lock. typeOfWorkaround lock v = do () <- takeMVar lock x <- evaluate (typeOf v) putMVar lock () return x ~d

On 09.10.2011, at 17:56, wagnerdm@seas.upenn.edu wrote:
Quoting Jean-Marie Gaillourdet
: That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating typeOf?
If there's a concurrency bug, surely the workaround is to protect calls to the non-thread-safe function with a lock.
typeOfWorkaround lock v = do () <- takeMVar lock x <- evaluate (typeOf v) putMVar lock () return x
Yes, but this workaround is in the IO monad while mine is not. Jean

Hi, I've continued my search for a proper workaround. Again, I did find some unexpected results. See below. On 09.10.2011, at 17:56, wagnerdm@seas.upenn.edu wrote:
Quoting Jean-Marie Gaillourdet
: That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating typeOf?
If there's a concurrency bug, surely the workaround is to protect calls to the non-thread-safe function with a lock.
typeOfWorkaround lock v = do () <- takeMVar lock x <- evaluate (typeOf v) putMVar lock () return x
~d
This is my previous program with your workaround, it is also attached as TypeRepEqLock.hs import Control.Concurrent import Control.Exception import Control.Monad import Data.Typeable import System.IO.Unsafe main :: IO () main = do { fin1 <- newEmptyMVar ; fin2 <- newEmptyMVar ; forkIO $ typeOf' () >>= putMVar fin1 ; forkIO $ typeOf' () >>= putMVar fin2 ; t1 <- takeMVar fin1 ; t2 <- takeMVar fin2 ; if (t1 /= t2) then putStrLn $ "typeOf " ++ show t1 ++ " /= typeOf " ++ show t2 else putStrLn "Ok" } {-# NOINLINE lock #-} lock :: MVar () lock = unsafePerformIO $ newMVar () -- Ugly workaround to http://hackage.haskell.org/trac/ghc/ticket/5540 typeOf' :: Typeable a => a -> IO TypeRep typeOf' x = do { () <- takeMVar lock ; t <- evaluate $ typeOf x ; putMVar lock () ; return t } Compile and execute: $ ghc-7.0.3 -threaded -rtsopts TypeRepEqLock.hs <snip> $ while true ; do ./TypeRepEqLock +RTS -N ; done Ok Ok Ok Ok Ok Ok Ok Ok Ok TypeRepEqLock: thread blocked indefinitely in an MVar operation Ok Ok Ok ^C^C I'm sorry but I don't see how this program could ever deadlock, unless there is some more locking in typeOf and (==) on TypeReps. On the other side, my admittedly ugly workaround works fine for hours and hours. 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 ; if (t1 /= t2) then putStrLn $ "typeOf " ++ show t1 ++ " /= typeOf " ++ show t2 else putStrLn "Ok" } typeOf' val | t1 == t2 = t1 | otherwise = typeOf' val where t1 = typeOf'' val t2 = typeOf''' val {-# NOINLINE typeOf' #-} typeOf'' x = typeOf x {-# NOINLINE typeOf'' #-} typeOf''' x = typeOf x {-# NOINLINE typeOf''' #-} $ ghc-7.0.3 -threaded -rtsopts TypeRepEq.hs <snip> $ while true ; do ./TypeRepEq +RTS -N ; done Ok Ok Ok Ok Ok Ok … Any hints how to avoid the "thread blocked indefinitely in an MVar operation" exception? Cheers, Jean

Did you try 7.2? As I mentioned, the issue should have gone away entirely because there is no shared cache any more Simon From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-bounces@haskell.org] On Behalf Of Jean-Marie Gaillourdet Sent: 12 October 2011 07:19 To: wagnerdm@seas.upenn.edu; Daniel Fischer Cc: glasgow-haskell-users@haskell.org Subject: Re: Is this a concurrency bug in base? Hi, I've continued my search for a proper workaround. Again, I did find some unexpected results. See below. On 09.10.2011, at 17:56, wagnerdm@seas.upenn.edu wrote:
Quoting Jean-Marie Gaillourdet
: That sounds plausible. Do you see any workaround? Perhaps repeatedly evaluating typeOf?
If there's a concurrency bug, surely the workaround is to protect calls to the non-thread-safe function with a lock.
typeOfWorkaround lock v = do () <- takeMVar lock x <- evaluate (typeOf v) putMVar lock () return x
~d
This is my previous program with your workaround, it is also attached as TypeRepEqLock.hs import Control.Concurrent import Control.Exception import Control.Monad import Data.Typeable import System.IO.Unsafe main :: IO () main = do { fin1 <- newEmptyMVar ; fin2 <- newEmptyMVar ; forkIO $ typeOf' () >>= putMVar fin1 ; forkIO $ typeOf' () >>= putMVar fin2 ; t1 <- takeMVar fin1 ; t2 <- takeMVar fin2 ; if (t1 /= t2) then putStrLn $ "typeOf " ++ show t1 ++ " /= typeOf " ++ show t2 else putStrLn "Ok" } {-# NOINLINE lock #-} lock :: MVar () lock = unsafePerformIO $ newMVar () -- Ugly workaround to http://hackage.haskell.org/trac/ghc/ticket/5540 typeOf' :: Typeable a => a -> IO TypeRep typeOf' x = do { () <- takeMVar lock ; t <- evaluate $ typeOf x ; putMVar lock () ; return t } Compile and execute: $ ghc-7.0.3 -threaded -rtsopts TypeRepEqLock.hs <snip> $ while true ; do ./TypeRepEqLock +RTS -N ; done Ok Ok Ok Ok Ok Ok Ok Ok Ok TypeRepEqLock: thread blocked indefinitely in an MVar operation Ok Ok Ok ^C^C I'm sorry but I don't see how this program could ever deadlock, unless there is some more locking in typeOf and (==) on TypeReps. On the other side, my admittedly ugly workaround works fine for hours and hours. 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 ; if (t1 /= t2) then putStrLn $ "typeOf " ++ show t1 ++ " /= typeOf " ++ show t2 else putStrLn "Ok" } typeOf' val | t1 == t2 = t1 | otherwise = typeOf' val where t1 = typeOf'' val t2 = typeOf''' val {-# NOINLINE typeOf' #-} typeOf'' x = typeOf x {-# NOINLINE typeOf'' #-} typeOf''' x = typeOf x {-# NOINLINE typeOf''' #-} $ ghc-7.0.3 -threaded -rtsopts TypeRepEq.hs <snip> $ while true ; do ./TypeRepEq +RTS -N ; done Ok Ok Ok Ok Ok Ok … Any hints how to avoid the "thread blocked indefinitely in an MVar operation" exception? Cheers, Jean _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Hi Simon, On 12.10.2011, at 10:34, Simon Peyton-Jones wrote:
Did you try 7.2? As I mentioned, the issue should have gone away entirely because there is no shared cache any more
Yes, I did test it with GHC 7.2. And yes, with GHC 7.2 typeOf is fine. I continued to look into that issue because I am interested in a practically working solution running with GHC 6.12 and 7.0. I am sorry if I didn't make that clear enough. Cheers, Jean

Jean-Marie Gaillourdet wrote:
This is my previous program with your workaround, it is also attached as TypeRepEqLock.hs
[snip]
Compile and execute:
$ ghc-7.0.3 -threaded -rtsopts TypeRepEqLock.hs <snip> $ while true ; do ./TypeRepEqLock +RTS -N ; done Ok Ok Ok Ok Ok Ok Ok Ok Ok TypeRepEqLock: thread blocked indefinitely in an MVar operation Ok Ok Ok ^C^C
This has nothing to do with Data.Typeable though - it appears to be some interaction between unsaferPerformIO and MVars that I do not understand. The following program occasionally terminates with "thread blocked indefinitely in an MVar operation", too (tested on ghc 7.0.3 and 7.2.1): import Control.Concurrent import Control.Exception import Control.Monad import System.IO.Unsafe main :: IO () main = do -- evaluate lock -- adding this line fixes the problem fin1 <- newEmptyMVar fin2 <- newEmptyMVar forkIO $ ping >>= putMVar fin1 forkIO $ ping >>= putMVar fin2 takeMVar fin1 takeMVar fin2 {-# NOINLINE lock #-} lock :: MVar () lock = unsafePerformIO $ newMVar () ping = do () <- takeMVar lock putMVar lock () Since I don't yet understand why this blocks, I cannot say whether it should work or not. Best regards, Bertram

Hi Bertram, On 12.10.2011, at 13:24, Bertram Felgenhauer wrote:
This has nothing to do with Data.Typeable though - it appears to be some interaction between unsaferPerformIO and MVars that I do not understand. The following program occasionally terminates with "thread blocked indefinitely in an MVar operation", too (tested on ghc 7.0.3 and 7.2.1):
import Control.Concurrent import Control.Exception import Control.Monad import System.IO.Unsafe
main :: IO () main = do -- evaluate lock -- adding this line fixes the problem
fin1 <- newEmptyMVar fin2 <- newEmptyMVar
forkIO $ ping >>= putMVar fin1 forkIO $ ping >>= putMVar fin2
takeMVar fin1 takeMVar fin2
{-# NOINLINE lock #-} lock :: MVar () lock = unsafePerformIO $ newMVar ()
ping = do () <- takeMVar lock putMVar lock ()
Since I don't yet understand why this blocks, I cannot say whether it should work or not.
I've seen blocks with GHC 6.12.1, but I never got one with 7.0.3 and 7.2.1. Probably, bad luck on my side. ;-) Cheers, Jean

On 12/10/2011 12:24, Bertram Felgenhauer wrote:
Jean-Marie Gaillourdet wrote:
This is my previous program with your workaround, it is also attached as TypeRepEqLock.hs
[snip]
Compile and execute:
$ ghc-7.0.3 -threaded -rtsopts TypeRepEqLock.hs <snip> $ while true ; do ./TypeRepEqLock +RTS -N ; done Ok Ok Ok Ok Ok Ok Ok Ok Ok TypeRepEqLock: thread blocked indefinitely in an MVar operation Ok Ok Ok ^C^C
This has nothing to do with Data.Typeable though - it appears to be some interaction between unsaferPerformIO and MVars that I do not understand. The following program occasionally terminates with "thread blocked indefinitely in an MVar operation", too (tested on ghc 7.0.3 and 7.2.1):
import Control.Concurrent import Control.Exception import Control.Monad import System.IO.Unsafe
main :: IO () main = do -- evaluate lock -- adding this line fixes the problem
fin1<- newEmptyMVar fin2<- newEmptyMVar
forkIO $ ping>>= putMVar fin1 forkIO $ ping>>= putMVar fin2
takeMVar fin1 takeMVar fin2
{-# NOINLINE lock #-} lock :: MVar () lock = unsafePerformIO $ newMVar ()
ping = do ()<- takeMVar lock putMVar lock ()
Since I don't yet understand why this blocks, I cannot say whether it should work or not.
I think it should work. Could you make a ticket for it please? Cheers, Simon

Simon Marlow wrote:
import Control.Concurrent import Control.Exception import Control.Monad import System.IO.Unsafe
main :: IO () main = do -- evaluate lock -- adding this line fixes the problem
fin1<- newEmptyMVar fin2<- newEmptyMVar
forkIO $ ping>>= putMVar fin1 forkIO $ ping>>= putMVar fin2
takeMVar fin1 takeMVar fin2
{-# NOINLINE lock #-} lock :: MVar () lock = unsafePerformIO $ newMVar ()
ping = do ()<- takeMVar lock putMVar lock ()
Since I don't yet understand why this blocks, I cannot say whether it should work or not.
I think it should work. Could you make a ticket for it please?
http://hackage.haskell.org/trac/ghc/ticket/5558 It occurred to me that normally, MVars will always be fully evaluated, since they are supposedly created by a previous IO action. This property is violated in this program. Perhaps that's the reason? Bertram

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

Thank you for the detailed investigation. I have not followed all the details of this thread, but I think that it may (happily) represent a bug in generating TypeReps that is already fixed. · We used to have a global cache from which we generated unique Int keys corresponding to type constructors. The trouble with this was that (a) you weren’t guaranteed to get the same key in every run, and (b) the cache was not initially designed to be thread-safe, and I’m not sure that we’d closed all race conditions. · But NOW we generate a MD5 hash, or fingerprint, of the type. So there is no global cache, no race condition, and you should get the same behaviour ever time. In short, can you try with 7.2? Thanks Simon From: glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-bounces@haskell.org] On Behalf Of Jean-Marie Gaillourdet Sent: 09 October 2011 12:53 To: glasgow-haskell-users Subject: Is this a concurrency bug in base? Hi, I am working on a library I'd like to release to hackage very soon, but I've found a problem with supporting GHC 6.12 and GHC 7.0. Consider the following program: import Control.Concurrent import Data.Typeable main :: IO () main = do { fin1 <- newEmptyMVar ; fin2 <- newEmptyMVar ; forkIO $ typeRepKey (typeOf ()) >>= print >> putMVar fin1 () ; forkIO $ typeRepKey (typeOf ()) >>= print >> putMVar fin2 () ; () <- takeMVar fin1 ; () <- takeMVar fin2 ; putStrLn "---" ; return () } When compiled with GHC 7.0.x or GHC 6.12.x, it should print two identical numbers. Sometimes it does not. To reproduce this compile and execute as follows: $ ghc-7.0.3 -rtsopts -threaded TypeRepKey.hs -o TypeRepKey $ while true ; do ./TypeRepKey +RTS -N ; done 0 0 --- 0 0 --- 0 0 --- 0 1 --- 0 0 --- … Ideally you should get an infinite number of zeros but once in a while you have a single(!) one in between. The two numbers of one program run should be identical, but their values may be arbitrary. But it should not be possible to have single outliers. This only happens when executed with more than one thread. I've also a somewhat larger program which seems to indicate that fromDynamic fails occasionally. I can post it as well if it helps. 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. All this was done on several Macs running the latest OS X Lion with ghc 7.0.3 from the binary distribution on the GHC download page. Actually, I am trying to find a method to use a "type" as key in a map which works before GHC 7.2. I'd be glad to get any ideas on how to achieve that, given that typeRepKey seems to buggy. I'd be happy to get any comments on this matter. Regards, Jean _______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

On 10/10/2011 09:04, Simon Peyton-Jones wrote:
Thank you for the detailed investigation. I have not followed all the details of this thread, but I *think* that it may (happily) represent a bug in generating TypeReps that is already fixed.
·We used to have a global cache from which we generated unique Int keys corresponding to type constructors. The trouble with this was that (a) you weren’t guaranteed to get the same key in every run, and (b) the cache was not initially designed to be thread-safe, and I’m not sure that we’d closed all race conditions.
Indeed, I don't think we closed *any* race conditions. The code looks completely unthreadsafe to me. There's a non-atomic lookup and update in the cache, and a non-atomic genSym to get new keys. It's pretty bad that we didn't notice this or fix it earlier. Sorry about the bug. As Simon said, 7.2 and later should fix it. Cheers, Simon
·But NOW we generate a MD5 hash, or fingerprint, of the type. So there is no global cache, no race condition, and you should get the same behaviour ever time.
In short, can you try with 7.2?
Thanks
Simon
*From:*glasgow-haskell-users-bounces@haskell.org [mailto:glasgow-haskell-users-bounces@haskell.org] *On Behalf Of *Jean-Marie Gaillourdet *Sent:* 09 October 2011 12:53 *To:* glasgow-haskell-users *Subject:* Is this a concurrency bug in base?
Hi,
I am working on a library I'd like to release to hackage very soon, but I've found a problem with supporting GHC 6.12 and GHC 7.0. Consider the following program:
import Control.Concurrent import Data.Typeable
main :: IO () main = do { fin1 <- newEmptyMVar ; fin2 <- newEmptyMVar
; forkIO $ typeRepKey (typeOf ()) >>= print >> putMVar fin1 () ; forkIO $ typeRepKey (typeOf ()) >>= print >> putMVar fin2 ()
; () <- takeMVar fin1 ; () <- takeMVar fin2 ; putStrLn "---" ; return () }
When compiled with GHC 7.0.x or GHC 6.12.x, it should print two identical numbers. Sometimes it does not. To reproduce this compile and execute as follows:
$ ghc-7.0.3 -rtsopts -threaded TypeRepKey.hs -o TypeRepKey $ while true ; do ./TypeRepKey +RTS -N ; done 0 0 --- 0 0 --- 0 0 --- 0 1 --- 0 0 --- …
Ideally you should get an infinite number of zeros but once in a while you have a single(!) one in between. The two numbers of one program run should be identical, but their values may be arbitrary. But it should not be possible to have single outliers.
This only happens when executed with more than one thread. I've also a somewhat larger program which seems to indicate that fromDynamic fails occasionally. I can post it as well if it helps. 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.
All this was done on several Macs running the latest OS X Lion with ghc 7.0.3 from the binary distribution on the GHC download page.
Actually, I am trying to find a method to use a "type" as key in a map which works before GHC 7.2. I'd be glad to get any ideas on how to achieve that, given that typeRepKey seems to buggy.
I'd be happy to get any comments on this matter.
Regards, Jean
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
_______________________________________________ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
participants (7)
-
Bertram Felgenhauer
-
Daniel Fischer
-
David Brown
-
Jean-Marie Gaillourdet
-
Simon Marlow
-
Simon Peyton-Jones
-
wagnerdm@seas.upenn.edu