[Haskell-cafe] Simple network client

Mads Lindstrøm mads_lindstroem at yahoo.dk
Tue Jan 29 08:44:42 EST 2008


Hi

Timo B. Hübel wrote:
> Hello,
> 
> I am using the very simple interactTCP example from [1] to play around with 
> Haskell network programming but I just can't get a simple client for that 
> example to work (it works like a charm with my telnet client, as described in 
> the article). 
> 
> This is what I am trying to do with the client:
> 
>   main = withSocketsDo $ do
>          hdl <- connectTo "localhost" (PortNumber 1234)
>          hSetBuffering hdl NoBuffering
>          hPutStr hdl "test message"
>          res <- hGetContents hdl
>          putStrLn (show res)

If you replace the `putStrLn (show res)` with this:

  mapM_ (\x -> putStr (show x) >> hFlush stdout) res

it works.

I _think_ the problem is that `putStrLn  (show res)` will wait until it
has read all of res. But as the client do not know when the server is
finished sending data, the client will wait forever.



Greetings,

Mads Lindstrøm

> 
> The server looks like this:
> 
>   interactTCP :: Int -> (String -> IO String) -> IO ()
>   interactTCP port f = withSocketsDo $ do
>           servSock <- listenOn $ PortNumber (fromIntegral port)
>           waitLoop f servSock
> 
>   waitLoop f servSock = do
>           bracket (fmap (\(h,_,_)->h) $ accept servSock)
>                   hClose
>                   (\h -> do
>                           hSetBuffering h NoBuffering
>                           hGetContents h >>= f >>= hPutStr h)
>           waitLoop f servSock
> 
>   main = interactTCP 1234 (return . map toUpper)
> 
> But is seems as some deadlocking occurs. Both programs just hang around doing 
> nothing. By inserting some debug output I was able to make sure that the 
> client successfully connects, but the data interchange just does not start. 
> Because the whole thing works using telnet, I suspect that I am doing 
> something fundamentally wrong in the client ...
> 
> Any hints are greatly appreciated.
> 
> Thanks,
> Timo
> 
> [1] 
> http://stephan.walter.name/blog/computers/programming/haskell/interacttcp.html
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list