Hi

I try to write a program that reads from a socket and communicates
the result over a TChan and writes it to stdout. Somehow I can't seem to get it right,
the result is only printed when I send ETX on the socket.

Attached is a sample program that shows the behvaviour.

Any hints on where my error is or how I could debug such a problem is appreciated.

regards

Stefan
import IO
import Control.Concurrent
import Control.Concurrent.STM
import Network
import System.Posix.Unistd

readIfReady False _ _ = return ()
readIfReady True h chan = do
	line <- hGetLine h
	atomically (writeTChan chan (line))

readFromHandle h chan = do
	ready <- hReady h
	readIfReady ready h chan
	usleep 1000
	readFromHandle h chan

writeFromChan rchan = do
	line <- atomically (readTChan rchan)
	hPutStr stdout (line ++ "\n")
	hFlush stdout
	writeFromChan rchan

acceptConnection sock = do
	(h, hostname, port) <- accept sock
	hSetBuffering h NoBuffering

	wchan <- atomically newTChan
	rchan <- atomically (dupTChan wchan)
	forkIO (readFromHandle h wchan)
	forkIO (writeFromChan rchan)
	acceptConnection sock

run = do
	sock <- listenOn (PortNumber (fromIntegral 1080))
	acceptConnection sock

main = do withSocketsDo $ run



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

Reply via email to