Why hIsEOF wait for completely full buffer while hGetChar doesn't ?
Nobuo Yamashita
nobsun at sampou.org
Thu May 26 22:32:58 EDT 2005
Hello,
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.
Are there any explanations ?
Best regards.
--
Nobuo Yamashita
More information about the Glasgow-haskell-users
mailing list