"interact" behaves oddly if used interactively

Marc A. Ziegert coeus at gmx.de
Wed Oct 1 13:53:20 EDT 2003


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

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


main = interact show
behaves similar to
main = interact (\x->seq (length x) x)


i do not know the exact implementation, but i think of it like ...


import System.IO        (hGetContents,hIsEOF,hGetChar,stdin)
import System.IO.Unsafe (unsafePerformIO)

interact :: (String -> String) -> IO ()
interact f = do s <- hGetContents stdin
                putStr $ f s

putStr = mapM_ putChar

hGetContents h = do eof <- hIsEOF h
                    if eof then return []
                           else c <- hGetChar h
                                return (c : (unsafePerformIO $ hGetContents h))


... so there will be the same problems like with getChar, hGetChar, getLine, or hGetLine (buffering), and with hGetContents and unsafePerformIO (sequrence of IOs).


for beginners/students: think about such situations: (to me, it was the reason to learn IO monadic programming)
read the next char(s) from input before writing the previous char(s) to output.

f :: String -> String
f [] = []
f (c:[]) = (c:[])
f (c:s) = (c:f s)

equals to

f :: String -> String
f [] = []
f (c:[]) = (c:[])
f (prev:s@(next:_)) = (prev:f s)



More information about the Haskell mailing list