add withFile and withBinaryFile (#966)
[ghc-base.git] / System / IO.hs
1 {-# OPTIONS_GHC -fno-implicit-prelude #-}
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
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
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 #if !defined(__NHC__)
152     hPutBuf,                   -- :: Handle -> Ptr a -> Int -> IO ()
153     hGetBuf,                   -- :: Handle -> Ptr a -> Int -> IO Int
154 #endif
155 #if !defined(__NHC__) && !defined(__HUGS__)
156     hPutBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
157     hGetBufNonBlocking,        -- :: Handle -> Ptr a -> Int -> IO Int
158 #endif
159
160     -- * Temporary files
161
162 #ifdef __GLASGOW_HASKELL__
163     openTempFile,
164     openBinaryTempFile,
165 #endif
166   ) where
167
168 #ifdef __GLASGOW_HASKELL__
169 import GHC.Base
170 import GHC.IOBase       -- Together these four Prelude modules define
171 import GHC.Handle       -- all the stuff exported by IO for the GHC version
172 import GHC.IO
173 import GHC.Exception
174 import GHC.Num
175 import GHC.Read
176 import GHC.Show
177 #endif
178
179 #ifdef __HUGS__
180 import Hugs.IO
181 import Hugs.IOExts
182 import Hugs.IORef
183 import Hugs.Prelude     ( throw, Exception(NonTermination) )
184 import Control.Exception ( bracket )
185 import System.IO.Unsafe ( unsafeInterleaveIO )
186 #endif
187
188 #ifdef __NHC__
189 import IO
190   ( Handle ()
191   , HandlePosn ()
192   , IOMode (ReadMode,WriteMode,AppendMode,ReadWriteMode)
193   , BufferMode (NoBuffering,LineBuffering,BlockBuffering)
194   , SeekMode (AbsoluteSeek,RelativeSeek,SeekFromEnd)
195   , stdin, stdout, stderr
196   , openFile                  -- :: FilePath -> IOMode -> IO Handle
197   , hClose                    -- :: Handle -> IO ()
198   , hFileSize                 -- :: Handle -> IO Integer
199   , hIsEOF                    -- :: Handle -> IO Bool
200   , isEOF                     -- :: IO Bool
201   , hSetBuffering             -- :: Handle -> BufferMode -> IO ()
202   , hGetBuffering             -- :: Handle -> IO BufferMode
203   , hFlush                    -- :: Handle -> IO ()
204   , hGetPosn                  -- :: Handle -> IO HandlePosn
205   , hSetPosn                  -- :: HandlePosn -> IO ()
206   , hSeek                     -- :: Handle -> SeekMode -> Integer -> IO ()
207   , hWaitForInput             -- :: Handle -> Int -> IO Bool
208   , hGetChar                  -- :: Handle -> IO Char
209   , hGetLine                  -- :: Handle -> IO [Char]
210   , hLookAhead                -- :: Handle -> IO Char
211   , hGetContents              -- :: Handle -> IO [Char]
212   , hPutChar                  -- :: Handle -> Char -> IO ()
213   , hPutStr                   -- :: Handle -> [Char] -> IO ()
214   , hPutStrLn                 -- :: Handle -> [Char] -> IO ()
215   , hPrint                    -- :: Handle -> [Char] -> IO ()
216   , hReady                    -- :: Handle -> [Char] -> IO ()
217   , hIsOpen, hIsClosed        -- :: Handle -> IO Bool
218   , hIsReadable, hIsWritable  -- :: Handle -> IO Bool
219   , hIsSeekable               -- :: Handle -> IO Bool
220   , bracket
221
222   , IO ()
223   , FilePath                  -- :: String
224   )
225 import NHC.IOExtras (fixIO)
226 #endif
227
228 -- -----------------------------------------------------------------------------
229 -- Standard IO
230
231 #ifdef __GLASGOW_HASKELL__
232 -- | Write a character to the standard output device
233 -- (same as 'hPutChar' 'stdout').
234
235 putChar         :: Char -> IO ()
236 putChar c       =  hPutChar stdout c
237
238 -- | Write a string to the standard output device
239 -- (same as 'hPutStr' 'stdout').
240
241 putStr          :: String -> IO ()
242 putStr s        =  hPutStr stdout s
243
244 -- | The same as 'putStr', but adds a newline character.
245
246 putStrLn        :: String -> IO ()
247 putStrLn s      =  do putStr s
248                       putChar '\n'
249
250 -- | The 'print' function outputs a value of any printable type to the
251 -- standard output device.
252 -- Printable types are those that are instances of class 'Show'; 'print'
253 -- converts values to strings for output using the 'show' operation and
254 -- adds a newline.
255 --
256 -- For example, a program to print the first 20 integers and their
257 -- powers of 2 could be written as:
258 --
259 -- > main = print ([(n, 2^n) | n <- [0..19]])
260
261 print           :: Show a => a -> IO ()
262 print x         =  putStrLn (show x)
263
264 -- | Read a character from the standard input device
265 -- (same as 'hGetChar' 'stdin').
266
267 getChar         :: IO Char
268 getChar         =  hGetChar stdin
269
270 -- | Read a line from the standard input device
271 -- (same as 'hGetLine' 'stdin').
272
273 getLine         :: IO String
274 getLine         =  hGetLine stdin
275
276 -- | The 'getContents' operation returns all user input as a single string,
277 -- which is read lazily as it is needed
278 -- (same as 'hGetContents' 'stdin').
279
280 getContents     :: IO String
281 getContents     =  hGetContents stdin
282
283 -- | The 'interact' function takes a function of type @String->String@
284 -- as its argument.  The entire input from the standard input device is
285 -- passed to this function as its argument, and the resulting string is
286 -- output on the standard output device.
287
288 interact        ::  (String -> String) -> IO ()
289 interact f      =   do s <- getContents
290                        putStr (f s)
291
292 -- | The 'readFile' function reads a file and
293 -- returns the contents of the file as a string.
294 -- The file is read lazily, on demand, as with 'getContents'.
295
296 readFile        :: FilePath -> IO String
297 readFile name   =  openFile name ReadMode >>= hGetContents
298
299 -- | The computation 'writeFile' @file str@ function writes the string @str@,
300 -- to the file @file@.
301 writeFile :: FilePath -> String -> IO ()
302 writeFile f txt = bracket (openFile f WriteMode) hClose
303                           (\hdl -> hPutStr hdl txt) 
304
305 -- | The computation 'appendFile' @file str@ function appends the string @str@,
306 -- to the file @file@.
307 --
308 -- Note that 'writeFile' and 'appendFile' write a literal string
309 -- to a file.  To write a value of any printable type, as with 'print',
310 -- use the 'show' function to convert the value to a string first.
311 --
312 -- > main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])
313
314 appendFile      :: FilePath -> String -> IO ()
315 appendFile f txt = bracket (openFile f AppendMode) hClose
316                            (\hdl -> hPutStr hdl txt)
317
318 -- | The 'readLn' function combines 'getLine' and 'readIO'.
319
320 readLn          :: Read a => IO a
321 readLn          =  do l <- getLine
322                       r <- readIO l
323                       return r
324
325 -- | The 'readIO' function is similar to 'read' except that it signals
326 -- parse failure to the 'IO' monad instead of terminating the program.
327
328 readIO          :: Read a => String -> IO a
329 readIO s        =  case (do { (x,t) <- reads s ;
330                               ("","") <- lex t ;
331                               return x }) of
332                         [x]    -> return x
333                         []     -> ioError (userError "Prelude.readIO: no parse")
334                         _      -> ioError (userError "Prelude.readIO: ambiguous parse")
335 #endif  /* __GLASGOW_HASKELL__ */
336
337 #ifndef __NHC__
338 -- | Computation 'hReady' @hdl@ indicates whether at least one item is
339 -- available for input from handle @hdl@.
340 -- 
341 -- This operation may fail with:
342 --
343 --  * 'System.IO.Error.isEOFError' if the end of file has been reached.
344
345 hReady          :: Handle -> IO Bool
346 hReady h        =  hWaitForInput h 0
347
348 -- | The same as 'hPutStr', but adds a newline character.
349
350 hPutStrLn       :: Handle -> String -> IO ()
351 hPutStrLn hndl str = do
352  hPutStr  hndl str
353  hPutChar hndl '\n'
354
355 -- | Computation 'hPrint' @hdl t@ writes the string representation of @t@
356 -- given by the 'shows' function to the file or channel managed by @hdl@
357 -- and appends a newline.
358 --
359 -- This operation may fail with:
360 --
361 --  * 'System.IO.Error.isFullError' if the device is full; or
362 --
363 --  * 'System.IO.Error.isPermissionError' if another system resource limit would be exceeded.
364
365 hPrint          :: Show a => Handle -> a -> IO ()
366 hPrint hdl      =  hPutStrLn hdl . show
367 #endif /* !__NHC__ */
368
369 -- | @'withFile' name mode act@ opens a file using 'openFile' and passes
370 -- the resulting handle to the computation @act@.  The handle will be
371 -- closed on exit from 'withFile', whether by normal termination or by
372 -- raising an exception.
373 withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
374 withFile name mode = bracket (openFile name mode) hClose
375
376 -- | @'withBinaryFile' name mode act@ opens a file using 'openBinaryFile'
377 -- and passes the resulting handle to the computation @act@.  The handle
378 -- will be closed on exit from 'withBinaryFile', whether by normal
379 -- termination or by raising an exception.
380 withBinaryFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r
381 withBinaryFile name mode = bracket (openBinaryFile name mode) hClose
382
383 -- ---------------------------------------------------------------------------
384 -- fixIO
385
386 #if defined(__GLASGOW_HASKELL__) || defined(__HUGS__)
387 fixIO :: (a -> IO a) -> IO a
388 fixIO k = do
389     ref <- newIORef (throw NonTermination)
390     ans <- unsafeInterleaveIO (readIORef ref)
391     result <- k ans
392     writeIORef ref result
393     return result
394
395 -- NOTE: we do our own explicit black holing here, because GHC's lazy
396 -- blackholing isn't enough.  In an infinite loop, GHC may run the IO
397 -- computation a few times before it notices the loop, which is wrong.
398 #endif
399
400 #if defined(__NHC__)
401 -- Assume a unix platform, where text and binary I/O are identical.
402 openBinaryFile = openFile
403 hSetBinaryMode _ _ = return ()
404 #endif
405
406 -- $locking
407 -- Implementations should enforce as far as possible, at least locally to the
408 -- Haskell process, multiple-reader single-writer locking on files.
409 -- That is, /there may either be many handles on the same file which manage
410 -- input, or just one handle on the file which manages output/.  If any
411 -- open or semi-closed handle is managing a file for output, no new
412 -- handle can be allocated for that file.  If any open or semi-closed
413 -- handle is managing a file for input, new handles can only be allocated
414 -- if they do not manage output.  Whether two files are the same is
415 -- implementation-dependent, but they should normally be the same if they
416 -- have the same absolute path name and neither has been renamed, for
417 -- example.
418 --
419 -- /Warning/: the 'readFile' operation holds a semi-closed handle on
420 -- the file until the entire contents of the file have been consumed.
421 -- It follows that an attempt to write to a file (using 'writeFile', for
422 -- example) that was earlier opened by 'readFile' will usually result in
423 -- failure with 'System.IO.Error.isAlreadyInUseError'.
424
425 -- -----------------------------------------------------------------------------
426 -- Utils
427
428 #ifdef __GLASGOW_HASKELL__
429 -- Copied here to avoid recursive dependency with Control.Exception
430 bracket 
431         :: IO a         -- ^ computation to run first (\"acquire resource\")
432         -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
433         -> (a -> IO c)  -- ^ computation to run in-between
434         -> IO c         -- returns the value from the in-between computation
435 bracket before after thing =
436   block (do
437     a <- before 
438     r <- catchException
439            (unblock (thing a))
440            (\e -> do { after a; throw e })
441     after a
442     return r
443  )
444 #endif