Why hIsEOF wait for completely full buffer while hGetChar doesn't ?

Simon Marlow simonmar at microsoft.com
Fri May 27 15:32:35 EDT 2005


On 27 May 2005 03:33, Nobuo Yamashita wrote:

> I am curious about reason why in GHC hIsEOF blocks in BlockBuffering
> mode while hGetChar doesn't.
> 
> I wrote following three programs for an experiment.
> 
>   -- echo0.hs
>   module Main where
>   import System.IO
>   main = hSetBuffering stdin (BlockBuffering (Just 5)) >> echo
>   echo = getChar >>= putChar >> hFlush stdout >> echo
> 
>   -- echo1.hs
>   module Main where
>   import System.IO
>   main = hSetBuffering stdin (BlockBuffering (Just 5)) >> echo
>   echo = do eof <- isEOF
>             if eof then return ()
>             else getChar >>= putChar >> hFlush stdout >> echo
> 
>   -- as.hs
>   module Main where
>   import System.IO
>   import Control.Concurrent
>   main = putChar 'a' >> hFlush stdour >> threadDelay 1000000 >> main
> 
> And run next two commandlines
> 
> % runghc as.hs | runghc echo0.hs
> % runghc as.hs | runghc echo1.hs
> 
> I had expected that the both behaviors were same; a character
> was output a second. But the former output a character a second, and
> the latter output 5 characters a time every 5 seconds.

Quite right, that's a bug, or at least an inconsistency.  hGetChar used
to wait for a completely full buffer before returning a character, but
we changed it to return as soon as any data at all was available.
However, we didn't change hIsEOF to match: it still waits for a
completely full buffer.  I've now fixed this.

As it turns out, BlockBuffering doesn't really do full block buffering
on an input Handle.  The BlockBuffering size does specify the maximum
amount of buffering performed, but all read operations return as soon as
the required amount of data is available, without waiting for the buffer
to completely fill up.  This seems a lot more useful than strict block
buffering.

Thanks for a well-researched bug report!

Cheers,
	Simon


More information about the Glasgow-haskell-users mailing list