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