Fix nhc98 code variations to use the extensible exception API.
[ghc-base.git] / Control / Exception.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2
3 #include "Typeable.h"
4
5 -----------------------------------------------------------------------------
6 -- |
7 -- Module      :  Control.Exception
8 -- Copyright   :  (c) The University of Glasgow 2001
9 -- License     :  BSD-style (see the file libraries/base/LICENSE)
10 -- 
11 -- Maintainer  :  libraries@haskell.org
12 -- Stability   :  experimental
13 -- Portability :  non-portable (extended exceptions)
14 --
15 -- This module provides support for raising and catching both built-in
16 -- and user-defined exceptions.
17 --
18 -- In addition to exceptions thrown by 'IO' operations, exceptions may
19 -- be thrown by pure code (imprecise exceptions) or by external events
20 -- (asynchronous exceptions), but may only be caught in the 'IO' monad.
21 -- For more details, see:
22 --
23 --  * /A semantics for imprecise exceptions/, by Simon Peyton Jones,
24 --    Alastair Reid, Tony Hoare, Simon Marlow, Fergus Henderson,
25 --    in /PLDI'99/.
26 --
27 --  * /Asynchronous exceptions in Haskell/, by Simon Marlow, Simon Peyton
28 --    Jones, Andy Moran and John Reppy, in /PLDI'01/.
29 --
30 -----------------------------------------------------------------------------
31
32 module Control.Exception (
33
34         -- * The Exception type
35         SomeException(..),
36         Exception(..),          -- instance Eq, Ord, Show, Typeable
37         IOException,            -- instance Eq, Ord, Show, Typeable
38         ArithException(..),     -- instance Eq, Ord, Show, Typeable
39         ArrayException(..),     -- instance Eq, Ord, Show, Typeable
40         AssertionFailed(..),
41         AsyncException(..),     -- instance Eq, Ord, Show, Typeable
42
43 #ifdef __GLASGOW_HASKELL__
44         NonTermination(..), nonTermination,
45         NestedAtomically(..), nestedAtomically,
46 #endif
47
48         BlockedOnDeadMVar(..),
49         BlockedIndefinitely(..),
50         Deadlock(..),
51         NoMethodError(..),
52         PatternMatchFail(..),
53         RecConError(..),
54         RecSelError(..),
55         RecUpdError(..),
56         ErrorCall(..),
57
58         -- * Throwing exceptions
59         throwIO,        -- :: Exception -> IO a
60         throw,          -- :: Exception -> a
61         ioError,        -- :: IOError -> IO a
62 #ifdef __GLASGOW_HASKELL__
63         throwTo,        -- :: ThreadId -> Exception -> a
64 #endif
65
66         -- * Catching Exceptions
67
68         -- |There are several functions for catching and examining
69         -- exceptions; all of them may only be used from within the
70         -- 'IO' monad.
71
72         -- ** The @catch@ functions
73         catch,     -- :: IO a -> (Exception -> IO a) -> IO a
74 #ifdef __GLASGOW_HASKELL__
75         catches, Handler(..),
76         catchJust, -- :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a
77 #endif
78
79         -- ** The @handle@ functions
80         handle,    -- :: (Exception -> IO a) -> IO a -> IO a
81         handleJust,-- :: (Exception -> Maybe b) -> (b -> IO a) -> IO a -> IO a
82
83         -- ** The @try@ functions
84         try,       -- :: IO a -> IO (Either Exception a)
85         tryJust,   -- :: (Exception -> Maybe b) -> a    -> IO (Either b a)
86         onException,
87
88         -- ** The @evaluate@ function
89         evaluate,  -- :: a -> IO a
90
91         -- ** The @mapException@ function
92         mapException,           -- :: (Exception -> Exception) -> a -> a
93
94         -- * Asynchronous Exceptions
95
96         -- $async
97
98         -- ** Asynchronous exception control
99
100         -- |The following two functions allow a thread to control delivery of
101         -- asynchronous exceptions during a critical region.
102
103         block,          -- :: IO a -> IO a
104         unblock,        -- :: IO a -> IO a
105         blocked,        -- :: IO Bool
106
107         -- *** Applying @block@ to an exception handler
108
109         -- $block_handler
110
111         -- *** Interruptible operations
112
113         -- $interruptible
114
115         -- * Assertions
116
117         assert,         -- :: Bool -> a -> a
118
119         -- * Utilities
120
121         bracket,        -- :: IO a -> (a -> IO b) -> (a -> IO c) -> IO ()
122         bracket_,       -- :: IO a -> IO b -> IO c -> IO ()
123         bracketOnError,
124
125         finally,        -- :: IO a -> IO b -> IO a
126
127 #ifdef __GLASGOW_HASKELL__
128         recSelError, recConError, irrefutPatError, runtimeError,
129         nonExhaustiveGuardsError, patError, noMethodBindingError,
130         assertError,
131 #endif
132   ) where
133
134 #ifdef __GLASGOW_HASKELL__
135 import GHC.Base
136 import GHC.IOBase
137 import GHC.List
138 import GHC.Show
139 import GHC.IOBase as ExceptionBase
140 import GHC.Exception hiding ( Exception )
141 import GHC.Conc
142 #endif
143
144 #ifdef __HUGS__
145 import Hugs.Exception   as ExceptionBase
146 #endif
147
148 import Data.Dynamic
149 import Data.Either
150 import Data.Maybe
151
152 #ifdef __NHC__
153 import qualified System.IO.Error as H'98 (catch)
154 import System.IO.Error (ioError)
155 import IO              (bracket)
156 import DIOError         -- defn of IOError type
157 import System          (ExitCode())
158 import System.IO.Unsafe (unsafePerformIO)
159 import Unsafe.Coerce    (unsafeCoerce)
160
161 -- minimum needed for nhc98 to pretend it has Exceptions
162
163 {-
164 data Exception   = IOException    IOException
165                  | ArithException ArithException
166                  | ArrayException ArrayException
167                  | AsyncException AsyncException
168                  | ExitException  ExitCode
169                  deriving Show
170 -}
171 class ({-Typeable e,-} Show e) => Exception e where
172     toException   :: e -> SomeException
173     fromException :: SomeException -> Maybe e
174
175 data SomeException = forall e . Exception e => SomeException e
176
177 INSTANCE_TYPEABLE0(SomeException,someExceptionTc,"SomeException")
178
179 instance Show SomeException where
180     showsPrec p (SomeException e) = showsPrec p e
181 instance Exception SomeException where
182     toException se = se
183     fromException = Just
184
185 type IOException = IOError
186 instance Exception IOError where
187     toException                     = SomeException
188     fromException (SomeException e) = Just (unsafeCoerce e)
189
190 data ArithException
191 data ArrayException
192 data AsyncException
193 data AssertionFailed
194 data PatternMatchFail
195 data NoMethodError
196 data Deadlock
197 data BlockedOnDeadMVar
198 data BlockedIndefinitely
199 data ErrorCall
200 data RecConError
201 data RecSelError
202 data RecUpdError
203 instance Show ArithException
204 instance Show ArrayException
205 instance Show AsyncException
206 instance Show AssertionFailed
207 instance Show PatternMatchFail
208 instance Show NoMethodError
209 instance Show Deadlock
210 instance Show BlockedOnDeadMVar
211 instance Show BlockedIndefinitely
212 instance Show ErrorCall
213 instance Show RecConError
214 instance Show RecSelError
215 instance Show RecUpdError
216
217 catch   :: Exception e
218         => IO a         -- ^ The computation to run
219         -> (e -> IO a)  -- ^ Handler to invoke if an exception is raised
220         -> IO a
221 catch io h = H'98.catch  io  (h . fromJust . fromException . toException)
222
223 throwIO  :: Exception e => e -> IO a
224 throwIO   = ioError . fromJust . fromException . toException
225
226 throw    :: Exception e => e -> a
227 throw     = unsafePerformIO . throwIO
228
229 evaluate :: a -> IO a
230 evaluate x = x `seq` return x
231
232 assert :: Bool -> a -> a
233 assert True  x = x
234 assert False _ = throw (toException (UserError "" "Assertion failed"))
235
236 #endif
237
238 #ifndef __GLASGOW_HASKELL__
239 -- Dummy definitions for implementations lacking asynchonous exceptions
240
241 block   :: IO a -> IO a
242 block    = id
243 unblock :: IO a -> IO a
244 unblock  = id
245 blocked :: IO Bool
246 blocked  = return False
247 #endif
248
249 -----------------------------------------------------------------------------
250 -- Catching exceptions
251
252 -- |This is the simplest of the exception-catching functions.  It
253 -- takes a single argument, runs it, and if an exception is raised
254 -- the \"handler\" is executed, with the value of the exception passed as an
255 -- argument.  Otherwise, the result is returned as normal.  For example:
256 --
257 -- >   catch (openFile f ReadMode) 
258 -- >       (\e -> hPutStr stderr ("Couldn't open "++f++": " ++ show e))
259 --
260 -- For catching exceptions in pure (non-'IO') expressions, see the
261 -- function 'evaluate'.
262 --
263 -- Note that due to Haskell\'s unspecified evaluation order, an
264 -- expression may return one of several possible exceptions: consider
265 -- the expression @error \"urk\" + 1 \`div\` 0@.  Does
266 -- 'catch' execute the handler passing
267 -- @ErrorCall \"urk\"@, or @ArithError DivideByZero@?
268 --
269 -- The answer is \"either\": 'catch' makes a
270 -- non-deterministic choice about which exception to catch.  If you
271 -- call it again, you might get a different exception back.  This is
272 -- ok, because 'catch' is an 'IO' computation.
273 --
274 -- Note that 'catch' catches all types of exceptions, and is generally
275 -- used for \"cleaning up\" before passing on the exception using
276 -- 'throwIO'.  It is not good practice to discard the exception and
277 -- continue, without first checking the type of the exception (it
278 -- might be a 'ThreadKilled', for example).  In this case it is usually better
279 -- to use 'catchJust' and select the kinds of exceptions to catch.
280 --
281 -- Also note that the "Prelude" also exports a function called
282 -- 'Prelude.catch' with a similar type to 'Control.Exception.catch',
283 -- except that the "Prelude" version only catches the IO and user
284 -- families of exceptions (as required by Haskell 98).  
285 --
286 -- We recommend either hiding the "Prelude" version of 'Prelude.catch'
287 -- when importing "Control.Exception": 
288 --
289 -- > import Prelude hiding (catch)
290 --
291 -- or importing "Control.Exception" qualified, to avoid name-clashes:
292 --
293 -- > import qualified Control.Exception as C
294 --
295 -- and then using @C.catch@
296 --
297 #ifndef __NHC__
298 catch   :: Exception e
299         => IO a         -- ^ The computation to run
300         -> (e -> IO a)  -- ^ Handler to invoke if an exception is raised
301         -> IO a
302 catch = ExceptionBase.catchException
303 #endif
304
305 catches :: IO a -> [Handler a] -> IO a
306 catches io handlers = io `catch` catchesHandler handlers
307
308 catchesHandler :: [Handler a] -> SomeException -> IO a
309 catchesHandler handlers e = foldr tryHandler (throw e) handlers
310     where tryHandler (Handler handler) res
311               = case fromException e of
312                 Just e' -> handler e'
313                 Nothing -> res
314
315 data Handler a = forall e . Exception e => Handler (e -> IO a)
316 -- | The function 'catchJust' is like 'catch', but it takes an extra
317 -- argument which is an /exception predicate/, a function which
318 -- selects which type of exceptions we\'re interested in.
319 --
320 -- >   result <- catchJust errorCalls thing_to_try handler
321 --
322 -- Any other exceptions which are not matched by the predicate
323 -- are re-raised, and may be caught by an enclosing
324 -- 'catch' or 'catchJust'.
325 catchJust
326         :: Exception e
327         => (e -> Maybe b)         -- ^ Predicate to select exceptions
328         -> IO a                   -- ^ Computation to run
329         -> (b -> IO a)            -- ^ Handler
330         -> IO a
331 catchJust p a handler = catch a handler'
332   where handler' e = case p e of 
333                         Nothing -> throw e
334                         Just b  -> handler b
335
336 -- | A version of 'catch' with the arguments swapped around; useful in
337 -- situations where the code for the handler is shorter.  For example:
338 --
339 -- >   do handle (\e -> exitWith (ExitFailure 1)) $
340 -- >      ...
341 handle     :: Exception e => (e -> IO a) -> IO a -> IO a
342 handle     =  flip catch
343
344 -- | A version of 'catchJust' with the arguments swapped around (see
345 -- 'handle').
346 handleJust :: Exception e => (e -> Maybe b) -> (b -> IO a) -> IO a -> IO a
347 handleJust p =  flip (catchJust p)
348
349 -----------------------------------------------------------------------------
350 -- 'mapException'
351
352 -- | This function maps one exception into another as proposed in the
353 -- paper \"A semantics for imprecise exceptions\".
354
355 -- Notice that the usage of 'unsafePerformIO' is safe here.
356
357 mapException :: Exception e => (e -> e) -> a -> a
358 mapException f v = unsafePerformIO (catch (evaluate v)
359                                           (\x -> throw (f x)))
360
361 -----------------------------------------------------------------------------
362 -- 'try' and variations.
363
364 -- | Similar to 'catch', but returns an 'Either' result which is
365 -- @('Right' a)@ if no exception was raised, or @('Left' e)@ if an
366 -- exception was raised and its value is @e@.
367 --
368 -- >  try a = catch (Right `liftM` a) (return . Left)
369 --
370 -- Note: as with 'catch', it is only polite to use this variant if you intend
371 -- to re-throw the exception after performing whatever cleanup is needed.
372 -- Otherwise, 'tryJust' is generally considered to be better.
373 --
374 -- Also note that "System.IO.Error" also exports a function called
375 -- 'System.IO.Error.try' with a similar type to 'Control.Exception.try',
376 -- except that it catches only the IO and user families of exceptions
377 -- (as required by the Haskell 98 @IO@ module).
378
379 try :: Exception e => IO a -> IO (Either e a)
380 try a = catch (a >>= \ v -> return (Right v)) (\e -> return (Left e))
381
382 -- | A variant of 'try' that takes an exception predicate to select
383 -- which exceptions are caught (c.f. 'catchJust').  If the exception
384 -- does not match the predicate, it is re-thrown.
385 tryJust :: Exception e => (e -> Maybe b) -> IO a -> IO (Either b a)
386 tryJust p a = do
387   r <- try a
388   case r of
389         Right v -> return (Right v)
390         Left  e -> case p e of
391                         Nothing -> throw e
392                         Just b  -> return (Left b)
393
394 onException :: IO a -> IO b -> IO a
395 onException io what = io `catch` \e -> do what
396                                           throw (e :: SomeException)
397
398 -----------------------------------------------------------------------------
399 -- Some Useful Functions
400
401 -- | When you want to acquire a resource, do some work with it, and
402 -- then release the resource, it is a good idea to use 'bracket',
403 -- because 'bracket' will install the necessary exception handler to
404 -- release the resource in the event that an exception is raised
405 -- during the computation.  If an exception is raised, then 'bracket' will 
406 -- re-raise the exception (after performing the release).
407 --
408 -- A common example is opening a file:
409 --
410 -- > bracket
411 -- >   (openFile "filename" ReadMode)
412 -- >   (hClose)
413 -- >   (\handle -> do { ... })
414 --
415 -- The arguments to 'bracket' are in this order so that we can partially apply 
416 -- it, e.g.:
417 --
418 -- > withFile name mode = bracket (openFile name mode) hClose
419 --
420 #ifndef __NHC__
421 bracket 
422         :: IO a         -- ^ computation to run first (\"acquire resource\")
423         -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
424         -> (a -> IO c)  -- ^ computation to run in-between
425         -> IO c         -- returns the value from the in-between computation
426 bracket before after thing =
427   block (do
428     a <- before 
429     r <- unblock (thing a) `onException` after a
430     after a
431     return r
432  )
433 #endif
434
435 -- | A specialised variant of 'bracket' with just a computation to run
436 -- afterward.
437 -- 
438 finally :: IO a         -- ^ computation to run first
439         -> IO b         -- ^ computation to run afterward (even if an exception 
440                         -- was raised)
441         -> IO a         -- returns the value from the first computation
442 a `finally` sequel =
443   block (do
444     r <- unblock a `onException` sequel
445     sequel
446     return r
447   )
448
449 -- | A variant of 'bracket' where the return value from the first computation
450 -- is not required.
451 bracket_ :: IO a -> IO b -> IO c -> IO c
452 bracket_ before after thing = bracket before (const after) (const thing)
453
454 -- | Like bracket, but only performs the final action if there was an 
455 -- exception raised by the in-between computation.
456 bracketOnError
457         :: IO a         -- ^ computation to run first (\"acquire resource\")
458         -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
459         -> (a -> IO c)  -- ^ computation to run in-between
460         -> IO c         -- returns the value from the in-between computation
461 bracketOnError before after thing =
462   block (do
463     a <- before 
464     unblock (thing a) `onException` after a
465   )
466
467 -- -----------------------------------------------------------------------------
468 -- Asynchronous exceptions
469
470 {- $async
471
472  #AsynchronousExceptions# Asynchronous exceptions are so-called because they arise due to
473 external influences, and can be raised at any point during execution.
474 'StackOverflow' and 'HeapOverflow' are two examples of
475 system-generated asynchronous exceptions.
476
477 The primary source of asynchronous exceptions, however, is
478 'throwTo':
479
480 >  throwTo :: ThreadId -> Exception -> IO ()
481
482 'throwTo' (also 'throwDynTo' and 'Control.Concurrent.killThread') allows one
483 running thread to raise an arbitrary exception in another thread.  The
484 exception is therefore asynchronous with respect to the target thread,
485 which could be doing anything at the time it receives the exception.
486 Great care should be taken with asynchronous exceptions; it is all too
487 easy to introduce race conditions by the over zealous use of
488 'throwTo'.
489 -}
490
491 {- $block_handler
492 There\'s an implied 'block' around every exception handler in a call
493 to one of the 'catch' family of functions.  This is because that is
494 what you want most of the time - it eliminates a common race condition
495 in starting an exception handler, because there may be no exception
496 handler on the stack to handle another exception if one arrives
497 immediately.  If asynchronous exceptions are blocked on entering the
498 handler, though, we have time to install a new exception handler
499 before being interrupted.  If this weren\'t the default, one would have
500 to write something like
501
502 >      block (
503 >           catch (unblock (...))
504 >                      (\e -> handler)
505 >      )
506
507 If you need to unblock asynchronous exceptions again in the exception
508 handler, just use 'unblock' as normal.
509
510 Note that 'try' and friends /do not/ have a similar default, because
511 there is no exception handler in this case.  If you want to use 'try'
512 in an asynchronous-exception-safe way, you will need to use
513 'block'.
514 -}
515
516 {- $interruptible
517
518 Some operations are /interruptible/, which means that they can receive
519 asynchronous exceptions even in the scope of a 'block'.  Any function
520 which may itself block is defined as interruptible; this includes
521 'Control.Concurrent.MVar.takeMVar'
522 (but not 'Control.Concurrent.MVar.tryTakeMVar'),
523 and most operations which perform
524 some I\/O with the outside world.  The reason for having
525 interruptible operations is so that we can write things like
526
527 >      block (
528 >         a <- takeMVar m
529 >         catch (unblock (...))
530 >               (\e -> ...)
531 >      )
532
533 if the 'Control.Concurrent.MVar.takeMVar' was not interruptible,
534 then this particular
535 combination could lead to deadlock, because the thread itself would be
536 blocked in a state where it can\'t receive any asynchronous exceptions.
537 With 'Control.Concurrent.MVar.takeMVar' interruptible, however, we can be
538 safe in the knowledge that the thread can receive exceptions right up
539 until the point when the 'Control.Concurrent.MVar.takeMVar' succeeds.
540 Similar arguments apply for other interruptible operations like
541 'System.IO.openFile'.
542 -}
543
544 #if !(__GLASGOW_HASKELL__ || __NHC__)
545 assert :: Bool -> a -> a
546 assert True x = x
547 assert False _ = throw (AssertionFailed "")
548 #endif
549
550 #ifndef __NHC__
551 recSelError, recConError, irrefutPatError, runtimeError,
552              nonExhaustiveGuardsError, patError, noMethodBindingError
553         :: Addr# -> a   -- All take a UTF8-encoded C string
554
555 recSelError              s = throw (RecSelError (unpackCStringUtf8# s)) -- No location info unfortunately
556 runtimeError             s = error (unpackCStringUtf8# s)               -- No location info unfortunately
557
558 nonExhaustiveGuardsError s = throw (PatternMatchFail (untangle s "Non-exhaustive guards in"))
559 irrefutPatError          s = throw (PatternMatchFail (untangle s "Irrefutable pattern failed for pattern"))
560 recConError              s = throw (RecConError      (untangle s "Missing field in record construction"))
561 noMethodBindingError     s = throw (NoMethodError    (untangle s "No instance nor default method for class operation"))
562 patError                 s = throw (PatternMatchFail (untangle s "Non-exhaustive patterns in"))
563
564 -----
565
566 data PatternMatchFail = PatternMatchFail String
567 INSTANCE_TYPEABLE0(PatternMatchFail,patternMatchFailTc,"PatternMatchFail")
568
569 instance Exception PatternMatchFail
570
571 instance Show PatternMatchFail where
572     showsPrec _ (PatternMatchFail err) = showString err
573
574 -----
575
576 data RecSelError = RecSelError String
577 INSTANCE_TYPEABLE0(RecSelError,recSelErrorTc,"RecSelError")
578
579 instance Exception RecSelError
580
581 instance Show RecSelError where
582     showsPrec _ (RecSelError err) = showString err
583
584 -----
585
586 data RecConError = RecConError String
587 INSTANCE_TYPEABLE0(RecConError,recConErrorTc,"RecConError")
588
589 instance Exception RecConError
590
591 instance Show RecConError where
592     showsPrec _ (RecConError err) = showString err
593
594 -----
595
596 data RecUpdError = RecUpdError String
597 INSTANCE_TYPEABLE0(RecUpdError,recUpdErrorTc,"RecUpdError")
598
599 instance Exception RecUpdError
600
601 instance Show RecUpdError where
602     showsPrec _ (RecUpdError err) = showString err
603
604 -----
605
606 data NoMethodError = NoMethodError String
607 INSTANCE_TYPEABLE0(NoMethodError,noMethodErrorTc,"NoMethodError")
608
609 instance Exception NoMethodError
610
611 instance Show NoMethodError where
612     showsPrec _ (NoMethodError err) = showString err
613
614 -----
615
616 data NonTermination = NonTermination
617 INSTANCE_TYPEABLE0(NonTermination,nonTerminationTc,"NonTermination")
618
619 instance Exception NonTermination
620
621 instance Show NonTermination where
622     showsPrec _ NonTermination = showString "<<loop>>"
623
624 -- GHC's RTS calls this
625 nonTermination :: SomeException
626 nonTermination = toException NonTermination
627
628 -----
629
630 data NestedAtomically = NestedAtomically
631 INSTANCE_TYPEABLE0(NestedAtomically,nestedAtomicallyTc,"NestedAtomically")
632
633 instance Exception NestedAtomically
634
635 instance Show NestedAtomically where
636     showsPrec _ NestedAtomically = showString "Control.Concurrent.STM.atomically was nested"
637
638 -- GHC's RTS calls this
639 nestedAtomically :: SomeException
640 nestedAtomically = toException NestedAtomically
641
642 -----
643
644 instance Exception Dynamic
645
646 #endif
647