Hi,

For GHC (6.0.1)

"main=interact id" basically echoes every line of my input, whereas
"main=interact show" correctly waits for EOF before outputting something.

Furthermore the buffering mode must be "LineBuffering".

If I explicitely set the buffering to "NoBuffering" I'm not able to enter EOF by typing "ctrl-d". Furthermore my terminal seems to remain in the buffering mode set by the previously called ghc-haskell program (because it effects programs that do not "hSetBuffering".)

With "runhugs" (Nov 2002) there is no premature output for "interact id", the buffering mode does not matter, but "ctrl-d" is not recognized as EOF.

NHC98 does not even wait for a line break before outputting the result (and echoes "\EOT" for "ctrl-d").

What should a student think about "interact" in the Prelude? (It's ok for pipes only, I guess.)

Christian

module Main where

import System.IO

main = do hSetBuffering stdin NoBuffering
          interact id

--
[EMAIL PROTECTED]:~/haskell/examples> bash --version
GNU bash, version 2.05b.0(1)-release (i586-suse-linux)
Copyright (C) 2002 Free Software Foundation, Inc.
[EMAIL PROTECTED]:~/haskell/examples> ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.0.1
[EMAIL PROTECTED]:~/haskell/examples> ghc --make Interact.hs -o interact
Chasing modules from: Interact.hs
Compiling Main             ( Interact.hs, ./Interact.o )
Linking ...
[EMAIL PROTECTED]:~/haskell/examples> ./interact
1
1
2
2
3
3
^D^D^D
ccc
interact: interrupted

_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to