[GHC] #367: Infinite loops can hang Concurrent Haskell

GHC ghc-devs at haskell.org
Tue Sep 2 03:01:31 UTC 2014


#367: Infinite loops can hang Concurrent Haskell
-------------------------------------+-------------------------------------
              Reporter:  simonpj     |            Owner:  ezyang
                  Type:  bug         |           Status:  new
              Priority:  lowest      |        Milestone:  ⊥
             Component:  Compiler    |          Version:  6.4.1
            Resolution:  None        |         Keywords:  scheduler
      Operating System:              |  allocation
  Unknown/Multiple                   |     Architecture:  Unknown/Multiple
       Type of failure:  Incorrect   |       Difficulty:  Unknown
  result at runtime                  |       Blocked By:
             Test Case:              |  Related Tickets:
  concurrent/should_run/T367,        |
  concurrent/should_run/T367_letnoescape|
              Blocking:              |
Differential Revisions:              |
-------------------------------------+-------------------------------------

Comment (by jberryman):

 As a user I'm having trouble understanding if the bug being discussed is
 the one reported. To be clear, is the following (very similar to #8521) an
 instance of this bug? Compiled with ghc 7.8.3 with `-O2 -threaded`, run
 with `+RTS -N` on a machine with two real cores.


 {{{
 module Main
     where

 import Data.IORef
 import Control.Concurrent

 main = do
     r <- newIORef False
     putStrLn "About to fork"

     forkIO $ f r
     threadDelay 1000000 -- 1 second

     putStrLn "Why is this never printed?!"
     writeIORef r True
     -- and why do we never exit?

 f :: IORef Bool -> IO ()
 f r = readIORef r >>= \b-> if b then print "Done" else f r
 }}}

 This wouldn't seem to have anything to do with whether `f`'s thread can be
 pre-empted or not, which is why I'm unsure.

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


More information about the ghc-tickets mailing list