[project @ 2002-10-30 18:21:25 by ross]
[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 #ifndef __HUGS__
29         throw,          -- :: Exception -> a
30 #endif
31         ioError,        -- :: Exception -> IO a
32 #ifndef __HUGS__
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 Prelude          hiding (catch)
115 import GHC.Base         ( assert )
116 import GHC.Exception    as ExceptionBase hiding (try, catch, bracket, bracket_)
117 import GHC.Conc         ( throwTo, ThreadId )
118 import GHC.IOBase       ( IO(..) )
119 #endif
120
121 #ifdef __HUGS__
122 import Prelude          hiding ( catch, ioError )
123 import Hugs.Exception   hiding ( evaluate )
124 import qualified Hugs.Exception as ExceptionBase
125 #endif
126
127 import System.IO.Error
128 import Data.Dynamic
129
130 #include "Dynamic.h"
131 INSTANCE_TYPEABLE0(Exception,exceptionTc,"Exception")
132 #ifdef __GLASGOW_HASKELL__
133 INSTANCE_TYPEABLE0(IOException,ioExceptionTc,"IOException")
134 INSTANCE_TYPEABLE0(ArithException,arithExceptionTc,"ArithException")
135 INSTANCE_TYPEABLE0(ArrayException,arrayExceptionTc,"ArrayException")
136 INSTANCE_TYPEABLE0(AsyncException,asyncExceptionTc,"AsyncException")
137 #endif
138
139 #ifdef __HUGS__
140 -- This is as close as Hugs gets to providing throw
141 throw :: Exception -> IO a
142 throw = throwIO
143 #endif
144
145 -----------------------------------------------------------------------------
146 -- Catching exceptions
147
148 -- |This is the simplest of the exception-catching functions.  It
149 -- takes a single argument, runs it, and if an exception is raised
150 -- the \"handler\" is executed, with the value of the exception passed as an
151 -- argument.  Otherwise, the result is returned as normal.  For example:
152 --
153 -- >   catch (openFile f ReadMode) 
154 -- >       (\e -> hPutStr stderr (\"Couldn\'t open \"++f++\": \" ++ show e))
155 --
156 -- For catching exceptions in pure (non-'IO') expressions, see the
157 -- function 'evaluate'.
158 --
159 -- Note that due to Haskell\'s unspecified evaluation order, an
160 -- expression may return one of several possible exceptions: consider
161 -- the expression @error \"urk\" + 1 \`div\` 0@.  Does
162 -- 'catch' execute the handler passing
163 -- @ErrorCall \"urk\"@, or @ArithError DivideByZero@?
164 --
165 -- The answer is \"either\": 'catch' makes a
166 -- non-deterministic choice about which exception to catch.  If you
167 -- call it again, you might get a different exception back.  This is
168 -- ok, because 'catch' is an 'IO' computation.
169 --
170 -- Note that 'catch' catches all types of exceptions, and is generally
171 -- used for \"cleaning up\" before passing on the exception using
172 -- 'ioError'.  It is not good practice to discard the exception and
173 -- continue, without first checking the type of the exception (it
174 -- might be a 'ThreadKilled', for example).  In this case it is usually better
175 -- to use 'catchJust' and select the kinds of exceptions to catch.
176 --
177 -- Also note that The "Prelude" also exports a
178 -- function called 'catch' which has the same type as
179 -- 'Exception.catch', the difference being that the
180 -- "Prelude" version only catches the IO and user
181 -- families of exceptions (as required by Haskell 98).  We recommend
182 -- either hiding the "Prelude" version of
183 -- 'catch' when importing
184 -- "Control.Exception", or importing
185 -- "Control.Exception" qualified, to avoid name-clashes.
186
187 catch   :: IO a                 -- ^ The computation to run
188         -> (Exception -> IO a)  -- ^ Handler to invoke if an exception is raised
189         -> IO a                 
190 catch =  ExceptionBase.catchException
191
192 -- | The function 'catchJust' is like 'catch', but it takes an extra
193 -- argument which is an /exception predicate/, a function which
194 -- selects which type of exceptions we\'re interested in.  There are
195 -- some predefined exception predicates for useful subsets of
196 -- exceptions: 'ioErrors', 'arithExceptions', and so on.  For example,
197 -- to catch just calls to the 'error' function, we could use
198 --
199 -- >   result \<- catchJust errorCalls thing_to_try handler
200 --
201 -- Any other exceptions which are not matched by the predicate
202 -- are re-raised, and may be caught by an enclosing
203 -- 'catch' or 'catchJust'.
204 catchJust
205         :: (Exception -> Maybe b) -- ^ Predicate to select exceptions
206         -> IO a                   -- ^ Computation to run
207         -> (b -> IO a)            -- ^ Handler
208         -> IO a
209 catchJust p a handler = catch a handler'
210   where handler' e = case p e of 
211                         Nothing -> throw e
212                         Just b  -> handler b
213
214 -- | A version of 'catch' with the arguments swapped around; useful in
215 -- situations where the code for the handler is shorter.  For example:
216 --
217 -- >   do handle (\e -> exitWith (ExitFailure 1)) $
218 -- >      ...
219 handle     :: (Exception -> IO a) -> IO a -> IO a
220 handle     =  flip catch
221
222 -- | A version of 'catchJust' with the arguments swapped around (see
223 -- 'handle').
224 handleJust :: (Exception -> Maybe b) -> (b -> IO a) -> IO a -> IO a
225 handleJust p =  flip (catchJust p)
226
227 -----------------------------------------------------------------------------
228 -- evaluate
229
230 -- | Forces its argument to be evaluated, and returns the result in
231 -- the 'IO' monad.  It can be used to order evaluation with respect to
232 -- other 'IO' operations; its semantics are given by
233 --
234 -- >   evaluate undefined `seq` return ()  ==> return ()
235 -- >   catch (evaluate undefined) (\e -> return ())  ==> return ()
236 --
237 -- NOTE: @(evaluate a)@ is /not/ the same as @(a \`seq\` return a)@.
238 evaluate :: a -> IO a
239 #if defined(__GLASGOW_HASKELL__)
240 evaluate a = IO $ \s -> case a `seq` () of () -> (# s, a #)
241         -- NB. can't write  
242         --      a `seq` (# s, a #)
243         -- because we can't have an unboxed tuple as a function argument
244 #elif defined(__HUGS__)
245 evaluate = ExceptionBase.evaluate
246 #endif
247
248 -----------------------------------------------------------------------------
249 -- 'try' and variations.
250
251 -- | Similar to 'catch', but returns an 'Either' result which is
252 -- @(Right a)@ if no exception was raised, or @(Left e)@ if an
253 -- exception was raised and its value is @e@.
254 --
255 -- >  try a = catch (Right \`liftM\` a) (return . Left)
256 --
257 -- Note: as with 'catch', it is only polite to use this variant if you intend
258 -- to re-throw the exception after performing whatever cleanup is needed.
259 -- Otherwise, 'tryJust' is generally considered to be better.
260 --
261 try :: IO a -> IO (Either Exception a)
262 try a = catch (a >>= \ v -> return (Right v)) (\e -> return (Left e))
263
264 -- | A variant of 'try' that takes an exception predicate to select
265 -- which exceptions are caught (c.f. 'catchJust').  If the exception
266 -- does not match the predicate, it is re-thrown.
267 tryJust :: (Exception -> Maybe b) -> IO a -> IO (Either b a)
268 tryJust p a = do
269   r <- try a
270   case r of
271         Right v -> return (Right v)
272         Left  e -> case p e of
273                         Nothing -> throw e
274                         Just b  -> return (Left b)
275
276 #ifdef __GLASGOW_HASKELL__
277 -----------------------------------------------------------------------------
278 -- Dynamic exceptions
279
280 -- $dynamic
281 --  #DynamicExceptions# Because the 'Exception' datatype is not extensible, there is an
282 -- interface for throwing and catching exceptions of type 'Dynamic'
283 -- (see "Data.Dynamic") which allows exception values of any type in
284 -- the 'Typeable' class to be thrown and caught.
285
286 -- | Raise any value as an exception, provided it is in the
287 -- 'Typeable' class.
288 throwDyn :: Typeable exception => exception -> b
289 throwDyn exception = throw (DynException (toDyn exception))
290
291 -- | A variant of 'throwDyn' that throws the dynamic exception to an
292 -- arbitrary thread (c.f. 'throwTo').
293 throwDynTo :: Typeable exception => ThreadId -> exception -> IO ()
294 throwDynTo t exception = throwTo t (DynException (toDyn exception))
295
296 -- | Catch dynamic exceptions of the required type.  All other
297 -- exceptions are re-thrown, including dynamic exceptions of the wrong
298 -- type.
299 --
300 -- When using dynamic exceptions it is advisable to define a new
301 -- datatype to use for your exception type, to avoid possible clashes
302 -- with dynamic exceptions used in other libraries.
303 --
304 catchDyn :: Typeable exception => IO a -> (exception -> IO a) -> IO a
305 catchDyn m k = catchException m handle
306   where handle ex = case ex of
307                            (DynException dyn) ->
308                                 case fromDynamic dyn of
309                                     Just exception  -> k exception
310                                     Nothing -> throw ex
311                            _ -> throw ex
312 #endif /* __GLASGOW_HASKELL__ */
313
314 -----------------------------------------------------------------------------
315 -- Exception Predicates
316
317 -- $preds
318 -- These pre-defined predicates may be used as the first argument to
319 -- 'catchJust', 'tryJust', or 'handleJust' to select certain common
320 -- classes of exceptions.
321
322 ioErrors                :: Exception -> Maybe IOError
323 #ifdef __GLASGOW_HASKELL__
324 arithExceptions         :: Exception -> Maybe ArithException
325 errorCalls              :: Exception -> Maybe String
326 dynExceptions           :: Exception -> Maybe Dynamic
327 assertions              :: Exception -> Maybe String
328 asyncExceptions         :: Exception -> Maybe AsyncException
329 #endif /* __GLASGOW_HASKELL__ */
330 userErrors              :: Exception -> Maybe String
331
332 #ifdef __HUGS__
333 ioErrors = justIoErrors
334 userErrors = justUserErrors
335 #endif
336
337 #ifdef __GLASGOW_HASKELL__
338 ioErrors e@(IOException _) = Just e
339 ioErrors _ = Nothing
340
341 arithExceptions (ArithException e) = Just e
342 arithExceptions _ = Nothing
343
344 errorCalls (ErrorCall e) = Just e
345 errorCalls _ = Nothing
346
347 assertions (AssertionFailed e) = Just e
348 assertions _ = Nothing
349
350 dynExceptions (DynException e) = Just e
351 dynExceptions _ = Nothing
352
353 asyncExceptions (AsyncException e) = Just e
354 asyncExceptions _ = Nothing
355
356 userErrors e@IOException{} | isUserError e = Just (ioeGetErrorString e)
357 userErrors _ = Nothing
358 #endif /* __GLASGOW_HASKELL__ */
359
360 -----------------------------------------------------------------------------
361 -- Some Useful Functions
362
363 -- | When you want to acquire a resource, do some work with it, and
364 -- then release the resource, it is a good idea to use 'bracket',
365 -- because 'bracket' will install the necessary exception handler to
366 -- release the resource in the event that an exception is raised
367 -- during the computation.  If an exception is raised, then 'bracket' will 
368 -- re-raise the exception (after performing the release).
369 --
370 -- A common example is opening a file:
371 --
372 -- > bracket
373 -- >   (openFile "filename" ReadMode)
374 -- >   (hClose)
375 -- >   (\handle -> do { ... })
376 --
377 -- The arguments to 'bracket' are in this order so that we can partially apply 
378 -- it, e.g.:
379 --
380 -- > withFile name = bracket (openFile name) hClose
381 --
382 bracket 
383         :: IO a         -- ^ computation to run first (\"acquire resource\")
384         -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
385         -> (a -> IO c)  -- ^ computation to run in-between
386         -> IO c         -- returns the value from the in-between computation
387 bracket before after thing =
388   block (do
389     a <- before 
390     r <- catch 
391            (unblock (thing a))
392            (\e -> do { after a; throw e })
393     after a
394     return r
395  )
396    
397
398 -- | A specialised variant of 'bracket' with just a computation to run
399 -- afterward.
400 -- 
401 finally :: IO a         -- ^ computation to run first
402         -> IO b         -- ^ computation to run afterward (even if an exception 
403                         -- was raised)
404         -> IO a         -- returns the value from the first computation
405 a `finally` sequel =
406   block (do
407     r <- catch 
408              (unblock a)
409              (\e -> do { sequel; throw e })
410     sequel
411     return r
412   )
413
414 -- | A variant of 'bracket' where the return value from the first computation
415 -- is not required.
416 bracket_ :: IO a -> IO b -> IO c -> IO c
417 bracket_ before after thing = bracket before (const after) (const thing)
418
419 -- -----------------------------------------------------------------------------
420 -- Asynchronous exceptions
421
422 {- $async
423
424  #AsynchronousExceptions# Asynchronous exceptions are so-called because they arise due to
425 external influences, and can be raised at any point during execution.
426 'StackOverflow' and 'HeapOverflow' are two examples of
427 system-generated asynchronous exceptions.
428
429 The primary source of asynchronous exceptions, however, is
430 'throwTo':
431
432 >  throwTo :: ThreadId -> Exception -> IO ()
433
434 'throwTo' (also 'throwDynTo' and 'Concurrent.killThread') allows one
435 running thread to raise an arbitrary exception in another thread.  The
436 exception is therefore asynchronous with respect to the target thread,
437 which could be doing anything at the time it receives the exception.
438 Great care should be taken with asynchronous exceptions; it is all too
439 easy to introduce race conditions by the over zealous use of
440 'throwTo'.
441 -}
442
443 {- $block_handler
444 There\'s an implied 'block' around every exception handler in a call
445 to one of the 'catch' family of functions.  This is because that is
446 what you want most of the time - it eliminates a common race condition
447 in starting an exception handler, because there may be no exception
448 handler on the stack to handle another exception if one arrives
449 immediately.  If asynchronous exceptions are blocked on entering the
450 handler, though, we have time to install a new exception handler
451 before being interrupted.  If this weren\'t the default, one would have
452 to write something like
453
454 >      block (
455 >           catch (unblock (...))
456 >                      (\e -> handler)
457 >      )
458
459 If you need to unblock asynchronous exceptions again in the exception
460 handler, just use 'unblock' as normal.
461
462 Note that 'try' and friends /do not/ have a similar default, because
463 there is no exception handler in this case.  If you want to use 'try'
464 in an asynchronous-exception-safe way, you will need to use
465 'block'.
466 -}
467
468 {- $interruptible
469
470 Some operations are /interruptible/, which means that they can receive
471 asynchronous exceptions even in the scope of a 'block'.  Any function
472 which may itself block is defined as interruptible; this includes
473 'takeMVar' (but not 'tryTakeMVar'), and most operations which perform
474 some I\/O with the outside world..  The reason for having
475 interruptible operations is so that we can write things like
476
477 >      block (
478 >         a <- takeMVar m
479 >         catch (unblock (...))
480 >               (\e -> ...)
481 >      )
482
483 if the 'takeMVar' was not interruptible, then this particular
484 combination could lead to deadlock, because the thread itself would be
485 blocked in a state where it can\'t receive any asynchronous exceptions.
486 With 'takeMVar' interruptible, however, we can be
487 safe in the knowledge that the thread can receive exceptions right up
488 until the point when the 'takeMVar' succeeds.
489 Similar arguments apply for other interruptible operations like
490 'IO.openFile'.
491 -}
492
493 -- -----------------------------------------------------------------------------
494 -- Assert
495
496 #ifdef __HADDOCK__
497 -- | If the first argument evaluates to 'True', then the result is the
498 -- second argument.  Otherwise an 'Assertion' exception is raised,
499 -- containing a 'String' with the source file and line number of the
500 -- call to assert.
501 --
502 -- Assertions can normally be turned on or off with a compiler flag
503 -- (for GHC, assertions are normally on unless the @-fignore-asserts@
504 -- option is give).  When assertions are turned off, the first
505 -- argument to 'assert' is ignored, and the second argument is
506 -- returned as the result.
507 assert :: Bool -> a -> a
508 #endif
509
510 #ifndef __GLASGOW_HASKELL__
511 assert :: Bool -> a -> a
512 assert True x = x
513 assert False _ = error "Assertion failure"
514 #endif