I recently upgraded to ghc 7.0.2 from 6.12.3, along with the Haskell
platform, and noticed that the following code no longer works as expected:

waitFor tvar = atomically $ do
    count <- readTVar tvar
    check (count == 0)

worker tchan tvar = loop
   where loop = do
           putStrLn "checking"
           finished <- atomically $ isEmptyTChan tchan
           threadDelay 50000
           if finished
              then atomically $ do val <- readTVar tvar
                                   writeTVar tvar $ (subtract 1) val
              else (atomically $ readTChan tchan) >> loop

test = do
  tchan <- newTChanIO
  pure $ forM_ [1..5] $ writeTChan tchan -- THIS LINE
  tvar <- newTVarIO 1
  forkIO $ worker tchan tvar
  waitFor tvar
  putStrLn "DONE"

This will work if I use atomically, but otherwise it does nothing, tchan
remains empty afterwards.
I'm not clear how this should behave.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to