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