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