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