> main = mapM (>>=putChar) getCharS where getCharS = getChar:getCharS
>
> How would you suggest to neatly insert the error handling code into ?
\begin{code}
-- some suggestions for a little zoo of cats
module Main where
import IO
import Monad
main0 = interact id
main1 = getContents >>= putStr
main2 = untilEOF (getChar>>=putChar)
catchEOF io = catch io (\e->unless (IO.isEOFError e) (ioError e))
untilEOF io = catchEOF (sequence_ $ repeat io)
main = main2
\end{code}
Claus
PS. I haven't kept up to date with buffering issues,
and hugs/ghci may not like this kind of code..
_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe