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