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