[Haskell] Waiting on multiple Chan-nels

Setzer, Sebastian (ext) sebastian.setzer.ext at siemens.com
Tue Dec 12 13:47:51 EST 2006


Hi,
How do you wait on multiple channels, but read only from one of them
(the first that gets an entry)? Is there a library-function I missed
which already does this?

What do you think of this solution?

Sebastian Setzer
--------------------------------------------------------------

-- ghc chantest.hs -o chantest
-- Usage: Enter "1", "2" or "0" to exit.
import System.IO
import Control.Concurrent
import Control.Concurrent.Chan

main :: IO()
main = do
	chan1 <- newChan
	chan2 <- newChan
	c1Thread <- forkIO (printChan "c1" chan1)
	c2Thread <- forkIO (printChan "c2" chan2)
	c12Thread <- forkIO (printChannels "c12" [chan1, chan2])
	mainloop chan1 chan2

mainloop :: Chan String -> Chan String -> IO ()
mainloop  chan1 chan2 = do
		c <- getChar
		command  c
	where -- chan1 and chan2 are in scope, here.
		go_on :: IO()
		go_on = mainloop chan1 chan2 			
		
		command :: Char -> IO()
		command '0' = do
			print "done"
		command '1' = do
			writeChan chan1 "main: 1"
			go_on
		command '2' = do
			writeChan chan2 "main: 2"
			go_on
		command '\n' = do -- ignore
			go_on
		command c = do
			print ("illegal: " ++ [c])
			go_on

-- return microseconds
seconds :: Int -> Int
seconds = (* 1000000)

printChan :: String -> (Chan String) -> IO()
printChan name chan = do
	-- threadDelay (seconds 3)
	-- print (name ++ " ready")
	s <- readChan chan
	printString name s
	printChan name chan

printChannels :: String -> [Chan String] -> IO()
printChannels name channels = do
	-- select (zip channels (repeat (printString name)))
	select $ zip channels $ repeat $ printString name
	printChannels name channels
	
printString :: String -> String -> IO ()
printString name s = print (name ++ ": " ++ s)

select :: [(Chan a, a -> IO())] -> IO ()
select channel_handler_pairs = do
	threadDelay (seconds 3)
	print "TODO: implement select"
{-
	TODO: implement select.
	- create MVar
	- For each element of the channel_handler_pairs - list, fork a
thread.
	- wait on an MVar for the signal "I'm done"
	- kill all helper threads (just to free the resources. They
wouldn't do
	  any harm)
	In the helper-threads:
	- readChan
	- try to signal "I'm ready" on the MVar.
	  If another thread was faster, unGetChan and exit
	- call the handler
	- signal "I'm done" and exit
	
	Problems:
	- If the Thread gets killed between readChan and unGetChan, the
message is lost.
	- if another thread reads between readChan and unGetChan,
	  its no fifo anymore (unlikely, because why would you want to
read with
	  multiple threads on the same Chan? - You'd use dupChan for
that
	  purpose. Unless you want every "event" to be handled only
once.
	  But then you would'nt use multiple threads, would you?)
	- "a" must be the same for every channel-handler-pair
	  Thats easy: instead of channel-handler-tuples, put functions
	  MVar -> IO() into the list and provide a nice-looking operator
	  to create them
	- Probably inefficient (lots of helper threads)
-}


More information about the Haskell mailing list