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