[GHC] #9965: getChanContents BlockedIndefinitelyOnMVar on 7.10 RC1
GHC
ghc-devs at haskell.org
Thu Jan 8 00:02:03 UTC 2015
#9965: getChanContents BlockedIndefinitelyOnMVar on 7.10 RC1
-------------------------------------+-------------------------------------
Reporter: jberryman | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: | Version: 7.10.1-rc1
libraries/base | Operating System: Unknown/Multiple
Keywords: | Type of failure: Incorrect result
Architecture: | at runtime
Unknown/Multiple | Blocked By:
Test Case: | Related Tickets:
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
All of the stanzas work on 7.8.3, but the middle one works incorrectly on
7.10:
{{{#!hs
module Main where
import Control.Concurrent.Chan
import Control.Monad
main = do
io <- newChan
let inp = [0] :: [Int]
mapM_ (writeChan io) inp
{-
-- WORKS:
outp <- getChanContents io
if 0 == head outp
then putStrLn "OK"
else error $ "Smoke test failed"
-}
-- BROKEN ON 7.10 (BlockedIndefinitelyOnMVar):
outp <- getChanContents io
if and (zipWith (==) inp outp)
then putStrLn "OK"
else error $ "Smoke test failed"
{-
-- WORKS:
forM_ inp $ \xIn-> do
xOut <- readChan io
unless (xIn == xOut) $
error $ "Smoke test failed"
-}
}}}
I first noticed the behavior in a Chan-like library I wrote, whose
internals are completely different from Chan, but where the
getChanContents is a copy-paste from Chan. So I assume it has something to
do with `unsafeInterleaveIO`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9965>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list