233148b0eaffffa011ccb91673cacb6e5820d0c8
[ghc-base.git] / GHC / IOBase.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -fno-implicit-prelude #-}
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  GHC.IOBase
6 -- Copyright   :  (c) The University of Glasgow 1994-2002
7 -- License     :  see libraries/base/LICENSE
8 -- 
9 -- Maintainer  :  cvs-ghc@haskell.org
10 -- Stability   :  internal
11 -- Portability :  non-portable (GHC Extensions)
12 --
13 -- Definitions for the 'IO' monad and its friends.
14 --
15 -----------------------------------------------------------------------------
16
17 module GHC.IOBase where
18
19 import GHC.ST
20 import GHC.Arr  -- to derive Ix class
21 import GHC.Enum -- to derive Enum class
22 import GHC.STRef
23 import GHC.Base
24 import GHC.Num  -- To get fromInteger etc, needed because of -fno-implicit-prelude
25 import Data.Maybe  ( Maybe(..) )
26 import GHC.Show
27 import GHC.List
28 import GHC.Read
29
30 #ifndef __HADDOCK__
31 import {-# SOURCE #-} Data.Dynamic
32 #endif
33
34 -- ---------------------------------------------------------------------------
35 -- The IO Monad
36
37 {-
38 The IO Monad is just an instance of the ST monad, where the state is
39 the real world.  We use the exception mechanism (in GHC.Exception) to
40 implement IO exceptions.
41
42 NOTE: The IO representation is deeply wired in to various parts of the
43 system.  The following list may or may not be exhaustive:
44
45 Compiler  - types of various primitives in PrimOp.lhs
46
47 RTS       - forceIO (StgMiscClosures.hc)
48           - catchzh_fast, (un)?blockAsyncExceptionszh_fast, raisezh_fast 
49             (Exceptions.hc)
50           - raiseAsync (Schedule.c)
51
52 Prelude   - GHC.IOBase.lhs, and several other places including
53             GHC.Exception.lhs.
54
55 Libraries - parts of hslibs/lang.
56
57 --SDM
58 -}
59
60 {-|
61 A value of type @'IO' a@ is a computation which, when performed,
62 does some I\/O before returning a value of type @a@.  
63
64 There is really only one way to \"perform\" an I\/O action: bind it to
65 @Main.main@ in your program.  When your program is run, the I\/O will
66 be performed.  It isn't possible to perform I\/O from an arbitrary
67 function, unless that function is itself in the 'IO' monad and called
68 at some point, directly or indirectly, from @Main.main@.
69
70 'IO' is a monad, so 'IO' actions can be combined using either the do-notation
71 or the '>>' and '>>=' operations from the 'Monad' class.
72 -}
73 newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
74
75 unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #))
76 unIO (IO a) = a
77
78 instance  Functor IO where
79    fmap f x = x >>= (return . f)
80
81 instance  Monad IO  where
82     {-# INLINE return #-}
83     {-# INLINE (>>)   #-}
84     {-# INLINE (>>=)  #-}
85     m >> k      =  m >>= \ _ -> k
86     return x    = returnIO x
87
88     m >>= k     = bindIO m k
89     fail s      = failIO s
90
91 failIO :: String -> IO a
92 failIO s = ioError (userError s)
93
94 liftIO :: IO a -> State# RealWorld -> STret RealWorld a
95 liftIO (IO m) = \s -> case m s of (# s', r #) -> STret s' r
96
97 bindIO :: IO a -> (a -> IO b) -> IO b
98 bindIO (IO m) k = IO ( \ s ->
99   case m s of 
100     (# new_s, a #) -> unIO (k a) new_s
101   )
102
103 thenIO :: IO a -> IO b -> IO b
104 thenIO (IO m) k = IO ( \ s ->
105   case m s of 
106     (# new_s, a #) -> unIO k new_s
107   )
108
109 returnIO :: a -> IO a
110 returnIO x = IO (\ s -> (# s, x #))
111
112 -- ---------------------------------------------------------------------------
113 -- Coercions between IO and ST
114
115 -- | A monad transformer embedding strict state transformers in the 'IO'
116 -- monad.  The 'RealWorld' parameter indicates that the internal state
117 -- used by the 'ST' computation is a special one supplied by the 'IO'
118 -- monad, and thus distinct from those used by invocations of 'runST'.
119 stToIO        :: ST RealWorld a -> IO a
120 stToIO (ST m) = IO m
121
122 ioToST        :: IO a -> ST RealWorld a
123 ioToST (IO m) = (ST m)
124
125 -- This relies on IO and ST having the same representation modulo the
126 -- constraint on the type of the state
127 --
128 unsafeIOToST        :: IO a -> ST s a
129 unsafeIOToST (IO io) = ST $ \ s -> (unsafeCoerce# io) s
130
131 -- ---------------------------------------------------------------------------
132 -- Unsafe IO operations
133
134 {-|
135 This is the \"back door\" into the 'IO' monad, allowing
136 'IO' computation to be performed at any time.  For
137 this to be safe, the 'IO' computation should be
138 free of side effects and independent of its environment.
139
140 If the I\/O computation wrapped in 'unsafePerformIO'
141 performs side effects, then the relative order in which those side
142 effects take place (relative to the main I\/O trunk, or other calls to
143 'unsafePerformIO') is indeterminate.  You have to be careful when 
144 writing and compiling modules that use 'unsafePerformIO':
145
146   * Use @{\-\# NOINLINE foo \#-\}@ as a pragma on any function @foo@
147         that calls 'unsafePerformIO'.  If the call is inlined,
148         the I\/O may be performed more than once.
149
150   * Use the compiler flag @-fno-cse@ to prevent common sub-expression
151         elimination being performed on the module, which might combine
152         two side effects that were meant to be separate.  A good example
153         is using multiple global variables (like @test@ in the example below).
154
155   * Make sure that the either you switch off let-floating, or that the 
156         call to 'unsafePerformIO' cannot float outside a lambda.  For example, 
157         if you say:
158         @
159            f x = unsafePerformIO (newIORef [])
160         @
161         you may get only one reference cell shared between all calls to @f@.
162         Better would be
163         @
164            f x = unsafePerformIO (newIORef [x])
165         @
166         because now it can't float outside the lambda.
167
168 It is less well known that
169 'unsafePerformIO' is not type safe.  For example:
170
171 >     test :: IORef [a]
172 >     test = unsafePerformIO $ newIORef []
173 >     
174 >     main = do
175 >             writeIORef test [42]
176 >             bang <- readIORef test
177 >             print (bang :: [Char])
178
179 This program will core dump.  This problem with polymorphic references
180 is well known in the ML community, and does not arise with normal
181 monadic use of references.  There is no easy way to make it impossible
182 once you use 'unsafePerformIO'.  Indeed, it is
183 possible to write @coerce :: a -> b@ with the
184 help of 'unsafePerformIO'.  So be careful!
185 -}
186 {-# NOINLINE unsafePerformIO #-}
187 unsafePerformIO :: IO a -> a
188 unsafePerformIO (IO m) = case m realWorld# of (# _, r #)   -> r
189
190 -- Why do we NOINLINE unsafePerformIO?  See the comment with
191 -- GHC.ST.runST.  Essentially the issue is that the IO computation
192 -- inside unsafePerformIO must be atomic: it must either all run, or
193 -- not at all.  If we let the compiler see the application of the IO
194 -- to realWorld#, it might float out part of the IO.
195
196 {-|
197 'unsafeInterleaveIO' allows 'IO' computation to be deferred lazily.
198 When passed a value of type @IO a@, the 'IO' will only be performed
199 when the value of the @a@ is demanded.  This is used to implement lazy
200 file reading, see 'System.IO.hGetContents'.
201 -}
202 {-# INLINE unsafeInterleaveIO #-}
203 unsafeInterleaveIO :: IO a -> IO a
204 unsafeInterleaveIO (IO m)
205   = IO ( \ s -> let
206                    r = case m s of (# _, res #) -> res
207                 in
208                 (# s, r #))
209
210 -- We believe that INLINE on unsafeInterleaveIO is safe, because the
211 -- state from this IO thread is passed explicitly to the interleaved
212 -- IO, so it cannot be floated out and shared.
213
214 -- ---------------------------------------------------------------------------
215 -- Handle type
216
217 data MVar a = MVar (MVar# RealWorld a)
218 {- ^
219 An 'MVar' (pronounced \"em-var\") is a synchronising variable, used
220 for communication between concurrent threads.  It can be thought of
221 as a a box, which may be empty or full.
222 -}
223
224 -- pull in Eq (Mvar a) too, to avoid GHC.Conc being an orphan-instance module
225 instance Eq (MVar a) where
226         (MVar mvar1#) == (MVar mvar2#) = sameMVar# mvar1# mvar2#
227
228 --  A Handle is represented by (a reference to) a record 
229 --  containing the state of the I/O port/device. We record
230 --  the following pieces of info:
231
232 --    * type (read,write,closed etc.)
233 --    * the underlying file descriptor
234 --    * buffering mode 
235 --    * buffer, and spare buffers
236 --    * user-friendly name (usually the
237 --      FilePath used when IO.openFile was called)
238
239 -- Note: when a Handle is garbage collected, we want to flush its buffer
240 -- and close the OS file handle, so as to free up a (precious) resource.
241
242 -- | Haskell defines operations to read and write characters from and to files,
243 -- represented by values of type @Handle@.  Each value of this type is a
244 -- /handle/: a record used by the Haskell run-time system to /manage/ I\/O
245 -- with file system objects.  A handle has at least the following properties:
246 -- 
247 --  * whether it manages input or output or both;
248 --
249 --  * whether it is /open/, /closed/ or /semi-closed/;
250 --
251 --  * whether the object is seekable;
252 --
253 --  * whether buffering is disabled, or enabled on a line or block basis;
254 --
255 --  * a buffer (whose length may be zero).
256 --
257 -- Most handles will also have a current I\/O position indicating where the next
258 -- input or output operation will occur.  A handle is /readable/ if it
259 -- manages only input or both input and output; likewise, it is /writable/ if
260 -- it manages only output or both input and output.  A handle is /open/ when
261 -- first allocated.
262 -- Once it is closed it can no longer be used for either input or output,
263 -- though an implementation cannot re-use its storage while references
264 -- remain to it.  Handles are in the 'Show' and 'Eq' classes.  The string
265 -- produced by showing a handle is system dependent; it should include
266 -- enough information to identify the handle for debugging.  A handle is
267 -- equal according to '==' only to itself; no attempt
268 -- is made to compare the internal state of different handles for equality.
269 --
270 -- GHC note: a 'Handle' will be automatically closed when the garbage
271 -- collector detects that it has become unreferenced by the program.
272 -- However, relying on this behaviour is not generally recommended:
273 -- the garbage collector is unpredictable.  If possible, use explicit
274 -- an explicit 'hClose' to close 'Handle's when they are no longer
275 -- required.  GHC does not currently attempt to free up file
276 -- descriptors when they have run out, it is your responsibility to
277 -- ensure that this doesn't happen.
278
279 data Handle 
280   = FileHandle                          -- A normal handle to a file
281         FilePath                        -- the file (invariant)
282         !(MVar Handle__)
283
284   | DuplexHandle                        -- A handle to a read/write stream
285         FilePath                        -- file for a FIFO, otherwise some
286                                         --   descriptive string.
287         !(MVar Handle__)                -- The read side
288         !(MVar Handle__)                -- The write side
289
290 -- NOTES:
291 --    * A 'FileHandle' is seekable.  A 'DuplexHandle' may or may not be
292 --      seekable.
293
294 instance Eq Handle where
295  (FileHandle _ h1)     == (FileHandle _ h2)     = h1 == h2
296  (DuplexHandle _ h1 _) == (DuplexHandle _ h2 _) = h1 == h2
297  _ == _ = False 
298
299 type FD = Int -- XXX ToDo: should be CInt
300
301 data Handle__
302   = Handle__ {
303       haFD          :: !FD,                  -- file descriptor
304       haType        :: HandleType,           -- type (read/write/append etc.)
305       haIsBin       :: Bool,                 -- binary mode?
306       haIsStream    :: Bool,                 -- is this a stream handle?
307       haBufferMode  :: BufferMode,           -- buffer contains read/write data?
308       haBuffer      :: !(IORef Buffer),      -- the current buffer
309       haBuffers     :: !(IORef BufferList),  -- spare buffers
310       haOtherSide   :: Maybe (MVar Handle__) -- ptr to the write side of a 
311                                              -- duplex handle.
312     }
313
314 -- ---------------------------------------------------------------------------
315 -- Buffers
316
317 -- The buffer is represented by a mutable variable containing a
318 -- record, where the record contains the raw buffer and the start/end
319 -- points of the filled portion.  We use a mutable variable so that
320 -- the common operation of writing (or reading) some data from (to)
321 -- the buffer doesn't need to modify, and hence copy, the handle
322 -- itself, it just updates the buffer.  
323
324 -- There will be some allocation involved in a simple hPutChar in
325 -- order to create the new Buffer structure (below), but this is
326 -- relatively small, and this only has to be done once per write
327 -- operation.
328
329 -- The buffer contains its size - we could also get the size by
330 -- calling sizeOfMutableByteArray# on the raw buffer, but that tends
331 -- to be rounded up to the nearest Word.
332
333 type RawBuffer = MutableByteArray# RealWorld
334
335 -- INVARIANTS on a Buffer:
336 --
337 --   * A handle *always* has a buffer, even if it is only 1 character long
338 --     (an unbuffered handle needs a 1 character buffer in order to support
339 --      hLookAhead and hIsEOF).
340 --   * r <= w
341 --   * if r == w, then r == 0 && w == 0
342 --   * if state == WriteBuffer, then r == 0
343 --   * a write buffer is never full.  If an operation
344 --     fills up the buffer, it will always flush it before 
345 --     returning.
346 --   * a read buffer may be full as a result of hLookAhead.  In normal
347 --     operation, a read buffer always has at least one character of space.
348
349 data Buffer 
350   = Buffer {
351         bufBuf   :: RawBuffer,
352         bufRPtr  :: !Int,
353         bufWPtr  :: !Int,
354         bufSize  :: !Int,
355         bufState :: BufferState
356   }
357
358 data BufferState = ReadBuffer | WriteBuffer deriving (Eq)
359
360 -- we keep a few spare buffers around in a handle to avoid allocating
361 -- a new one for each hPutStr.  These buffers are *guaranteed* to be the
362 -- same size as the main buffer.
363 data BufferList 
364   = BufferListNil 
365   | BufferListCons RawBuffer BufferList
366
367
368 bufferIsWritable :: Buffer -> Bool
369 bufferIsWritable Buffer{ bufState=WriteBuffer } = True
370 bufferIsWritable _other = False
371
372 bufferEmpty :: Buffer -> Bool
373 bufferEmpty Buffer{ bufRPtr=r, bufWPtr=w } = r == w
374
375 -- only makes sense for a write buffer
376 bufferFull :: Buffer -> Bool
377 bufferFull b@Buffer{ bufWPtr=w } = w >= bufSize b
378
379 --  Internally, we classify handles as being one
380 --  of the following:
381
382 data HandleType
383  = ClosedHandle
384  | SemiClosedHandle
385  | ReadHandle
386  | WriteHandle
387  | AppendHandle
388  | ReadWriteHandle
389
390 isReadableHandleType ReadHandle         = True
391 isReadableHandleType ReadWriteHandle    = True
392 isReadableHandleType _                  = False
393
394 isWritableHandleType AppendHandle    = True
395 isWritableHandleType WriteHandle     = True
396 isWritableHandleType ReadWriteHandle = True
397 isWritableHandleType _               = False
398
399 -- | File and directory names are values of type 'String', whose precise
400 -- meaning is operating system dependent. Files can be opened, yielding a
401 -- handle which can then be used to operate on the contents of that file.
402
403 type FilePath = String
404
405 -- ---------------------------------------------------------------------------
406 -- Buffering modes
407
408 -- | Three kinds of buffering are supported: line-buffering, 
409 -- block-buffering or no-buffering.  These modes have the following
410 -- effects. For output, items are written out, or /flushed/,
411 -- from the internal buffer according to the buffer mode:
412 --
413 --  * /line-buffering/: the entire output buffer is flushed
414 --    whenever a newline is output, the buffer overflows, 
415 --    a 'System.IO.hFlush' is issued, or the handle is closed.
416 --
417 --  * /block-buffering/: the entire buffer is written out whenever it
418 --    overflows, a 'System.IO.hFlush' is issued, or the handle is closed.
419 --
420 --  * /no-buffering/: output is written immediately, and never stored
421 --    in the buffer.
422 --
423 -- An implementation is free to flush the buffer more frequently,
424 -- but not less frequently, than specified above.
425 -- The output buffer is emptied as soon as it has been written out.
426 --
427 -- Similarly, input occurs according to the buffer mode for the handle:
428 --
429 --  * /line-buffering/: when the buffer for the handle is not empty,
430 --    the next item is obtained from the buffer; otherwise, when the
431 --    buffer is empty, characters up to and including the next newline
432 --    character are read into the buffer.  No characters are available
433 --    until the newline character is available or the buffer is full.
434 --
435 --  * /block-buffering/: when the buffer for the handle becomes empty,
436 --    the next block of data is read into the buffer.
437 --
438 --  * /no-buffering/: the next input item is read and returned.
439 --    The 'System.IO.hLookAhead' operation implies that even a no-buffered
440 --    handle may require a one-character buffer.
441 --
442 -- The default buffering mode when a handle is opened is
443 -- implementation-dependent and may depend on the file system object
444 -- which is attached to that handle.
445 -- For most implementations, physical files will normally be block-buffered 
446 -- and terminals will normally be line-buffered.
447
448 data BufferMode  
449  = NoBuffering  -- ^ buffering is disabled if possible.
450  | LineBuffering
451                 -- ^ line-buffering should be enabled if possible.
452  | BlockBuffering (Maybe Int)
453                 -- ^ block-buffering should be enabled if possible.
454                 -- The size of the buffer is @n@ items if the argument
455                 -- is 'Just' @n@ and is otherwise implementation-dependent.
456    deriving (Eq, Ord, Read, Show)
457
458 -- ---------------------------------------------------------------------------
459 -- IORefs
460
461 -- |A mutable variable in the 'IO' monad
462 newtype IORef a = IORef (STRef RealWorld a)
463
464 -- explicit instance because Haddock can't figure out a derived one
465 instance Eq (IORef a) where
466   IORef x == IORef y = x == y
467
468 -- |Build a new 'IORef'
469 newIORef    :: a -> IO (IORef a)
470 newIORef v = stToIO (newSTRef v) >>= \ var -> return (IORef var)
471
472 -- |Read the value of an 'IORef'
473 readIORef   :: IORef a -> IO a
474 readIORef  (IORef var) = stToIO (readSTRef var)
475
476 -- |Write a new value into an 'IORef'
477 writeIORef  :: IORef a -> a -> IO ()
478 writeIORef (IORef var) v = stToIO (writeSTRef var v)
479
480 -- ---------------------------------------------------------------------------
481 -- | An 'IOArray' is a mutable, boxed, non-strict array in the 'IO' monad.  
482 -- The type arguments are as follows:
483 --
484 --  * @i@: the index type of the array (should be an instance of 'Ix')
485 --
486 --  * @e@: the element type of the array.
487 --
488 -- 
489
490 newtype IOArray i e = IOArray (STArray RealWorld i e)
491
492 -- explicit instance because Haddock can't figure out a derived one
493 instance Eq (IOArray i e) where
494   IOArray x == IOArray y = x == y
495
496 -- |Build a new 'IOArray'
497 newIOArray :: Ix i => (i,i) -> e -> IO (IOArray i e)
498 {-# INLINE newIOArray #-}
499 newIOArray lu init  = stToIO $ do {marr <- newSTArray lu init; return (IOArray marr)}
500
501 -- | Read a value from an 'IOArray'
502 unsafeReadIOArray  :: Ix i => IOArray i e -> Int -> IO e
503 {-# INLINE unsafeReadIOArray #-}
504 unsafeReadIOArray (IOArray marr) i = stToIO (unsafeReadSTArray marr i)
505
506 -- | Write a new value into an 'IOArray'
507 unsafeWriteIOArray :: Ix i => IOArray i e -> Int -> e -> IO ()
508 {-# INLINE unsafeWriteIOArray #-}
509 unsafeWriteIOArray (IOArray marr) i e = stToIO (unsafeWriteSTArray marr i e)
510
511 -- | Read a value from an 'IOArray'
512 readIOArray  :: Ix i => IOArray i e -> i -> IO e
513 readIOArray (IOArray marr) i = stToIO (readSTArray marr i)
514
515 -- | Write a new value into an 'IOArray'
516 writeIOArray :: Ix i => IOArray i e -> i -> e -> IO ()
517 writeIOArray (IOArray marr) i e = stToIO (writeSTArray marr i e)
518
519
520 -- ---------------------------------------------------------------------------
521 -- Show instance for Handles
522
523 -- handle types are 'show'n when printing error msgs, so
524 -- we provide a more user-friendly Show instance for it
525 -- than the derived one.
526
527 instance Show HandleType where
528   showsPrec p t =
529     case t of
530       ClosedHandle      -> showString "closed"
531       SemiClosedHandle  -> showString "semi-closed"
532       ReadHandle        -> showString "readable"
533       WriteHandle       -> showString "writable"
534       AppendHandle      -> showString "writable (append)"
535       ReadWriteHandle   -> showString "read-writable"
536
537 instance Show Handle where 
538   showsPrec p (FileHandle   file _)   = showHandle file
539   showsPrec p (DuplexHandle file _ _) = showHandle file
540
541 showHandle file = showString "{handle: " . showString file . showString "}"
542
543 -- ------------------------------------------------------------------------
544 -- Exception datatype and operations
545
546 -- |The type of exceptions.  Every kind of system-generated exception
547 -- has a constructor in the 'Exception' type, and values of other
548 -- types may be injected into 'Exception' by coercing them to
549 -- 'Data.Dynamic.Dynamic' (see the section on Dynamic Exceptions:
550 -- "Control.Exception\#DynamicExceptions").
551 data Exception
552   = ArithException      ArithException
553         -- ^Exceptions raised by arithmetic
554         -- operations.  (NOTE: GHC currently does not throw
555         -- 'ArithException's except for 'DivideByZero').
556   | ArrayException      ArrayException
557         -- ^Exceptions raised by array-related
558         -- operations.  (NOTE: GHC currently does not throw
559         -- 'ArrayException's).
560   | AssertionFailed     String
561         -- ^This exception is thrown by the
562         -- 'assert' operation when the condition
563         -- fails.  The 'String' argument contains the
564         -- location of the assertion in the source program.
565   | AsyncException      AsyncException
566         -- ^Asynchronous exceptions (see section on Asynchronous Exceptions: "Control.Exception\#AsynchronousExceptions").
567   | BlockedOnDeadMVar
568         -- ^The current thread was executing a call to
569         -- 'Control.Concurrent.MVar.takeMVar' that could never return,
570         -- because there are no other references to this 'MVar'.
571   | BlockedIndefinitely
572         -- ^The current thread was waiting to retry an atomic memory transaction
573         -- that could never become possible to complete because there are no other
574         -- threads referring to any of teh TVars involved.
575   | Deadlock
576         -- ^There are no runnable threads, so the program is
577         -- deadlocked.  The 'Deadlock' exception is
578         -- raised in the main thread only (see also: "Control.Concurrent").
579   | DynException        Dynamic
580         -- ^Dynamically typed exceptions (see section on Dynamic Exceptions: "Control.Exception\#DynamicExceptions").
581   | ErrorCall           String
582         -- ^The 'ErrorCall' exception is thrown by 'error'.  The 'String'
583         -- argument of 'ErrorCall' is the string passed to 'error' when it was
584         -- called.
585   | ExitException       ExitCode
586         -- ^The 'ExitException' exception is thrown by 'System.Exit.exitWith' (and
587         -- 'System.Exit.exitFailure').  The 'ExitCode' argument is the value passed 
588         -- to 'System.Exit.exitWith'.  An unhandled 'ExitException' exception in the
589         -- main thread will cause the program to be terminated with the given 
590         -- exit code.
591   | IOException         IOException
592         -- ^These are the standard IO exceptions generated by
593         -- Haskell\'s @IO@ operations.  See also "System.IO.Error".
594   | NoMethodError       String
595         -- ^An attempt was made to invoke a class method which has
596         -- no definition in this instance, and there was no default
597         -- definition given in the class declaration.  GHC issues a
598         -- warning when you compile an instance which has missing
599         -- methods.
600   | NonTermination
601         -- ^The current thread is stuck in an infinite loop.  This
602         -- exception may or may not be thrown when the program is
603         -- non-terminating.
604   | PatternMatchFail    String
605         -- ^A pattern matching failure.  The 'String' argument should contain a
606         -- descriptive message including the function name, source file
607         -- and line number.
608   | RecConError         String
609         -- ^An attempt was made to evaluate a field of a record
610         -- for which no value was given at construction time.  The
611         -- 'String' argument gives the location of the
612         -- record construction in the source program.
613   | RecSelError         String
614         -- ^A field selection was attempted on a constructor that
615         -- doesn\'t have the requested field.  This can happen with
616         -- multi-constructor records when one or more fields are
617         -- missing from some of the constructors.  The
618         -- 'String' argument gives the location of the
619         -- record selection in the source program.
620   | RecUpdError         String
621         -- ^An attempt was made to update a field in a record,
622         -- where the record doesn\'t have the requested field.  This can
623         -- only occur with multi-constructor records, when one or more
624         -- fields are missing from some of the constructors.  The
625         -- 'String' argument gives the location of the
626         -- record update in the source program.
627
628 -- |The type of arithmetic exceptions
629 data ArithException
630   = Overflow
631   | Underflow
632   | LossOfPrecision
633   | DivideByZero
634   | Denormal
635   deriving (Eq, Ord)
636
637
638 -- |Asynchronous exceptions
639 data AsyncException
640   = StackOverflow
641         -- ^The current thread\'s stack exceeded its limit.
642         -- Since an exception has been raised, the thread\'s stack
643         -- will certainly be below its limit again, but the
644         -- programmer should take remedial action
645         -- immediately.
646   | HeapOverflow
647         -- ^The program\'s heap is reaching its limit, and
648         -- the program should take action to reduce the amount of
649         -- live data it has. Notes:
650         --
651         --      * It is undefined which thread receives this exception.
652         --
653         --      * GHC currently does not throw 'HeapOverflow' exceptions.
654   | ThreadKilled
655         -- ^This exception is raised by another thread
656         -- calling 'Control.Concurrent.killThread', or by the system
657         -- if it needs to terminate the thread for some
658         -- reason.
659   deriving (Eq, Ord)
660
661 -- | Exceptions generated by array operations
662 data ArrayException
663   = IndexOutOfBounds    String
664         -- ^An attempt was made to index an array outside
665         -- its declared bounds.
666   | UndefinedElement    String
667         -- ^An attempt was made to evaluate an element of an
668         -- array that had not been initialized.
669   deriving (Eq, Ord)
670
671 stackOverflow, heapOverflow :: Exception -- for the RTS
672 stackOverflow = AsyncException StackOverflow
673 heapOverflow  = AsyncException HeapOverflow
674
675 instance Show ArithException where
676   showsPrec _ Overflow        = showString "arithmetic overflow"
677   showsPrec _ Underflow       = showString "arithmetic underflow"
678   showsPrec _ LossOfPrecision = showString "loss of precision"
679   showsPrec _ DivideByZero    = showString "divide by zero"
680   showsPrec _ Denormal        = showString "denormal"
681
682 instance Show AsyncException where
683   showsPrec _ StackOverflow   = showString "stack overflow"
684   showsPrec _ HeapOverflow    = showString "heap overflow"
685   showsPrec _ ThreadKilled    = showString "thread killed"
686
687 instance Show ArrayException where
688   showsPrec _ (IndexOutOfBounds s)
689         = showString "array index out of range"
690         . (if not (null s) then showString ": " . showString s
691                            else id)
692   showsPrec _ (UndefinedElement s)
693         = showString "undefined array element"
694         . (if not (null s) then showString ": " . showString s
695                            else id)
696
697 instance Show Exception where
698   showsPrec _ (IOException err)          = shows err
699   showsPrec _ (ArithException err)       = shows err
700   showsPrec _ (ArrayException err)       = shows err
701   showsPrec _ (ErrorCall err)            = showString err
702   showsPrec _ (ExitException err)        = showString "exit: " . shows err
703   showsPrec _ (NoMethodError err)        = showString err
704   showsPrec _ (PatternMatchFail err)     = showString err
705   showsPrec _ (RecSelError err)          = showString err
706   showsPrec _ (RecConError err)          = showString err
707   showsPrec _ (RecUpdError err)          = showString err
708   showsPrec _ (AssertionFailed err)      = showString err
709   showsPrec _ (DynException _err)        = showString "unknown exception"
710   showsPrec _ (AsyncException e)         = shows e
711   showsPrec _ (BlockedOnDeadMVar)        = showString "thread blocked indefinitely"
712   showsPrec _ (BlockedIndefinitely)      = showString "thread blocked indefinitely"
713   showsPrec _ (NonTermination)           = showString "<<loop>>"
714   showsPrec _ (Deadlock)                 = showString "<<deadlock>>"
715
716 instance Eq Exception where
717   IOException e1      == IOException e2      = e1 == e2
718   ArithException e1   == ArithException e2   = e1 == e2
719   ArrayException e1   == ArrayException e2   = e1 == e2
720   ErrorCall e1        == ErrorCall e2        = e1 == e2
721   ExitException e1    == ExitException e2    = e1 == e2
722   NoMethodError e1    == NoMethodError e2    = e1 == e2
723   PatternMatchFail e1 == PatternMatchFail e2 = e1 == e2
724   RecSelError e1      == RecSelError e2      = e1 == e2
725   RecConError e1      == RecConError e2      = e1 == e2
726   RecUpdError e1      == RecUpdError e2      = e1 == e2
727   AssertionFailed e1  == AssertionFailed e2  = e1 == e2
728   DynException _      == DynException _      = False -- incomparable
729   AsyncException e1   == AsyncException e2   = e1 == e2
730   BlockedOnDeadMVar   == BlockedOnDeadMVar   = True
731   NonTermination      == NonTermination      = True
732   Deadlock            == Deadlock            = True
733   _                   == _                   = False
734
735 -- -----------------------------------------------------------------------------
736 -- The ExitCode type
737
738 -- We need it here because it is used in ExitException in the
739 -- Exception datatype (above).
740
741 data ExitCode
742   = ExitSuccess -- ^ indicates successful termination;
743   | ExitFailure Int
744                 -- ^ indicates program failure with an exit code.
745                 -- The exact interpretation of the code is
746                 -- operating-system dependent.  In particular, some values
747                 -- may be prohibited (e.g. 0 on a POSIX-compliant system).
748   deriving (Eq, Ord, Read, Show)
749
750 -- --------------------------------------------------------------------------
751 -- Primitive throw
752
753 -- | Throw an exception.  Exceptions may be thrown from purely
754 -- functional code, but may only be caught within the 'IO' monad.
755 throw :: Exception -> a
756 throw exception = raise# exception
757
758 -- | A variant of 'throw' that can be used within the 'IO' monad.
759 --
760 -- Although 'throwIO' has a type that is an instance of the type of 'throw', the
761 -- two functions are subtly different:
762 --
763 -- > throw e   `seq` return ()  ===> throw e
764 -- > throwIO e `seq` return ()  ===> return ()
765 --
766 -- The first example will cause the exception @e@ to be raised,
767 -- whereas the second one won\'t.  In fact, 'throwIO' will only cause
768 -- an exception to be raised when it is used within the 'IO' monad.
769 -- The 'throwIO' variant should be used in preference to 'throw' to
770 -- raise an exception within the 'IO' monad because it guarantees
771 -- ordering with respect to other 'IO' operations, whereas 'throw'
772 -- does not.
773 throwIO         :: Exception -> IO a
774 throwIO err     =  IO $ raiseIO# err
775
776 ioException     :: IOException -> IO a
777 ioException err =  IO $ raiseIO# (IOException err)
778
779 -- | Raise an 'IOError' in the 'IO' monad.
780 ioError         :: IOError -> IO a 
781 ioError         =  ioException
782
783 -- ---------------------------------------------------------------------------
784 -- IOError type
785
786 -- | The Haskell 98 type for exceptions in the 'IO' monad.
787 -- Any I\/O operation may raise an 'IOError' instead of returning a result.
788 -- For a more general type of exception, including also those that arise
789 -- in pure code, see 'Control.Exception.Exception'.
790 --
791 -- In Haskell 98, this is an opaque type.
792 type IOError = IOException
793
794 -- |Exceptions that occur in the @IO@ monad.
795 -- An @IOException@ records a more specific error type, a descriptive
796 -- string and maybe the handle that was used when the error was
797 -- flagged.
798 data IOException
799  = IOError {
800      ioe_handle   :: Maybe Handle,   -- the handle used by the action flagging 
801                                      -- the error.
802      ioe_type     :: IOErrorType,    -- what it was.
803      ioe_location :: String,         -- location.
804      ioe_description :: String,      -- error type specific information.
805      ioe_filename :: Maybe FilePath  -- filename the error is related to.
806    }
807
808 instance Eq IOException where
809   (IOError h1 e1 loc1 str1 fn1) == (IOError h2 e2 loc2 str2 fn2) = 
810     e1==e2 && str1==str2 && h1==h2 && loc1==loc2 && fn1==fn2
811
812 -- | An abstract type that contains a value for each variant of 'IOError'.
813 data IOErrorType
814   -- Haskell 98:
815   = AlreadyExists
816   | NoSuchThing
817   | ResourceBusy
818   | ResourceExhausted
819   | EOF
820   | IllegalOperation
821   | PermissionDenied
822   | UserError
823   -- GHC only:
824   | UnsatisfiedConstraints
825   | SystemError
826   | ProtocolError
827   | OtherError
828   | InvalidArgument
829   | InappropriateType
830   | HardwareFault
831   | UnsupportedOperation
832   | TimeExpired
833   | ResourceVanished
834   | Interrupted
835   | DynIOError Dynamic -- cheap&cheerful extensible IO error type.
836
837 instance Eq IOErrorType where
838    x == y = 
839      case x of
840        DynIOError{} -> False -- from a strictness POV, compatible with a derived Eq inst?
841        _ -> getTag x ==# getTag y
842  
843 instance Show IOErrorType where
844   showsPrec _ e =
845     showString $
846     case e of
847       AlreadyExists     -> "already exists"
848       NoSuchThing       -> "does not exist"
849       ResourceBusy      -> "resource busy"
850       ResourceExhausted -> "resource exhausted"
851       EOF               -> "end of file"
852       IllegalOperation  -> "illegal operation"
853       PermissionDenied  -> "permission denied"
854       UserError         -> "user error"
855       HardwareFault     -> "hardware fault"
856       InappropriateType -> "inappropriate type"
857       Interrupted       -> "interrupted"
858       InvalidArgument   -> "invalid argument"
859       OtherError        -> "failed"
860       ProtocolError     -> "protocol error"
861       ResourceVanished  -> "resource vanished"
862       SystemError       -> "system error"
863       TimeExpired       -> "timeout"
864       UnsatisfiedConstraints -> "unsatisified constraints" -- ultra-precise!
865       UnsupportedOperation -> "unsupported operation"
866       DynIOError{}      -> "unknown IO error"
867
868 -- | Construct an 'IOError' value with a string describing the error.
869 -- The 'fail' method of the 'IO' instance of the 'Monad' class raises a
870 -- 'userError', thus:
871 --
872 -- > instance Monad IO where 
873 -- >   ...
874 -- >   fail s = ioError (userError s)
875 --
876 userError       :: String  -> IOError
877 userError str   =  IOError Nothing UserError "" str Nothing
878
879 -- ---------------------------------------------------------------------------
880 -- Showing IOErrors
881
882 instance Show IOException where
883     showsPrec p (IOError hdl iot loc s fn) =
884       (case fn of
885          Nothing -> case hdl of
886                         Nothing -> id
887                         Just h  -> showsPrec p h . showString ": "
888          Just name -> showString name . showString ": ") .
889       (case loc of
890          "" -> id
891          _  -> showString loc . showString ": ") .
892       showsPrec p iot . 
893       (case s of
894          "" -> id
895          _  -> showString " (" . showString s . showString ")")
896
897 -- -----------------------------------------------------------------------------
898 -- IOMode type
899
900 data IOMode      =  ReadMode | WriteMode | AppendMode | ReadWriteMode
901                     deriving (Eq, Ord, Ix, Enum, Read, Show)
902 \end{code}