d52c2c9d068b02b80e0551b89fbaec9011b888c5
[ghc-base.git] / System / IO.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  System.IO
5 -- Copyright   :  (c) The University of Glasgow 2001
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  stable
10 -- Portability :  portable
11 --
12 -- The standard IO library.
13 --
14 -----------------------------------------------------------------------------
15
16 module System.IO (
17     -- * The IO monad
18
19     IO,                        -- instance MonadFix
20     fixIO,                     -- :: (a -> IO a) -> IO a
21
22     -- * Files and handles
23
24     FilePath,                  -- :: String
25
26     Handle,             -- abstract, instance of: Eq, Show.
27
28     -- | GHC note: a 'Handle' will be automatically closed when the garbage
29     -- collector detects that it has become unreferenced by the program.
30     -- However, relying on this behaviour is not generally recommended:
31     -- the garbage collector is unpredictable.  If possible, use
32     -- an explicit 'hClose' to close 'Handle's when they are no longer
33     -- required.  GHC does not currently attempt to free up file
34     -- descriptors when they have run out, it is your responsibility to
35     -- ensure that this doesn't happen.
36
37     -- ** Standard handles
38
39     -- | Three handles are allocated during program initialisation,
40     -- and are initially open.
41
42     stdin, stdout, stderr,   -- :: Handle
43
44     -- * Opening and closing files
45
46     -- ** Opening files
47
48     withFile,
49     openFile,                  -- :: FilePath -> IOMode -> IO Handle
50     IOMode(ReadMode,WriteMode,AppendMode,ReadWriteMode),
51
52     -- ** Closing files
53
54     hClose,                    -- :: Handle -> IO ()
55
56     -- ** Special cases
57
58     -- | These functions are also exported by the "Prelude".
59
60     readFile,                  -- :: FilePath -> IO String
61     writeFile,                 -- :: FilePath -> String -> IO ()
62     appendFile,                -- :: FilePath -> String -> IO ()
63
64     -- ** File locking
65
66     -- $locking
67
68     -- * Operations on handles
69
70     -- ** Determining and changing the size of a file
71
72     hFileSize,                 -- :: Handle -> IO Integer
73 #ifdef __GLASGOW_HASKELL__
74     hSetFileSize,              -- :: Handle -> Integer -> IO ()
75 #endif
76
77     -- ** Detecting the end of input
78
79     hIsEOF,                    -- :: Handle -> IO Bool
80     isEOF,                     -- :: IO Bool
81
82     -- ** Buffering operations
83
84     BufferMode(NoBuffering,LineBuffering,BlockBuffering),
85     hSetBuffering,             -- :: Handle -> BufferMode -> IO ()
86     hGetBuffering,             -- :: Handle -> IO BufferMode
87     hFlush,                    -- :: Handle -> IO ()
88
89     -- ** Repositioning handles
90
91     hGetPosn,                  -- :: Handle -> IO HandlePosn
92     hSetPosn,                  -- :: HandlePosn -> IO ()
93     HandlePosn,                -- abstract, instance of: Eq, Show.
94
95     hSeek,                     -- :: Handle -> SeekMode -> Integer -> IO ()
96     SeekMode(AbsoluteSeek,RelativeSeek,SeekFromEnd),
97 #if !defined(__NHC__)
98     hTell,                     -- :: Handle -> IO Integer
99 #endif
100
101     -- ** Handle properties
102
103     hIsOpen, hIsClosed,        -- :: Handle -> IO Bool
104     hIsReadable, hIsWritable,  -- :: Handle -> IO Bool
105     hIsSeekable,               -- :: Handle -> IO Bool
106
107     -- ** Terminal operations (not portable: GHC\/Hugs only)
108
109 #if !defined(__NHC__)
110     hIsTerminalDevice,          -- :: Handle -> IO Bool
111
112     hSetEcho,                   -- :: Handle -> Bool -> IO ()
113     hGetEcho,                   -- :: Handle -> IO Bool
114 #endif
115
116     -- ** Showing handle state (not portable: GHC only)
117
118 #ifdef __GLASGOW_HASKELL__
119     hShow,                      -- :: Handle -> IO String
120 #endif
121
122     -- * Text input and output
123
124     -- ** Text input
125
126     hWaitForInput,             -- :: Handle -> Int -> IO Bool
127     hReady,                    -- :: Handle -> IO Bool
128     hGetChar,                  -- :: Handle -> IO Char
129     hGetLine,                  -- :: Handle -> IO [Char]
130     hLookAhead,                -- :: Handle -> IO Char
131     hGetContents,              -- :: Handle -> IO [Char]
132
133     -- ** Text output
134
135     hPutChar,                  -- :: Handle -> Char -> IO ()
136     hPutStr,                   -- :: Handle -> [Char] -> IO ()
137     hPutStrLn,                 -- :: Handle -> [Char] -> IO ()
138     hPrint,                    -- :: Show a => Handle -> a -> IO ()
139
140     -- ** Special cases for standard input and output
141
142     -- | These functions are also exported by the "Prelude".
143
144     interact,                  -- :: (String -> String) -> IO ()
145     putChar,                   -- :: Char   -> IO ()
146     putStr,                    -- :: String -> IO () 
147     putStrLn,                  -- :: String -> IO ()
148     print,                     -- :: Show a => a -> IO ()
149     getChar,                   -- :: IO Char
150     getLine,                   -- :: IO String
151     getContents,               -- :: IO String
152     readIO,                    -- :: Read a => String -> IO a
153     readLn,                    -- :: Read a => IO a
154
155     -- * Binary input and output
156
157     withBinaryFile,
158     openBinaryFile,            -- :: FilePath -> IOMode -> IO Handle
159     hSetBinaryMode,            -- :: Handle -> Bool -> IO ()
160     hPutBuf,                   -- :: Handle -> Ptr a -> Int -> IO ()
161     hGetBuf,                   -- :: Handle -> Ptr a -> Int -> IO Int
162 #if !defined(__NHC__) && !defined(__HUGS__)
163     hGetBufSome,               -- :: Handle -> Ptr a -> Int -> IO Int
164     hPutBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
165     hGetBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
166 #endif
167
168     -- * Temporary files
169
170     openTempFile,
171     openBinaryTempFile,
172     openTempFileWithDefaultPermissions,
173     openBinaryTempFileWithDefaultPermissions,
174
175 #if !defined(__NHC__) && !defined(__HUGS__)
176     -- * Unicode encoding\/decoding
177
178     -- | A text-mode 'Handle' has an associated 'TextEncoding', which
179     -- is used to decode bytes into Unicode characters when reading,
180     -- and encode Unicode characters into bytes when writing.
181     --
182     -- The default 'TextEncoding' is the same as the default encoding
183     -- on your system, which is also available as 'localeEncoding'.
184     -- (GHC note: on Windows, we currently do not support double-byte
185     -- encodings; if the console\'s code page is unsupported, then
186     -- 'localeEncoding' will be 'latin1'.)
187     --
188     -- Encoding and decoding errors are always detected and reported,
189     -- except during lazy I/O ('hGetContents', 'getContents', and
190     -- 'readFile'), where a decoding error merely results in
191     -- termination of the character stream, as with other I/O errors.
192
193     hSetEncoding, 
194     hGetEncoding,
195
196     -- ** Unicode encodings
197     TextEncoding, 
198     latin1,
199     utf8, utf8_bom,
200     utf16, utf16le, utf16be,
201     utf32, utf32le, utf32be, 
202     localeEncoding,
203     mkTextEncoding,
204 #endif
205
206 #if !defined(__NHC__) && !defined(__HUGS__)
207     -- * Newline conversion
208     
209     -- | In Haskell, a newline is always represented by the character
210     -- '\n'.  However, in files and external character streams, a
211     -- newline may be represented by another character sequence, such
212     -- as '\r\n'.
213     --
214     -- A text-mode 'Handle' has an associated 'NewlineMode' that
215     -- specifies how to transate newline characters.  The
216     -- 'NewlineMode' specifies the input and output translation
217     -- separately, so that for instance you can translate '\r\n'
218     -- to '\n' on input, but leave newlines as '\n' on output.
219     --
220     -- The default 'NewlineMode' for a 'Handle' is
221     -- 'nativeNewlineMode', which does no translation on Unix systems,
222     -- but translates '\r\n' to '\n' and back on Windows.
223     --
224     -- Binary-mode 'Handle's do no newline translation at all.
225     --
226     hSetNewlineMode, 
227     Newline(..), nativeNewline, 
228     NewlineMode(..), 
229     noNewlineTranslation, universalNewlineMode, nativeNewlineMode,
230 #endif
231   ) where
232
233 import Control.Exception.Base
234
235 #ifndef __NHC__
236 import Data.Bits
237 import Data.List
238 import Data.Maybe
239 import Foreign.C.Error
240 import Foreign.C.Types
241 import System.Posix.Internals
242 import System.Posix.Types
243 #endif
244
245 #ifdef __GLASGOW_HASKELL__
246 import GHC.Base
247 import GHC.IO hiding ( onException )
248 import GHC.IO.IOMode
249 import GHC.IO.Handle.FD
250 import qualified GHC.IO.FD as FD
251 import GHC.IO.Handle
252 import GHC.IO.Handle.Text ( hGetBufSome, hPutStrLn )
253 import GHC.IORef
254 import GHC.IO.Exception ( userError )
255 import GHC.IO.Encoding
256 import GHC.Num
257 import Text.Read
258 import GHC.Show
259 #endif
260
261 #ifdef __HUGS__
262 import Hugs.IO
263 import Hugs.IOExts
264 import Hugs.IORef
265 import System.IO.Unsafe ( unsafeInterleaveIO )
266 #endif
267
268 #ifdef __NHC__
269 import IO
270   ( Handle ()
271   , HandlePosn ()
272   , IOMode (ReadMode,WriteMode,AppendMode,ReadWriteMode)
273   , BufferMode (NoBuffering,LineBuffering,BlockBuffering)
274   , SeekMode (AbsoluteSeek,RelativeSeek,SeekFromEnd)
275   , stdin, stdout, stderr
276   , openFile                  -- :: FilePath -> IOMode -> IO Handle
277   , hClose                    -- :: Handle -> IO ()
278   , hFileSize                 -- :: Handle -> IO Integer
279   , hIsEOF                    -- :: Handle -> IO Bool
280   , isEOF                     -- :: IO Bool
281   , hSetBuffering             -- :: Handle -> BufferMode -> IO ()
282   , hGetBuffering             -- :: Handle -> IO BufferMode
283   , hFlush                    -- :: Handle -> IO ()
284   , hGetPosn                  -- :: Handle -> IO HandlePosn
285   , hSetPosn                  -- :: HandlePosn -> IO ()
286   , hSeek                     -- :: Handle -> SeekMode -> Integer -> IO ()
287   , hWaitForInput             -- :: Handle -> Int -> IO Bool
288   , hGetChar                  -- :: Handle -> IO Char
289   , hGetLine                  -- :: Handle -> IO [Char]
290   , hLookAhead                -- :: Handle -> IO Char
291   , hGetContents              -- :: Handle -> IO [Char]
292   , hPutChar                  -- :: Handle -> Char -> IO ()
293   , hPutStr                   -- :: Handle -> [Char] -> IO ()
294   , hPutStrLn                 -- :: Handle -> [Char] -> IO ()
295   , hPrint                    -- :: Handle -> [Char] -> IO ()
296   , hReady                    -- :: Handle -> [Char] -> IO ()
297   , hIsOpen, hIsClosed        -- :: Handle -> IO Bool
298   , hIsReadable, hIsWritable  -- :: Handle -> IO Bool
299   , hIsSeekable               -- :: Handle -> IO Bool
300   , bracket
301
302   , IO ()
303   , FilePath                  -- :: String
304   )
305 import NHC.IOExtras (fixIO, hPutBuf, hGetBuf)
306 import NHC.FFI (Ptr)
307 #endif
308
309 -- -----------------------------------------------------------------------------
310 -- Standard IO
311
312 #ifdef __GLASGOW_HASKELL__
313 -- | Write a character to the standard output device
314 -- (same as 'hPutChar' 'stdout').
315
316 putChar         :: Char -> IO ()
317 putChar c       =  hPutChar stdout c
318
319 -- | Write a string to the standard output device
320 -- (same as 'hPutStr' 'stdout').
321
322 putStr          :: String -> IO ()
323 putStr s        =  hPutStr stdout s
324
325 -- | The same as 'putStr', but adds a newline character.
326
327 putStrLn        :: String -> IO ()
328 putStrLn s      =  hPutStrLn stdout s
329
330 -- | The 'print' function outputs a value of any printable type to the
331 -- standard output device.
332 -- Printable types are those that are instances of class 'Show'; 'print'
333 -- converts values to strings for output using the 'show' operation and
334 -- adds a newline.
335 --
336 -- For example, a program to print the first 20 integers and their
337 -- powers of 2 could be written as:
338 --
339 -- > main = print ([(n, 2^n) | n <- [0..19]])
340
341 print           :: Show a => a -> IO ()
342 print x         =  putStrLn (show x)
343
344 -- | Read a character from the standard input device
345 -- (same as 'hGetChar' 'stdin').
346
347 getChar         :: IO Char
348 getChar         =  hGetChar stdin
349
350 -- | Read a line from the standard input device
351 -- (same as 'hGetLine' 'stdin').
352
353 getLine         :: IO String
354 getLine         =  hGetLine stdin
355
356 -- | The 'getContents' operation returns all user input as a single string,
357 -- which is read lazily as it is needed
358 -- (same as 'hGetContents' 'stdin').
359
360 getContents     :: IO String
361 getContents     =  hGetContents stdin
362
363 -- | The 'interact' function takes a function of type @String->String@
364 -- as its argument.  The entire input from the standard input device is
365 -- passed to this function as its argument, and the resulting string is
366 -- output on the standard output device.
367
368 interact        ::  (String -> String) -> IO ()
369 interact f      =   do s <- getContents
370                        putStr (f s)
371
372 -- | The 'readFile' function reads a file and
373 -- returns the contents of the file as a string.
374 -- The file is read lazily, on demand, as with 'getContents'.
375
376 readFile        :: FilePath -> IO String
377 readFile name   =  openFile name ReadMode >>= hGetContents
378
379 -- | The computation 'writeFile' @file str@ function writes the string @str@,
380 -- to the file @file@.
381 writeFile :: FilePath -> String -> IO ()
382 writeFile f txt = withFile f WriteMode (\ hdl -> hPutStr hdl txt)
383
384 -- | The computation 'appendFile' @file str@ function appends the string @str@,
385 -- to the file @file@.
386 --
387 -- Note that 'writeFile' and 'appendFile' write a literal string
388 -- to a file.  To write a value of any printable type, as with 'print',
389 -- use the 'show' function to convert the value to a string first.
390 --
391 -- > main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])
392
393 appendFile      :: FilePath -> String -> IO ()
394 appendFile f txt = withFile f AppendMode (\ hdl -> hPutStr hdl txt)
395
396 -- | The 'readLn' function combines 'getLine' and 'readIO'.
397
398 readLn          :: Read a => IO a
399 readLn          =  do l <- getLine
400                       r <- readIO l
401                       return r
402
403 -- | The 'readIO' function is similar to 'read' except that it signals
404 -- parse failure to the 'IO' monad instead of terminating the program.
405
406 readIO          :: Read a => String -> IO a
407 readIO s        =  case (do { (x,t) <- reads s ;
408                               ("","") <- lex t ;
409                               return x }) of
410                         [x]    -> return x
411                         []     -> ioError (userError "Prelude.readIO: no parse")
412                         _      -> ioError (userError "Prelude.readIO: ambiguous parse")
413 #endif  /* __GLASGOW_HASKELL__ */
414
415 #ifndef __NHC__
416 -- | Computation 'hReady' @hdl@ indicates whether at least one item is
417 -- available for input from handle @hdl@.
418 -- 
419 -- This operation may fail with:
420 --
421 --  * 'System.IO.Error.isEOFError' if the end of file has been reached.
422
423 hReady          :: Handle -> IO Bool
424 hReady h        =  hWaitForInput h 0
425
426 -- | Computation 'hPrint' @hdl t@ writes the string representation of @t@
427 -- given by the 'shows' function to the file or channel managed by @hdl@
428 -- and appends a newline.
429 --
430 -- This operation may fail with:
431 --
432 --  * 'System.IO.Error.isFullError' if the device is full; or
433 --
434 --  * 'System.IO.Error.isPermissionError' if another system resource limit would be exceeded.
435
436 hPrint          :: Show a => Handle -> a -> IO ()
437 hPrint hdl      =  hPutStrLn hdl . show
438 #endif /* !__NHC__ */
439
440 -- | @'withFile' name mode act@ opens a file using 'openFile' and passes
441 -- the resulting handle to the computation @act@.  The handle will be
442 -- closed on exit from 'withFile', whether by normal termination or by
443 -- raising an exception.  If closing the handle raises an exception, then
444 -- this exception will be raised by 'withFile' rather than any exception
445 -- raised by 'act'.
446 withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
447 withFile name mode = bracket (openFile name mode) hClose
448
449 -- | @'withBinaryFile' name mode act@ opens a file using 'openBinaryFile'
450 -- and passes the resulting handle to the computation @act@.  The handle
451 -- will be closed on exit from 'withBinaryFile', whether by normal
452 -- termination or by raising an exception.
453 withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
454 withBinaryFile name mode = bracket (openBinaryFile name mode) hClose
455
456 -- ---------------------------------------------------------------------------
457 -- fixIO
458
459 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
460 fixIO :: (a -> IO a) -> IO a
461 fixIO k = do
462     ref <- newIORef (throw NonTermination)
463     ans <- unsafeInterleaveIO (readIORef ref)
464     result <- k ans
465     writeIORef ref result
466     return result
467
468 -- NOTE: we do our own explicit black holing here, because GHC's lazy
469 -- blackholing isn't enough.  In an infinite loop, GHC may run the IO
470 -- computation a few times before it notices the loop, which is wrong.
471 #endif
472
473 #if defined(__NHC__)
474 -- Assume a unix platform, where text and binary I/O are identical.
475 openBinaryFile = openFile
476 hSetBinaryMode _ _ = return ()
477
478 type CMode = Int
479 #endif
480
481 -- | The function creates a temporary file in ReadWrite mode.
482 -- The created file isn\'t deleted automatically, so you need to delete it manually.
483 --
484 -- The file is creates with permissions such that only the current
485 -- user can read\/write it.
486 --
487 -- With some exceptions (see below), the file will be created securely
488 -- in the sense that an attacker should not be able to cause
489 -- openTempFile to overwrite another file on the filesystem using your
490 -- credentials, by putting symbolic links (on Unix) in the place where
491 -- the temporary file is to be created.  On Unix the @O_CREAT@ and
492 -- @O_EXCL@ flags are used to prevent this attack, but note that
493 -- @O_EXCL@ is sometimes not supported on NFS filesystems, so if you
494 -- rely on this behaviour it is best to use local filesystems only.
495 --
496 openTempFile :: FilePath   -- ^ Directory in which to create the file
497              -> String     -- ^ File name template. If the template is \"foo.ext\" then
498                            -- the created file will be \"fooXXX.ext\" where XXX is some
499                            -- random number.
500              -> IO (FilePath, Handle)
501 openTempFile tmp_dir template
502     = openTempFile' "openTempFile" tmp_dir template False 0o600
503
504 -- | Like 'openTempFile', but opens the file in binary mode. See 'openBinaryFile' for more comments.
505 openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle)
506 openBinaryTempFile tmp_dir template
507     = openTempFile' "openBinaryTempFile" tmp_dir template True 0o600
508
509 -- | Like 'openTempFile', but uses the default file permissions
510 openTempFileWithDefaultPermissions :: FilePath -> String
511                                    -> IO (FilePath, Handle)
512 openTempFileWithDefaultPermissions tmp_dir template
513     = openTempFile' "openBinaryTempFile" tmp_dir template False 0o666
514
515 -- | Like 'openBinaryTempFile', but uses the default file permissions
516 openBinaryTempFileWithDefaultPermissions :: FilePath -> String
517                                          -> IO (FilePath, Handle)
518 openBinaryTempFileWithDefaultPermissions tmp_dir template
519     = openTempFile' "openBinaryTempFile" tmp_dir template True 0o666
520
521 openTempFile' :: String -> FilePath -> String -> Bool -> CMode
522               -> IO (FilePath, Handle)
523 openTempFile' loc tmp_dir template binary mode = do
524   pid <- c_getpid
525   findTempName pid
526   where
527     -- We split off the last extension, so we can use .foo.ext files
528     -- for temporary files (hidden on Unix OSes). Unfortunately we're
529     -- below filepath in the hierarchy here.
530     (prefix,suffix) =
531        case break (== '.') $ reverse template of
532          -- First case: template contains no '.'s. Just re-reverse it.
533          (rev_suffix, "")       -> (reverse rev_suffix, "")
534          -- Second case: template contains at least one '.'. Strip the
535          -- dot from the prefix and prepend it to the suffix (if we don't
536          -- do this, the unique number will get added after the '.' and
537          -- thus be part of the extension, which is wrong.)
538          (rev_suffix, '.':rest) -> (reverse rest, '.':reverse rev_suffix)
539          -- Otherwise, something is wrong, because (break (== '.')) should
540          -- always return a pair with either the empty string or a string
541          -- beginning with '.' as the second component.
542          _                      -> error "bug in System.IO.openTempFile"
543
544 #ifndef __NHC__
545     oflags1 = rw_flags .|. o_EXCL
546
547     binary_flags
548       | binary    = o_BINARY
549       | otherwise = 0
550
551     oflags = oflags1 .|. binary_flags
552 #endif
553
554 #if defined(__NHC__)
555     findTempName x = do h <- openFile filepath ReadWriteMode
556                         return (filepath, h)
557 #elif defined(__GLASGOW_HASKELL__)
558     findTempName x = do
559       fd <- withFilePath filepath $ \ f ->
560               c_open f oflags mode
561       if fd < 0
562        then do
563          errno <- getErrno
564          if errno == eEXIST
565            then findTempName (x+1)
566            else ioError (errnoToIOError loc errno Nothing (Just tmp_dir))
567        else do
568
569          (fD,fd_type) <- FD.mkFD fd ReadWriteMode Nothing{-no stat-}
570                               False{-is_socket-} 
571                               True{-is_nonblock-}
572
573          h <- mkHandleFromFD fD fd_type filepath ReadWriteMode False{-set non-block-}
574                            (Just localeEncoding)
575
576          return (filepath, h)
577 #else
578          h <- fdToHandle fd `onException` c_close fd
579          return (filepath, h)
580 #endif
581
582       where
583         filename        = prefix ++ show x ++ suffix
584         filepath        = tmp_dir `combine` filename
585
586         -- XXX bits copied from System.FilePath, since that's not available here
587         combine a b
588                   | null b = a
589                   | null a = b
590                   | last a == pathSeparator = a ++ b
591                   | otherwise = a ++ [pathSeparator] ++ b
592
593 #if __HUGS__
594         fdToHandle fd   = openFd (fromIntegral fd) False ReadWriteMode binary
595 #endif
596
597 -- XXX Should use filepath library
598 pathSeparator :: Char
599 #ifdef mingw32_HOST_OS
600 pathSeparator = '\\'
601 #else
602 pathSeparator = '/'
603 #endif
604
605 #ifndef __NHC__
606 -- XXX Copied from GHC.Handle
607 std_flags, output_flags, rw_flags :: CInt
608 std_flags    = o_NONBLOCK   .|. o_NOCTTY
609 output_flags = std_flags    .|. o_CREAT
610 rw_flags     = output_flags .|. o_RDWR
611 #endif
612
613 #ifdef __NHC__
614 foreign import ccall "getpid" c_getpid :: IO Int
615 #endif
616
617 -- $locking
618 -- Implementations should enforce as far as possible, at least locally to the
619 -- Haskell process, multiple-reader single-writer locking on files.
620 -- That is, /there may either be many handles on the same file which manage input, or just one handle on the file which manages output/.  If any
621 -- open or semi-closed handle is managing a file for output, no new
622 -- handle can be allocated for that file.  If any open or semi-closed
623 -- handle is managing a file for input, new handles can only be allocated
624 -- if they do not manage output.  Whether two files are the same is
625 -- implementation-dependent, but they should normally be the same if they
626 -- have the same absolute path name and neither has been renamed, for
627 -- example.
628 --
629 -- /Warning/: the 'readFile' operation holds a semi-closed handle on
630 -- the file until the entire contents of the file have been consumed.
631 -- It follows that an attempt to write to a file (using 'writeFile', for
632 -- example) that was earlier opened by 'readFile' will usually result in
633 -- failure with 'System.IO.Error.isAlreadyInUseError'.