8086b22f7c2a185275fe9957634e02a177561e0c
[ghc-base.git] / Control / Exception.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  Control.Exception
4 -- Copyright   :  (c) The University of Glasgow 2001
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  non-portable
10 --
11 -- This module provides support for raising and catching both built-in
12 -- and user-defined exceptions.
13 --
14 -----------------------------------------------------------------------------
15
16 module Control.Exception (
17
18         -- * The Exception type
19         Exception(..),          -- instance Eq, Ord, Show, Typeable
20 #ifdef __GLASGOW_HASKELL__
21         IOException,            -- instance Eq, Ord, Show, Typeable
22         ArithException(..),     -- instance Eq, Ord, Show, Typeable
23         ArrayException(..),     -- instance Eq, Ord, Show, Typeable
24         AsyncException(..),     -- instance Eq, Ord, Show, Typeable
25 #endif
26
27         -- * Throwing exceptions
28 #ifdef __HUGS__
29         throwIO,        -- :: Exception -> IO a
30 #else
31         throw,          -- :: Exception -> a
32         ioError,        -- :: Exception -> IO a
33         throwTo,        -- :: ThreadId -> Exception -> a
34 #endif
35
36         -- * Catching Exceptions
37
38         -- |There are several functions for catching and examining
39         -- exceptions; all of them may only be used from within the
40         -- 'IO' monad.
41
42         -- ** The @catch@ functions
43         catch,     -- :: IO a -> (Exception -> IO a) -> IO a
44         catchJust, -- :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a
45
46         -- ** The @handle@ functions
47         handle,    -- :: (Exception -> IO a) -> IO a -> IO a
48         handleJust,-- :: (Exception -> Maybe b) -> (b -> IO a) -> IO a -> IO a
49
50         -- ** The @try@ functions
51         try,       -- :: IO a -> IO (Either Exception a)
52         tryJust,   -- :: (Exception -> Maybe b) -> a    -> IO (Either b a)
53
54         -- ** The @evaluate@ function
55         evaluate,  -- :: a -> IO a
56
57         -- ** Exception predicates
58         
59         -- $preds
60
61         ioErrors,               -- :: Exception -> Maybe IOError
62 #ifndef __HUGS__
63         arithExceptions,        -- :: Exception -> Maybe ArithException
64         errorCalls,             -- :: Exception -> Maybe String
65         dynExceptions,          -- :: Exception -> Maybe Dynamic
66         assertions,             -- :: Exception -> Maybe String
67         asyncExceptions,        -- :: Exception -> Maybe AsyncException
68 #endif /* __HUGS__ */
69         userErrors,             -- :: Exception -> Maybe String
70
71 #ifdef __GLASGOW_HASKELL__
72         -- * Dynamic exceptions
73
74         -- $dynamic
75         throwDyn,       -- :: Typeable ex => ex -> b
76         throwDynTo,     -- :: Typeable ex => ThreadId -> ex -> b
77         catchDyn,       -- :: Typeable ex => IO a -> (ex -> IO a) -> IO a
78 #endif
79         
80         -- * Asynchronous Exceptions
81
82         -- $async
83
84         -- ** Asynchronous exception control
85
86         -- |The following two functions allow a thread to control delivery of
87         -- asynchronous exceptions during a critical region.
88
89         block,          -- :: IO a -> IO a
90         unblock,        -- :: IO a -> IO a
91
92         -- *** Applying @block@ to an exception handler
93
94         -- $block_handler
95
96         -- *** Interruptible operations
97
98         -- $interruptible
99
100         -- * Assertions
101
102         assert,         -- :: Bool -> a -> a
103
104         -- * Utilities
105
106         bracket,        -- :: IO a -> (a -> IO b) -> (a -> IO c) -> IO ()
107         bracket_,       -- :: IO a -> IO b -> IO c -> IO ()
108
109         finally,        -- :: IO a -> IO b -> IO b
110
111   ) where
112
113 #ifdef __GLASGOW_HASKELL__
114 import GHC.Base         ( assert )
115 import GHC.Exception    as ExceptionBase hiding (try, catch, bracket, bracket_)
116 import GHC.Conc         ( throwTo, ThreadId )
117 import GHC.IOBase       ( IO(..) )
118 #endif
119
120 #ifdef __HUGS__
121 import Hugs.Exception   hiding ( evaluate )
122 import qualified Hugs.Exception as ExceptionBase
123 #endif
124
125 import Prelude          hiding ( catch )
126 import System.IO.Error
127 import Data.Dynamic
128
129 #include "Dynamic.h"
130 INSTANCE_TYPEABLE0(Exception,exceptionTc,"Exception")
131 #ifdef __GLASGOW_HASKELL__
132 INSTANCE_TYPEABLE0(IOException,ioExceptionTc,"IOException")
133 INSTANCE_TYPEABLE0(ArithException,arithExceptionTc,"ArithException")
134 INSTANCE_TYPEABLE0(ArrayException,arrayExceptionTc,"ArrayException")
135 INSTANCE_TYPEABLE0(AsyncException,asyncExceptionTc,"AsyncException")
136 #endif
137
138 #ifdef __HUGS__
139 -- This is as close as Hugs gets to providing throw
140 throw :: Exception -> IO a
141 throw = throwIO
142 #endif
143
144 -----------------------------------------------------------------------------
145 -- Catching exceptions
146
147 -- |This is the simplest of the exception-catching functions.  It
148 -- takes a single argument, runs it, and if an exception is raised
149 -- the \"handler\" is executed, with the value of the exception passed as an
150 -- argument.  Otherwise, the result is returned as normal.  For example:
151 --
152 -- >   catch (openFile f ReadMode) 
153 -- >       (\e -> hPutStr stderr (\"Couldn\'t open \"++f++\": \" ++ show e))
154 --
155 -- For catching exceptions in pure (non-'IO') expressions, see the
156 -- function 'evaluate'.
157 --
158 -- Note that due to Haskell\'s unspecified evaluation order, an
159 -- expression may return one of several possible exceptions: consider
160 -- the expression @error \"urk\" + 1 \`div\` 0@.  Does
161 -- 'catch' execute the handler passing
162 -- @ErrorCall \"urk\"@, or @ArithError DivideByZero@?
163 --
164 -- The answer is \"either\": 'catch' makes a
165 -- non-deterministic choice about which exception to catch.  If you
166 -- call it again, you might get a different exception back.  This is
167 -- ok, because 'catch' is an 'IO' computation.
168 --
169 -- Note that 'catch' catches all types of exceptions, and is generally
170 -- used for \"cleaning up\" before passing on the exception using
171 -- 'ioError'.  It is not good practice to discard the exception and
172 -- continue, without first checking the type of the exception (it
173 -- might be a 'ThreadKilled', for example).  In this case it is usually better
174 -- to use 'catchJust' and select the kinds of exceptions to catch.
175 --
176 -- Also note that The "Prelude" also exports a
177 -- function called 'catch' which has the same type as
178 -- 'Exception.catch', the difference being that the
179 -- "Prelude" version only catches the IO and user
180 -- families of exceptions (as required by Haskell 98).  We recommend
181 -- either hiding the "Prelude" version of
182 -- 'catch' when importing
183 -- "Control.Exception", or importing
184 -- "Control.Exception" qualified, to avoid name-clashes.
185
186 catch   :: IO a                 -- ^ The computation to run
187         -> (Exception -> IO a)  -- ^ Handler to invoke if an exception is raised
188         -> IO a                 
189 catch =  ExceptionBase.catchException
190
191 -- | The function 'catchJust' is like 'catch', but it takes an extra
192 -- argument which is an /exception predicate/, a function which
193 -- selects which type of exceptions we\'re interested in.  There are
194 -- some predefined exception predicates for useful subsets of
195 -- exceptions: 'ioErrors', 'arithExceptions', and so on.  For example,
196 -- to catch just calls to the 'error' function, we could use
197 --
198 -- >   result \<- catchJust errorCalls thing_to_try handler
199 --
200 -- Any other exceptions which are not matched by the predicate
201 -- are re-raised, and may be caught by an enclosing
202 -- 'catch' or 'catchJust'.
203 catchJust
204         :: (Exception -> Maybe b) -- ^ Predicate to select exceptions
205         -> IO a                   -- ^ Computation to run
206         -> (b -> IO a)            -- ^ Handler
207         -> IO a
208 catchJust p a handler = catch a handler'
209   where handler' e = case p e of 
210                         Nothing -> throw e
211                         Just b  -> handler b
212
213 -- | A version of 'catch' with the arguments swapped around; useful in
214 -- situations where the code for the handler is shorter.  For example:
215 --
216 -- >   do handle (\e -> exitWith (ExitFailure 1)) $
217 -- >      ...
218 handle     :: (Exception -> IO a) -> IO a -> IO a
219 handle     =  flip catch
220
221 -- | A version of 'catchJust' with the arguments swapped around (see
222 -- 'handle').
223 handleJust :: (Exception -> Maybe b) -> (b -> IO a) -> IO a -> IO a
224 handleJust p =  flip (catchJust p)
225
226 -----------------------------------------------------------------------------
227 -- evaluate
228
229 -- | Forces its argument to be evaluated, and returns the result in
230 -- the 'IO' monad.  It can be used to order evaluation with respect to
231 -- other 'IO' operations; its semantics are given by
232 --
233 -- >   evaluate undefined `seq` return ()  ==> return ()
234 -- >   catch (evaluate undefined) (\e -> return ())  ==> return ()
235 --
236 -- NOTE: @(evaluate a)@ is /not/ the same as @(a \`seq\` return a)@.
237 evaluate :: a -> IO a
238 #if defined(__GLASGOW_HASKELL__)
239 evaluate a = IO $ \s -> case a `seq` () of () -> (# s, a #)
240         -- NB. can't write  
241         --      a `seq` (# s, a #)
242         -- because we can't have an unboxed tuple as a function argument
243 #elif defined(__HUGS__)
244 evaluate = ExceptionBase.evaluate
245 #endif
246
247 -----------------------------------------------------------------------------
248 -- 'try' and variations.
249
250 -- | Similar to 'catch', but returns an 'Either' result which is
251 -- @(Right a)@ if no exception was raised, or @(Left e)@ if an
252 -- exception was raised and its value is @e@.
253 --
254 -- >  try a = catch (Right \`liftM\` a) (return . Left)
255 --
256 -- Note: as with 'catch', it is only polite to use this variant if you intend
257 -- to re-throw the exception after performing whatever cleanup is needed.
258 -- Otherwise, 'tryJust' is generally considered to be better.
259 --
260 try :: IO a -> IO (Either Exception a)
261 try a = catch (a >>= \ v -> return (Right v)) (\e -> return (Left e))
262
263 -- | A variant of 'try' that takes an exception predicate to select
264 -- which exceptions are caught (c.f. 'catchJust').  If the exception
265 -- does not match the predicate, it is re-thrown.
266 tryJust :: (Exception -> Maybe b) -> IO a -> IO (Either b a)
267 tryJust p a = do
268   r <- try a
269   case r of
270         Right v -> return (Right v)
271         Left  e -> case p e of
272                         Nothing -> throw e
273                         Just b  -> return (Left b)
274
275 #ifdef __GLASGOW_HASKELL__
276 -----------------------------------------------------------------------------
277 -- Dynamic exceptions
278
279 -- $dynamic
280 --  #DynamicExceptions# Because the 'Exception' datatype is not extensible, there is an
281 -- interface for throwing and catching exceptions of type 'Dynamic'
282 -- (see "Data.Dynamic") which allows exception values of any type in
283 -- the 'Typeable' class to be thrown and caught.
284
285 -- | Raise any value as an exception, provided it is in the
286 -- 'Typeable' class.
287 throwDyn :: Typeable exception => exception -> b
288 throwDyn exception = throw (DynException (toDyn exception))
289
290 -- | A variant of 'throwDyn' that throws the dynamic exception to an
291 -- arbitrary thread (c.f. 'throwTo').
292 throwDynTo :: Typeable exception => ThreadId -> exception -> IO ()
293 throwDynTo t exception = throwTo t (DynException (toDyn exception))
294
295 -- | Catch dynamic exceptions of the required type.  All other
296 -- exceptions are re-thrown, including dynamic exceptions of the wrong
297 -- type.
298 --
299 -- When using dynamic exceptions it is advisable to define a new
300 -- datatype to use for your exception type, to avoid possible clashes
301 -- with dynamic exceptions used in other libraries.
302 --
303 catchDyn :: Typeable exception => IO a -> (exception -> IO a) -> IO a
304 catchDyn m k = catchException m handle
305   where handle ex = case ex of
306                            (DynException dyn) ->
307                                 case fromDynamic dyn of
308                                     Just exception  -> k exception
309                                     Nothing -> throw ex
310                            _ -> throw ex
311 #endif /* __GLASGOW_HASKELL__ */
312
313 -----------------------------------------------------------------------------
314 -- Exception Predicates
315
316 -- $preds
317 -- These pre-defined predicates may be used as the first argument to
318 -- 'catchJust', 'tryJust', or 'handleJust' to select certain common
319 -- classes of exceptions.
320
321 #ifdef __GLASGOW_HASKELL__
322 ioErrors                :: Exception -> Maybe IOError
323 arithExceptions         :: Exception -> Maybe ArithException
324 errorCalls              :: Exception -> Maybe String
325 dynExceptions           :: Exception -> Maybe Dynamic
326 assertions              :: Exception -> Maybe String
327 asyncExceptions         :: Exception -> Maybe AsyncException
328 userErrors              :: Exception -> Maybe String
329 #endif /* __GLASGOW_HASKELL__ */
330
331 #ifdef __GLASGOW_HASKELL__
332 ioErrors e@(IOException _) = Just e
333 ioErrors _ = Nothing
334
335 arithExceptions (ArithException e) = Just e
336 arithExceptions _ = Nothing
337
338 errorCalls (ErrorCall e) = Just e
339 errorCalls _ = Nothing
340
341 assertions (AssertionFailed e) = Just e
342 assertions _ = Nothing
343
344 dynExceptions (DynException e) = Just e
345 dynExceptions _ = Nothing
346
347 asyncExceptions (AsyncException e) = Just e
348 asyncExceptions _ = Nothing
349
350 userErrors e@IOException{} | isUserError e = Just (ioeGetErrorString e)
351 userErrors _ = Nothing
352 #endif /* __GLASGOW_HASKELL__ */
353
354 -----------------------------------------------------------------------------
355 -- Some Useful Functions
356
357 -- | When you want to acquire a resource, do some work with it, and
358 -- then release the resource, it is a good idea to use 'bracket',
359 -- because 'bracket' will install the necessary exception handler to
360 -- release the resource in the event that an exception is raised
361 -- during the computation.  If an exception is raised, then 'bracket' will 
362 -- re-raise the exception (after performing the release).
363 --
364 -- A common example is opening a file:
365 --
366 -- > bracket
367 -- >   (openFile "filename" ReadMode)
368 -- >   (hClose)
369 -- >   (\handle -> do { ... })
370 --
371 -- The arguments to 'bracket' are in this order so that we can partially apply 
372 -- it, e.g.:
373 --
374 -- > withFile name = bracket (openFile name) hClose
375 --
376 bracket 
377         :: IO a         -- ^ computation to run first (\"acquire resource\")
378         -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
379         -> (a -> IO c)  -- ^ computation to run in-between
380         -> IO c         -- returns the value from the in-between computation
381 bracket before after thing =
382   block (do
383     a <- before 
384     r <- catch 
385            (unblock (thing a))
386            (\e -> do { after a; throw e })
387     after a
388     return r
389  )
390    
391
392 -- | A specialised variant of 'bracket' with just a computation to run
393 -- afterward.
394 -- 
395 finally :: IO a         -- ^ computation to run first
396         -> IO b         -- ^ computation to run afterward (even if an exception 
397                         -- was raised)
398         -> IO a         -- returns the value from the first computation
399 a `finally` sequel =
400   block (do
401     r <- catch 
402              (unblock a)
403              (\e -> do { sequel; throw e })
404     sequel
405     return r
406   )
407
408 -- | A variant of 'bracket' where the return value from the first computation
409 -- is not required.
410 bracket_ :: IO a -> IO b -> IO c -> IO c
411 bracket_ before after thing = bracket before (const after) (const thing)
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 '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 'takeMVar' (but not 'tryTakeMVar'), and most operations which perform
468 some I\/O with the outside world..  The reason for having
469 interruptible operations is so that we can write things like
470
471 >      block (
472 >         a <- takeMVar m
473 >         catch (unblock (...))
474 >               (\e -> ...)
475 >      )
476
477 if the 'takeMVar' was not interruptible, then this particular
478 combination could lead to deadlock, because the thread itself would be
479 blocked in a state where it can\'t receive any asynchronous exceptions.
480 With 'takeMVar' interruptible, however, we can be
481 safe in the knowledge that the thread can receive exceptions right up
482 until the point when the 'takeMVar' succeeds.
483 Similar arguments apply for other interruptible operations like
484 'IO.openFile'.
485 -}
486
487 -- -----------------------------------------------------------------------------
488 -- Assert
489
490 #ifdef __HADDOCK__
491 -- | If the first argument evaluates to 'True', then the result is the
492 -- second argument.  Otherwise an 'Assertion' exception is raised,
493 -- containing a 'String' with the source file and line number of the
494 -- call to assert.
495 --
496 -- Assertions can normally be turned on or off with a compiler flag
497 -- (for GHC, assertions are normally on unless the @-fignore-asserts@
498 -- option is give).  When assertions are turned off, the first
499 -- argument to 'assert' is ignored, and the second argument is
500 -- returned as the result.
501 assert :: Bool -> a -> a
502 #endif
503
504 #ifndef __GLASGOW_HASKELL__
505 assert :: Bool -> a -> a
506 assert True x = x
507 assert False _ = error "Assertion failure"
508 #endif