[GHC] #8298: +RTS -hb crash when blocking on empty TChan

GHC ghc-devs at haskell.org
Sat Sep 14 16:34:27 CEST 2013


#8298: +RTS -hb crash when blocking on empty TChan
------------------------------------------------+--------------------------
       Reporter:  exFalso                       |             Owner:
           Type:  bug                           |            Status:  new
       Priority:  normal                        |         Milestone:
      Component:  Runtime System                |           Version:  7.6.3
       Keywords:  biographical stm tchan block  |  Operating System:  Linux
   Architecture:  x86_64 (amd64)                |   Type of failure:
     Difficulty:  Unknown                       |  Runtime crash
     Blocked By:                                |         Test Case:
Related Tickets:                                |          Blocking:
------------------------------------------------+--------------------------
 Running the following code

 {{{
 module Main where

 import Control.Concurrent
 import Control.Concurrent.STM

 main :: IO ()
 main = do
   c <- newTChanIO
   forkIO . atomically $ readTChan c
   return ()
 }}}

 produces:

 {{{
 $ ./tmp +RTS -hb
 tmp: internal error: Invalid object in processHeapClosureForDead(): 0
     (GHC version 7.6.3 for x86_64_unknown_linux)
 }}}

 It crashes without forkIO as well, I inserted it so that a plain run
 doesn't result in "thread blocked indefinitely in an STM transaction".

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8298>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler



More information about the ghc-tickets mailing list