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