[Haskell-cafe] How to flush with IterIO in echo server

dm-list-haskell-cafe at scs.stanford.edu dm-list-haskell-cafe at scs.stanford.edu
Wed Jun 29 19:29:35 CEST 2011


At Wed, 29 Jun 2011 21:13:47 +1000,
John Ky wrote:
> 
> Hi Haskell Cafe,
> 
> I've written an echo server using just sockets:
> 
> ...
> 
> When I send text to it, it will echo it back immediately after my newline.
> 
> I then modified it to user IterIO:
> 
>     import Control.Concurrent
>     import Control.Exception
>     import Control.Monad
>     import Control.Monad.Trans
>     import Data.IterIO
>     import Data.IterIO.Inum
>     import Network
>     import System.IO
>     import System.IO.Error (isEOFError)
>     import qualified Data.ByteString.Lazy as L
>    
>     iterHandle' :: (MonadIO m) => Handle -> IO (Iter L.ByteString m (), Onum
>     L.ByteString m a)
>     iterHandle' = iterHandle
>    
>     main = withSocketsDo $ do
>       sListen <- listenOn (PortNumber 8000)
>       putStrLn "Listening on Port 8000"
>       forkIO $ forever $ do
>         (sSession, hostname, port) <- accept sListen
>         putStrLn ("Connected to " ++ hostname ++ ":" ++ show port)
>         forkIO $ do
>           (iter, enum) <- iterHandle' sSession
>           enum |$ iter
>           return ()
>       putStrLn "Press <CTRL-D> to quit."
>       exitOnCtrlD
>    
>     exitOnCtrlD = try getLine >>= either
>       (\e -> unless (isEOFError e) $ ioError e)
>       (const exitOnCtrlD)
> 
> It works, however it doesn't send anything back to me until end of file.
> 
> I fixed that problem with my sockets version by flushing after each line, but
> I don't know if IterIO will let me flush on every newline.

The buffering is actually happening in the Handle code.  One way to
avoid this is to change your code to call hSetBuffering as follows:

      hSetBuffering sSession NoBuffering
      (iter, enum) <- iterHandle' sSession

This is mentioned in the documentation of handleI, but arguably should
also be there in the docs for iterHandle.  I think I'll add a mention
there.

If you use Sockets and call iterStream, that should also avoid the
problem.

David



More information about the Haskell-Cafe mailing list