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