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