
#11508: QuickCheck application hangs with concurrent read/write of Chan -------------------------------------+------------------------------------- Reporter: orion | Owner: Type: bug | Status: infoneeded Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: x86_64 | (amd64) Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): If I change the program so that it no longer runs the tests via QuickCheck as follows: {{{ {-# LANGUAGE OverloadedStrings, CPP #-} module Main where import Imports import Control.Concurrent import Control.Concurrent.Async import Data.ByteString instance Arbitrary ByteString where arbitrary = pack <$> arbitrary doFoo :: Bool -> Int -> ByteString -> (ByteString -> IO ()) -> (IO ByteString) -> IO ByteString doFoo _ 0 g _ _ = return g doFoo b i g w r = if b then do w g doFoo False (i-1) g w r else do f <- r doFoo True (i-1) f w r prop :: ByteString -> IO Bool prop x = do chan <- newChan let w s = writeChan chan s r = readChan chan (y, z) <- concurrently (doFoo True 10 x w r) (doFoo False 10 x w r) return $ y == z main :: IO () main = print =<< prop "Hello" }}} then when the program runs it terminates with: {{{ properties: thread blocked indefinitely in an MVar operation }}} Interestingly, it does that regardless of whether the program is compiled with `-threaded` or not. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11508#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler