[Haskell-cafe] why isn't the thread blocked?
Changying Li
lchangying at gmail.com
Sat Aug 16 12:22:35 EDT 2008
I writed a little program to test forkIO. in fact, I want to know how to
implement the 'select' system call in haskell:
module Main where
import Control.Concurrent.Chan
import Control.Concurrent
import System.IO
main = do
chan <- newChan
handles <- mapM ((flip openFile) ReadMode) ["/tmp/a","/tmp/b","/tmp/c"]
let readF h = do
myID <- myThreadId
chan' <- dupChan chan
char <- hGetChar h
writeChan chan' $ show myID
putStrLn [char]
threads <- mapM (\h -> forkIO $ readF h) handles
nr <- readChan chan
mapM killThread $ filter (\x -> show x == nr ) threads
putStrLn nr
I first mkfifo /tmp/{a,b,c} , then run 'echo "hello" >/tmp/a', then
'runhaskell thisProgram.hs'
but I got an error:
test.hs: /tmp/b: hGetChar: end of file
test.hs: /tmp/c: hGetChar: end of file
I think the thread will be blocked when /tmp/b has nothing.
but it get EOF, why ?
--
Thanks & Regards
Changying Li
More information about the Haskell-Cafe
mailing list