[GHC] #15312: getChanContents exception behavior seems a bit odd
GHC
ghc-devs at haskell.org
Tue Jun 26 04:09:24 UTC 2018
#15312: getChanContents exception behavior seems a bit odd
-------------------------------------+-------------------------------------
Reporter: dfeuer | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone: 8.6.1
Component: Core | Version: 8.4.3
Libraries |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect result
Unknown/Multiple | at runtime
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
I've been playing around with `Control.Concurrent.Chan` today. Something
seems a bit off:
{{{#!hs
-- Bug.hs
import Control.Concurrent (forkIO, yield)
import Control.Concurrent.Chan
import Data.List (elem)
import Control.Exception
import Control.Concurrent.MVar
data Ex = Ex deriving Show
instance Exception Ex
main = do
ch <- newChan
sync1 <- newEmptyMVar
sync2 <- newEmptyMVar
forkIO $ do {writeList2Chan ch [1..3*10^6 :: Int]; putMVar sync1 ()}
yield
writeChan ch (-12)
cont <- getChanContents ch
tid <- forkIO $ do
evaluate (last cont)
putMVar sync2 ()
yield
throwTo tid Ex
print (elem (3*10^6) cont)
takeMVar sync1
tryTakeMVar sync2
}}}
When I run this single-threaded (`+RTS -N1`), it prints
{{{
Bug: Ex
Bug: Ex
}}}
One of the thunks in the lazy list gets overwritten by the (asynchronous)
exception. This seems a bit surprising; is it the way it should be? Does
`hGetContents` do this too?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15312>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list