Chapter "IO" of the Haskell 98 Library Report contains this example:
import IO
import System
main = do
[f1,f2] <- getArgs
h1 <- openFile f1 ReadMode
h2 <- openFile f2 WriteMode
copyFile h1 h2
hClose h1
hClose h2
copyFile h1 h2 = do
eof <- hIsEOF h1
if eof then return () else
do
c <- hGetChar h1
hPutChar h2 (toUpper c)
copyFile h1 h2
in Unix which has no kernel file locking, this code has a race
condition: if some other process truncates f1 after the test for eof
but before the hGetChar, then that code throws an EOF exception, which
is probably not the programmer's intention.
In fact, I'm sure it's not the programmer's intention because the very next
lines in the library report are
An equivalent but much shorter version, using string I/O is:
import System
main = do
[f1,f2] <- getArgs
s <- readFile f1
writeFile f2 (map toUpper s)
... which never throws an EOF exception.
this next accurately expresses the programmer's intention:
copyFile h1 h2 = do
catch
do
c <- hGetChar h1
hPutChar h2 (toUpper c)
copyFile h1 h2
\e -> if isEOFError e then return () else ioError e
but it would be nice for a small program fragment be able to loop over
the contents of an input file without resorting to "catch", which is
more awkard than most constructs. that is easy to achieve: we
introduce a new primitive, hGetCharMaybe, which combines the test for
EOF and the read into one atomic action and allows us to rewrite that
last as
copyFile h1 h2 = do
c <- hGetCharMaybe h1
case c of
Nothing -> return ()
Just char -> hPutChar h2 (toUpper char) >> copyFile h1 h2
in fact, it might win to remove hIsEOF and hGetChar and derivatives
from the library. this would occasionally force the programmer to
rearrange his code or to write slightly less efficient IO code, but
would often prevent the programmer from writing code containing race
conditions. generally only systems programmers know to avoid race
conditions, and systems programmers are not Haskell's main "customers".
P.S., I prefer the CPS version of hGetCharMaybe because it shortens the code,
but alas it is not very Haskellish:
hGetCharCPS :: Handle -> IO() -> (Char -> IO()) -> IO()
hGetCharCPS h eof continue =
hGetCharMaybe h>>=\c->case c of Nothing->eof;Just char->continue char
copyFile h1 h2 =
hGetCharCPS h1 (return ())
\char -> hPutChar h2 (toUpper char) >> copyFile h1 h2