According with the philosophy of STM, readTChan does not block, but retries:

readTChan :: TChan a -> STM a
readTChan (TChan read _write) = do
  listhead <- readTVar read
  head <- readTVar listhead
  case head of
    TNil -> retry
    TCons a tail -> do
	writeTVar read tail
	return a
This retry forces the execution of the whole atomic block, so it do readTVar again, readTVar suppossedly "wait" without locking as well, until new data is available. Because it is True, the atomic block terminates. 

The readTVar behaviour is not clear form me,  althoug it is convenient. Otherwise any atomic block with readTVar and retries would loop continuously.

So I think that this execution is convenient, if not correct

2009/10/24 Paolino <paolo.veronelli@gmail.com>
I have a doubt that this code works like I want because actual STM
implementation exposes its effects

import Control.Concurrent
import Control.Concurrent.STM

main = do
    c <- atomically $ newTChan :: IO (TChan ())
    r <- atomically $ newTVar False
    forkIO $ do
        atomically $ do
            r0 <- readTVar r
            case r0 of
                True -> return ()
                False -> readTChan c
        myThreadId >>= killThread
    threadDelay 1000000
    atomically (writeTVar r True)

The thread stops on readTChan, but exits when I change the TVar, which
happens before the readTChan.

Should I trust this is the correct STM behaviour , and will not change
in different implementations ?

thanks

paolino
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe