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