Rejig the extensible exceptions so there is less circular importing
[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     hPutBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
155     hGetBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
156 #endif
157
158     -- * Temporary files
159
160     openTempFile,
161     openBinaryTempFile,
162   ) where
163
164 #ifndef __NHC__
165 import Data.Bits
166 import Data.List
167 import Data.Maybe
168 import Foreign.C.Error
169 import Foreign.C.String
170 import System.Posix.Internals
171 #endif
172
173 #ifdef __GLASGOW_HASKELL__
174 import GHC.IOBase       as ExceptionBase
175 #endif
176 #ifdef __HUGS__
177 import Hugs.Exception   as ExceptionBase
178 #endif
179
180 #ifdef __GLASGOW_HASKELL__
181 import GHC.Base
182 import GHC.IOBase       -- Together these four Prelude modules define
183 import GHC.Handle       -- all the stuff exported by IO for the GHC version
184 import GHC.IO
185 import GHC.Exception
186 import GHC.Num
187 import GHC.Read
188 import GHC.Show
189 #endif
190
191 #ifdef __HUGS__
192 import Hugs.IO
193 import Hugs.IOExts
194 import Hugs.IORef
195 import Hugs.Prelude     ( throw, Exception(NonTermination) )
196 import Control.Exception ( bracket )
197 import System.IO.Unsafe ( unsafeInterleaveIO )
198 #endif
199
200 #ifdef __NHC__
201 import IO
202   ( Handle ()
203   , HandlePosn ()
204   , IOMode (ReadMode,WriteMode,AppendMode,ReadWriteMode)
205   , BufferMode (NoBuffering,LineBuffering,BlockBuffering)
206   , SeekMode (AbsoluteSeek,RelativeSeek,SeekFromEnd)
207   , stdin, stdout, stderr
208   , openFile                  -- :: FilePath -> IOMode -> IO Handle
209   , hClose                    -- :: Handle -> IO ()
210   , hFileSize                 -- :: Handle -> IO Integer
211   , hIsEOF                    -- :: Handle -> IO Bool
212   , isEOF                     -- :: IO Bool
213   , hSetBuffering             -- :: Handle -> BufferMode -> IO ()
214   , hGetBuffering             -- :: Handle -> IO BufferMode
215   , hFlush                    -- :: Handle -> IO ()
216   , hGetPosn                  -- :: Handle -> IO HandlePosn
217   , hSetPosn                  -- :: HandlePosn -> IO ()
218   , hSeek                     -- :: Handle -> SeekMode -> Integer -> IO ()
219   , hWaitForInput             -- :: Handle -> Int -> IO Bool
220   , hGetChar                  -- :: Handle -> IO Char
221   , hGetLine                  -- :: Handle -> IO [Char]
222   , hLookAhead                -- :: Handle -> IO Char
223   , hGetContents              -- :: Handle -> IO [Char]
224   , hPutChar                  -- :: Handle -> Char -> IO ()
225   , hPutStr                   -- :: Handle -> [Char] -> IO ()
226   , hPutStrLn                 -- :: Handle -> [Char] -> IO ()
227   , hPrint                    -- :: Handle -> [Char] -> IO ()
228   , hReady                    -- :: Handle -> [Char] -> IO ()
229   , hIsOpen, hIsClosed        -- :: Handle -> IO Bool
230   , hIsReadable, hIsWritable  -- :: Handle -> IO Bool
231   , hIsSeekable               -- :: Handle -> IO Bool
232   , bracket
233
234   , IO ()
235   , FilePath                  -- :: String
236   )
237 import NHC.IOExtras (fixIO, hPutBuf, hGetBuf)
238 import NHC.FFI (Ptr)
239 #endif
240
241 -- -----------------------------------------------------------------------------
242 -- Standard IO
243
244 #ifdef __GLASGOW_HASKELL__
245 -- | Write a character to the standard output device
246 -- (same as 'hPutChar' 'stdout').
247
248 putChar         :: Char -> IO ()
249 putChar c       =  hPutChar stdout c
250
251 -- | Write a string to the standard output device
252 -- (same as 'hPutStr' 'stdout').
253
254 putStr          :: String -> IO ()
255 putStr s        =  hPutStr stdout s
256
257 -- | The same as 'putStr', but adds a newline character.
258
259 putStrLn        :: String -> IO ()
260 putStrLn s      =  do putStr s
261                       putChar '\n'
262
263 -- | The 'print' function outputs a value of any printable type to the
264 -- standard output device.
265 -- Printable types are those that are instances of class 'Show'; 'print'
266 -- converts values to strings for output using the 'show' operation and
267 -- adds a newline.
268 --
269 -- For example, a program to print the first 20 integers and their
270 -- powers of 2 could be written as:
271 --
272 -- > main = print ([(n, 2^n) | n <- [0..19]])
273
274 print           :: Show a => a -> IO ()
275 print x         =  putStrLn (show x)
276
277 -- | Read a character from the standard input device
278 -- (same as 'hGetChar' 'stdin').
279
280 getChar         :: IO Char
281 getChar         =  hGetChar stdin
282
283 -- | Read a line from the standard input device
284 -- (same as 'hGetLine' 'stdin').
285
286 getLine         :: IO String
287 getLine         =  hGetLine stdin
288
289 -- | The 'getContents' operation returns all user input as a single string,
290 -- which is read lazily as it is needed
291 -- (same as 'hGetContents' 'stdin').
292
293 getContents     :: IO String
294 getContents     =  hGetContents stdin
295
296 -- | The 'interact' function takes a function of type @String->String@
297 -- as its argument.  The entire input from the standard input device is
298 -- passed to this function as its argument, and the resulting string is
299 -- output on the standard output device.
300
301 interact        ::  (String -> String) -> IO ()
302 interact f      =   do s <- getContents
303                        putStr (f s)
304
305 -- | The 'readFile' function reads a file and
306 -- returns the contents of the file as a string.
307 -- The file is read lazily, on demand, as with 'getContents'.
308
309 readFile        :: FilePath -> IO String
310 readFile name   =  openFile name ReadMode >>= hGetContents
311
312 -- | The computation 'writeFile' @file str@ function writes the string @str@,
313 -- to the file @file@.
314 writeFile :: FilePath -> String -> IO ()
315 writeFile f txt = withFile f WriteMode (\ hdl -> hPutStr hdl txt)
316
317 -- | The computation 'appendFile' @file str@ function appends the string @str@,
318 -- to the file @file@.
319 --
320 -- Note that 'writeFile' and 'appendFile' write a literal string
321 -- to a file.  To write a value of any printable type, as with 'print',
322 -- use the 'show' function to convert the value to a string first.
323 --
324 -- > main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])
325
326 appendFile      :: FilePath -> String -> IO ()
327 appendFile f txt = withFile f AppendMode (\ hdl -> hPutStr hdl txt)
328
329 -- | The 'readLn' function combines 'getLine' and 'readIO'.
330
331 readLn          :: Read a => IO a
332 readLn          =  do l <- getLine
333                       r <- readIO l
334                       return r
335
336 -- | The 'readIO' function is similar to 'read' except that it signals
337 -- parse failure to the 'IO' monad instead of terminating the program.
338
339 readIO          :: Read a => String -> IO a
340 readIO s        =  case (do { (x,t) <- reads s ;
341                               ("","") <- lex t ;
342                               return x }) of
343                         [x]    -> return x
344                         []     -> ioError (userError "Prelude.readIO: no parse")
345                         _      -> ioError (userError "Prelude.readIO: ambiguous parse")
346 #endif  /* __GLASGOW_HASKELL__ */
347
348 #ifndef __NHC__
349 -- | Computation 'hReady' @hdl@ indicates whether at least one item is
350 -- available for input from handle @hdl@.
351 -- 
352 -- This operation may fail with:
353 --
354 --  * 'System.IO.Error.isEOFError' if the end of file has been reached.
355
356 hReady          :: Handle -> IO Bool
357 hReady h        =  hWaitForInput h 0
358
359 -- | The same as 'hPutStr', but adds a newline character.
360
361 hPutStrLn       :: Handle -> String -> IO ()
362 hPutStrLn hndl str = do
363  hPutStr  hndl str
364  hPutChar hndl '\n'
365
366 -- | Computation 'hPrint' @hdl t@ writes the string representation of @t@
367 -- given by the 'shows' function to the file or channel managed by @hdl@
368 -- and appends a newline.
369 --
370 -- This operation may fail with:
371 --
372 --  * 'System.IO.Error.isFullError' if the device is full; or
373 --
374 --  * 'System.IO.Error.isPermissionError' if another system resource limit would be exceeded.
375
376 hPrint          :: Show a => Handle -> a -> IO ()
377 hPrint hdl      =  hPutStrLn hdl . show
378 #endif /* !__NHC__ */
379
380 -- | @'withFile' name mode act@ opens a file using 'openFile' and passes
381 -- the resulting handle to the computation @act@.  The handle will be
382 -- closed on exit from 'withFile', whether by normal termination or by
383 -- raising an exception.
384 withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
385 withFile name mode = bracket (openFile name mode) hClose
386
387 -- | @'withBinaryFile' name mode act@ opens a file using 'openBinaryFile'
388 -- and passes the resulting handle to the computation @act@.  The handle
389 -- will be closed on exit from 'withBinaryFile', whether by normal
390 -- termination or by raising an exception.
391 withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
392 withBinaryFile name mode = bracket (openBinaryFile name mode) hClose
393
394 -- ---------------------------------------------------------------------------
395 -- fixIO
396
397 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
398 fixIO :: (a -> IO a) -> IO a
399 fixIO k = do
400     ref <- newIORef (throw NonTermination)
401     ans <- unsafeInterleaveIO (readIORef ref)
402     result <- k ans
403     writeIORef ref result
404     return result
405
406 -- NOTE: we do our own explicit black holing here, because GHC's lazy
407 -- blackholing isn't enough.  In an infinite loop, GHC may run the IO
408 -- computation a few times before it notices the loop, which is wrong.
409 #endif
410
411 #if defined(__NHC__)
412 -- Assume a unix platform, where text and binary I/O are identical.
413 openBinaryFile = openFile
414 hSetBinaryMode _ _ = return ()
415 #endif
416
417 -- | The function creates a temporary file in ReadWrite mode.
418 -- The created file isn\'t deleted automatically, so you need to delete it manually.
419 --
420 -- The file is creates with permissions such that only the current
421 -- user can read\/write it.
422 --
423 -- With some exceptions (see below), the file will be created securely
424 -- in the sense that an attacker should not be able to cause
425 -- openTempFile to overwrite another file on the filesystem using your
426 -- credentials, by putting symbolic links (on Unix) in the place where
427 -- the temporary file is to be created.  On Unix the @O_CREAT@ and
428 -- @O_EXCL@ flags are used to prevent this attack, but note that
429 -- @O_EXCL@ is sometimes not supported on NFS filesystems, so if you
430 -- rely on this behaviour it is best to use local filesystems only.
431 --
432 openTempFile :: FilePath   -- ^ Directory in which to create the file
433              -> String     -- ^ File name template. If the template is \"foo.ext\" then
434                            -- the created file will be \"fooXXX.ext\" where XXX is some
435                            -- random number.
436              -> IO (FilePath, Handle)
437 openTempFile tmp_dir template = openTempFile' "openTempFile" tmp_dir template False
438
439 -- | Like 'openTempFile', but opens the file in binary mode. See 'openBinaryFile' for more comments.
440 openBinaryTempFile :: FilePath -> String -> IO (FilePath, Handle)
441 openBinaryTempFile tmp_dir template = openTempFile' "openBinaryTempFile" tmp_dir template True
442
443 openTempFile' :: String -> FilePath -> String -> Bool -> IO (FilePath, Handle)
444 openTempFile' loc tmp_dir template binary = do
445   pid <- c_getpid
446   findTempName pid
447   where
448     -- We split off the last extension, so we can use .foo.ext files
449     -- for temporary files (hidden on Unix OSes). Unfortunately we're
450     -- below filepath in the hierarchy here.
451     (prefix,suffix) =
452        case break (== '.') $ reverse template of
453          -- First case: template contains no '.'s. Just re-reverse it.
454          (rev_suffix, "")       -> (reverse rev_suffix, "")
455          -- Second case: template contains at least one '.'. Strip the
456          -- dot from the prefix and prepend it to the suffix (if we don't
457          -- do this, the unique number will get added after the '.' and
458          -- thus be part of the extension, which is wrong.)
459          (rev_suffix, '.':rest) -> (reverse rest, '.':reverse rev_suffix)
460          -- Otherwise, something is wrong, because (break (== '.')) should
461          -- always return a pair with either the empty string or a string
462          -- beginning with '.' as the second component.
463          _                      -> error "bug in System.IO.openTempFile"
464
465 #ifndef __NHC__
466     oflags1 = rw_flags .|. o_EXCL
467
468     binary_flags
469       | binary    = o_BINARY
470       | otherwise = 0
471
472     oflags = oflags1 .|. binary_flags
473 #endif
474
475 #ifdef __NHC__
476     findTempName x = do h <- openFile filepath ReadWriteMode
477                         return (filepath, h)
478 #else
479     findTempName x = do
480       fd <- withCString filepath $ \ f ->
481               c_open f oflags 0o600
482       if fd < 0
483        then do
484          errno <- getErrno
485          if errno == eEXIST
486            then findTempName (x+1)
487            else ioError (errnoToIOError loc errno Nothing (Just tmp_dir))
488        else do
489          -- XXX We want to tell fdToHandle what the filepath is,
490          -- as any exceptions etc will only be able to report the
491          -- fd currently
492          h <- fdToHandle fd
493                 `ExceptionBase.catchAny` \e -> do c_close fd; throw e
494          return (filepath, h)
495 #endif
496       where
497         filename        = prefix ++ show x ++ suffix
498         filepath        = tmp_dir `combine` filename
499
500         -- XXX bits copied from System.FilePath, since that's not available here
501         combine a b
502                   | null b = a
503                   | null a = b
504                   | last a == pathSeparator = a ++ b
505                   | otherwise = a ++ [pathSeparator] ++ b
506
507 #if __HUGS__
508         fdToHandle fd   = openFd (fromIntegral fd) False ReadWriteMode binary
509 #endif
510
511 -- XXX Should use filepath library
512 pathSeparator :: Char
513 #ifdef mingw32_HOST_OS
514 pathSeparator = '\\'
515 #else
516 pathSeparator = '/'
517 #endif
518
519 #ifndef __NHC__
520 -- XXX Copied from GHC.Handle
521 std_flags    = o_NONBLOCK   .|. o_NOCTTY
522 output_flags = std_flags    .|. o_CREAT
523 read_flags   = std_flags    .|. o_RDONLY
524 write_flags  = output_flags .|. o_WRONLY
525 rw_flags     = output_flags .|. o_RDWR
526 append_flags = write_flags  .|. o_APPEND
527 #endif
528
529 #ifdef __NHC__
530 foreign import ccall "getpid" c_getpid :: IO Int
531 #endif
532
533 -- $locking
534 -- Implementations should enforce as far as possible, at least locally to the
535 -- Haskell process, multiple-reader single-writer locking on files.
536 -- That is, /there may either be many handles on the same file which manage
537 -- input, or just one handle on the file which manages output/.  If any
538 -- open or semi-closed handle is managing a file for output, no new
539 -- handle can be allocated for that file.  If any open or semi-closed
540 -- handle is managing a file for input, new handles can only be allocated
541 -- if they do not manage output.  Whether two files are the same is
542 -- implementation-dependent, but they should normally be the same if they
543 -- have the same absolute path name and neither has been renamed, for
544 -- example.
545 --
546 -- /Warning/: the 'readFile' operation holds a semi-closed handle on
547 -- the file until the entire contents of the file have been consumed.
548 -- It follows that an attempt to write to a file (using 'writeFile', for
549 -- example) that was earlier opened by 'readFile' will usually result in
550 -- failure with 'System.IO.Error.isAlreadyInUseError'.
551
552 -- -----------------------------------------------------------------------------
553 -- Utils
554
555 #ifdef __GLASGOW_HASKELL__
556 -- Copied here to avoid recursive dependency with Control.Exception
557 bracket
558         :: IO a         -- ^ computation to run first (\"acquire resource\")
559         -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
560         -> (a -> IO c)  -- ^ computation to run in-between
561         -> IO c         -- returns the value from the in-between computation
562 bracket before after thing =
563   block (do
564     a <- before
565     r <- catchAny
566            (unblock (thing a))
567            (\e -> do { after a; throw e })
568     after a
569     return r
570  )
571 #endif