
Hello Cafe, Here is a simple program that yields strange results: module Main where import Control.Concurrent import Control.Concurrent.Chan import Control.Monad main = do c <- newChan writeChan c 1 forkIO $ forever $ do i <- readChan c print ("forkio",i) isEmptyChan c >>= print First of all, if we try to run it via runhaskell, it will hang: runhaskell deadlock.hs ("forkio",1) -- no more output -- Compiled version OTOH behaves differently dependent on compilation flags. Without -threaded: ./deadlock ("forkio",1) False With -threaded: ./deadlock False Now, this is strange thing: we put single element into the channel. We take it out. And then we see the channel isn't really empty. Perhaps there is a race condition here? So we put an delay, so that we will be sure the check for empty channel occurs 1 second later than the channel is emptied. import Control.Concurrent import Control.Concurrent.Chan import Control.Monad main = do c <- newChan writeChan c 1 forkIO $ forever $ do i <- readChan c print ("forkio",i) threadDelay 1000000 isEmptyChan c >>= print This program will misbehave. Invariably of -threaded flag it will go like this: ./deadlock ("forkio",1) deadlock: thread blocked indefinitely in an MVar operation I have no idea what is the problem here. Perhaps I'm not using the library in the right way. Does anyone has any idea what's going on here? Best regards, Krzysztof Skrzętnicki

Shame on me, I forgot to include the software versions I use:
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.12.3
$ uname -a
Linux raptor 2.6.37-ARCH #1 SMP PREEMPT Sat Jan 29 20:00:33 CET 2011 x86_64
Intel(R) Core(TM) i7 CPU 870 @ 2.93GHz GenuineIntel GNU/Linux
This is a normal Arch Linux setup with GHC installed via pacman.
Best regards,
Krzysztof Skrzętnicki
2011/2/9 Krzysztof Skrzętnicki
Hello Cafe,
Here is a simple program that yields strange results:
module Main where
import Control.Concurrent import Control.Concurrent.Chan import Control.Monad
main = do c <- newChan writeChan c 1 forkIO $ forever $ do i <- readChan c print ("forkio",i) isEmptyChan c >>= print
First of all, if we try to run it via runhaskell, it will hang:
runhaskell deadlock.hs ("forkio",1) -- no more output --
Compiled version OTOH behaves differently dependent on compilation flags. Without -threaded: ./deadlock ("forkio",1) False
With -threaded: ./deadlock False
Now, this is strange thing: we put single element into the channel. We take it out. And then we see the channel isn't really empty. Perhaps there is a race condition here? So we put an delay, so that we will be sure the check for empty channel occurs 1 second later than the channel is emptied.
import Control.Concurrent import Control.Concurrent.Chan import Control.Monad
main = do c <- newChan writeChan c 1 forkIO $ forever $ do i <- readChan c print ("forkio",i) threadDelay 1000000 isEmptyChan c >>= print
This program will misbehave. Invariably of -threaded flag it will go like this:
./deadlock ("forkio",1) deadlock: thread blocked indefinitely in an MVar operation
I have no idea what is the problem here. Perhaps I'm not using the library in the right way. Does anyone has any idea what's going on here?
Best regards, Krzysztof Skrzętnicki

On 09/02/11 15:34, Krzysztof Skrzętnicki wrote:
Hello Cafe,
Here is a simple program that yields strange results:
module Main where
import Control.Concurrent import Control.Concurrent.Chan import Control.Monad
main = do c <- newChan writeChan c 1 forkIO $ forever $ do i <- readChan c print ("forkio",i) isEmptyChan c >>= print
Now, this is strange thing: we put single element into the channel. We take it out.
What your program does is put a single element into the channel, and then *repeatedly* try to take one out (notice the forever you have in there!). Judging by the results, the program deadlocks, which seems like a reasonable outcome to me. Thanks, Neil.

You've been bitten by the following bug:
http://hackage.haskell.org/trac/ghc/ticket/4154
In short, isEmptyChan will block because of the concurrent call to readChan.
The "solution" is to not use isEmptyChan or switch to STM.
2011/2/9 Krzysztof Skrzętnicki
Hello Cafe,
Here is a simple program that yields strange results:
module Main where
import Control.Concurrent import Control.Concurrent.Chan import Control.Monad
main = do c <- newChan writeChan c 1 forkIO $ forever $ do i <- readChan c print ("forkio",i) isEmptyChan c >>= print
First of all, if we try to run it via runhaskell, it will hang:
runhaskell deadlock.hs ("forkio",1) -- no more output --
Compiled version OTOH behaves differently dependent on compilation flags. Without -threaded: ./deadlock ("forkio",1) False
With -threaded: ./deadlock False
Now, this is strange thing: we put single element into the channel. We take it out. And then we see the channel isn't really empty. Perhaps there is a race condition here? So we put an delay, so that we will be sure the check for empty channel occurs 1 second later than the channel is emptied.
import Control.Concurrent import Control.Concurrent.Chan import Control.Monad
main = do c <- newChan writeChan c 1 forkIO $ forever $ do i <- readChan c print ("forkio",i) threadDelay 1000000 isEmptyChan c >>= print
This program will misbehave. Invariably of -threaded flag it will go like this:
./deadlock ("forkio",1) deadlock: thread blocked indefinitely in an MVar operation
I have no idea what is the problem here. Perhaps I'm not using the library in the right way. Does anyone has any idea what's going on here?
Best regards, Krzysztof Skrzętnicki
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Holger Reinhardt
-
Krzysztof Skrzętnicki
-
Neil Brown