add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Control / Exception.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude, ExistentialQuantification #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Control.Exception
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 --
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  experimental
11 -- Portability :  non-portable (extended exceptions)
12 --
13 -- This module provides support for raising and catching both built-in
14 -- and user-defined exceptions.
15 --
16 -- In addition to exceptions thrown by 'IO' operations, exceptions may
17 -- be thrown by pure code (imprecise exceptions) or by external events
18 -- (asynchronous exceptions), but may only be caught in the 'IO' monad.
19 -- For more details, see:
20 --
21 --  * /A semantics for imprecise exceptions/, by Simon Peyton Jones,
22 --    Alastair Reid, Tony Hoare, Simon Marlow, Fergus Henderson,
23 --    in /PLDI'99/.
24 --
25 --  * /Asynchronous exceptions in Haskell/, by Simon Marlow, Simon Peyton
26 --    Jones, Andy Moran and John Reppy, in /PLDI'01/.
27 --
28 --  * /An Extensible Dynamically-Typed Hierarchy of Exceptions/,
29 --    by Simon Marlow, in /Haskell '06/.
30 --
31 -----------------------------------------------------------------------------
32
33 module Control.Exception (
34
35         -- * The Exception type
36 #ifdef __HUGS__
37         SomeException,
38 #else
39         SomeException(..),
40 #endif
41         Exception(..),          -- class
42         IOException,            -- instance Eq, Ord, Show, Typeable, Exception
43         ArithException(..),     -- instance Eq, Ord, Show, Typeable, Exception
44         ArrayException(..),     -- instance Eq, Ord, Show, Typeable, Exception
45         AssertionFailed(..),
46         AsyncException(..),     -- instance Eq, Ord, Show, Typeable, Exception
47
48 #if __GLASGOW_HASKELL__ || __HUGS__
49         NonTermination(..),
50         NestedAtomically(..),
51 #endif
52 #ifdef __NHC__
53         System.ExitCode(), -- instance Exception
54 #endif
55
56         BlockedIndefinitelyOnMVar(..),
57         BlockedIndefinitelyOnSTM(..),
58         Deadlock(..),
59         NoMethodError(..),
60         PatternMatchFail(..),
61         RecConError(..),
62         RecSelError(..),
63         RecUpdError(..),
64         ErrorCall(..),
65
66         -- * Throwing exceptions
67         throw,
68         throwIO,
69         ioError,
70 #ifdef __GLASGOW_HASKELL__
71         throwTo,
72 #endif
73
74         -- * Catching Exceptions
75
76         -- $catching
77
78         -- ** Catching all exceptions
79
80         -- $catchall
81
82         -- ** The @catch@ functions
83         catch,
84         catches, Handler(..),
85         catchJust,
86
87         -- ** The @handle@ functions
88         handle,
89         handleJust,
90
91         -- ** The @try@ functions
92         try,
93         tryJust,
94
95         -- ** The @evaluate@ function
96         evaluate,
97
98         -- ** The @mapException@ function
99         mapException,
100
101         -- * Asynchronous Exceptions
102
103         -- $async
104
105         -- ** Asynchronous exception control
106
107         -- |The following functions allow a thread to control delivery of
108         -- asynchronous exceptions during a critical region.
109
110         mask,
111 #ifndef __NHC__
112         mask_,
113         uninterruptibleMask,
114         uninterruptibleMask_,
115         MaskingState(..),
116         getMaskingState,
117         allowInterrupt,
118 #endif
119
120         -- ** (deprecated) Asynchronous exception control
121
122         block,
123         unblock,
124         blocked,
125
126         -- *** Applying @mask@ to an exception handler
127
128         -- $block_handler
129
130         -- *** Interruptible operations
131
132         -- $interruptible
133
134         -- * Assertions
135
136         assert,
137
138         -- * Utilities
139
140         bracket,
141         bracket_,
142         bracketOnError,
143
144         finally,
145         onException,
146
147   ) where
148
149 import Control.Exception.Base
150
151 #ifdef __GLASGOW_HASKELL__
152 import GHC.Base
153 import GHC.IO (unsafeUnmask)
154 import Data.Maybe
155 #else
156 import Prelude hiding (catch)
157 #endif
158
159 #ifdef __NHC__
160 import System (ExitCode())
161 #endif
162
163 -- | You need this when using 'catches'.
164 data Handler a = forall e . Exception e => Handler (e -> IO a)
165
166 {- |
167 Sometimes you want to catch two different sorts of exception. You could
168 do something like
169
170 > f = expr `catch` \ (ex :: ArithException) -> handleArith ex
171 >          `catch` \ (ex :: IOException)    -> handleIO    ex
172
173 However, there are a couple of problems with this approach. The first is
174 that having two exception handlers is inefficient. However, the more
175 serious issue is that the second exception handler will catch exceptions
176 in the first, e.g. in the example above, if @handleArith@ throws an
177 @IOException@ then the second exception handler will catch it.
178
179 Instead, we provide a function 'catches', which would be used thus:
180
181 > f = expr `catches` [Handler (\ (ex :: ArithException) -> handleArith ex),
182 >                     Handler (\ (ex :: IOException)    -> handleIO    ex)]
183 -}
184 catches :: IO a -> [Handler a] -> IO a
185 catches io handlers = io `catch` catchesHandler handlers
186
187 catchesHandler :: [Handler a] -> SomeException -> IO a
188 catchesHandler handlers e = foldr tryHandler (throw e) handlers
189     where tryHandler (Handler handler) res
190               = case fromException e of
191                 Just e' -> handler e'
192                 Nothing -> res
193
194 -- -----------------------------------------------------------------------------
195 -- Catching exceptions
196
197 {- $catching
198
199 There are several functions for catching and examining
200 exceptions; all of them may only be used from within the
201 'IO' monad.
202
203 Here's a rule of thumb for deciding which catch-style function to
204 use:
205
206  * If you want to do some cleanup in the event that an exception
207    is raised, use 'finally', 'bracket' or 'onException'.
208
209  * To recover after an exception and do something else, the best
210    choice is to use one of the 'try' family.
211
212  * ... unless you are recovering from an asynchronous exception, in which
213    case use 'catch' or 'catchJust'.
214
215 The difference between using 'try' and 'catch' for recovery is that in
216 'catch' the handler is inside an implicit 'block' (see \"Asynchronous
217 Exceptions\") which is important when catching asynchronous
218 exceptions, but when catching other kinds of exception it is
219 unnecessary.  Furthermore it is possible to accidentally stay inside
220 the implicit 'block' by tail-calling rather than returning from the
221 handler, which is why we recommend using 'try' rather than 'catch' for
222 ordinary exception recovery.
223
224 A typical use of 'tryJust' for recovery looks like this:
225
226 >  do r <- tryJust (guard . isDoesNotExistError) $ getEnv "HOME"
227 >     case r of
228 >       Left  e    -> ...
229 >       Right home -> ...
230
231 -}
232
233 -- -----------------------------------------------------------------------------
234 -- Asynchronous exceptions
235
236 -- | When invoked inside 'mask', this function allows a blocked
237 -- asynchronous exception to be raised, if one exists.  It is
238 -- equivalent to performing an interruptible operation (see
239 -- #interruptible#), but does not involve any actual blocking.
240 --
241 -- When called outside 'mask', or inside 'uninterruptibleMask', this
242 -- function has no effect.
243 allowInterrupt :: IO ()
244 allowInterrupt = unsafeUnmask $ return ()
245
246 {- $async
247
248  #AsynchronousExceptions# Asynchronous exceptions are so-called because they arise due to
249 external influences, and can be raised at any point during execution.
250 'StackOverflow' and 'HeapOverflow' are two examples of
251 system-generated asynchronous exceptions.
252
253 The primary source of asynchronous exceptions, however, is
254 'throwTo':
255
256 >  throwTo :: ThreadId -> Exception -> IO ()
257
258 'throwTo' (also 'Control.Concurrent.killThread') allows one
259 running thread to raise an arbitrary exception in another thread.  The
260 exception is therefore asynchronous with respect to the target thread,
261 which could be doing anything at the time it receives the exception.
262 Great care should be taken with asynchronous exceptions; it is all too
263 easy to introduce race conditions by the over zealous use of
264 'throwTo'.
265 -}
266
267 {- $block_handler
268 There\'s an implied 'mask' around every exception handler in a call
269 to one of the 'catch' family of functions.  This is because that is
270 what you want most of the time - it eliminates a common race condition
271 in starting an exception handler, because there may be no exception
272 handler on the stack to handle another exception if one arrives
273 immediately.  If asynchronous exceptions are masked on entering the
274 handler, though, we have time to install a new exception handler
275 before being interrupted.  If this weren\'t the default, one would have
276 to write something like
277
278 >      mask $ \restore ->
279 >           catch (restore (...))
280 >                 (\e -> handler)
281
282 If you need to unblock asynchronous exceptions again in the exception
283 handler, 'restore' can be used there too.
284
285 Note that 'try' and friends /do not/ have a similar default, because
286 there is no exception handler in this case.  Don't use 'try' for
287 recovering from an asynchronous exception.
288 -}
289
290 {- $interruptible
291
292  #interruptible#
293 Some operations are /interruptible/, which means that they can receive
294 asynchronous exceptions even in the scope of a 'mask'.  Any function
295 which may itself block is defined as interruptible; this includes
296 'Control.Concurrent.MVar.takeMVar'
297 (but not 'Control.Concurrent.MVar.tryTakeMVar'),
298 and most operations which perform
299 some I\/O with the outside world.  The reason for having
300 interruptible operations is so that we can write things like
301
302 >      mask $ \restore -> do
303 >         a <- takeMVar m
304 >         catch (restore (...))
305 >               (\e -> ...)
306
307 if the 'Control.Concurrent.MVar.takeMVar' was not interruptible,
308 then this particular
309 combination could lead to deadlock, because the thread itself would be
310 blocked in a state where it can\'t receive any asynchronous exceptions.
311 With 'Control.Concurrent.MVar.takeMVar' interruptible, however, we can be
312 safe in the knowledge that the thread can receive exceptions right up
313 until the point when the 'Control.Concurrent.MVar.takeMVar' succeeds.
314 Similar arguments apply for other interruptible operations like
315 'System.IO.openFile'.
316
317 It is useful to think of 'mask' not as a way to completely prevent
318 asynchronous exceptions, but as a way to switch from asynchronous mode
319 to polling mode.  The main difficulty with asynchronous
320 exceptions is that they normally can occur anywhere, but within a
321 'mask' an asynchronous exception is only raised by operations that are
322 interruptible (or call other interruptible operations).  In many cases
323 these operations may themselves raise exceptions, such as I\/O errors,
324 so the caller will usually be prepared to handle exceptions arising from the
325 operation anyway.  To perfom an explicit poll for asynchronous exceptions
326 inside 'mask', use 'allowInterrupt'.
327
328 Sometimes it is too onerous to handle exceptions in the middle of a
329 critical piece of stateful code.  There are three ways to handle this
330 kind of situation:
331
332  * Use STM.  Since a transaction is always either completely executed
333    or not at all, transactions are a good way to maintain invariants
334    over state in the presence of asynchronous (and indeed synchronous)
335    exceptions.
336
337  * Use 'mask', and avoid interruptible operations.  In order to do
338    this, we have to know which operations are interruptible.  It is
339    impossible to know for any given library function whether it might
340    invoke an interruptible operation internally; so instead we give a
341    list of guaranteed-not-to-be-interruptible operations below.
342
343  * Use 'uninterruptibleMask'.  This is generally not recommended,
344    unless you can guarantee that any interruptible operations invoked
345    during the scope of 'uninterruptibleMask' can only ever block for
346    a short time.  Otherwise, 'uninterruptibleMask' is a good way to
347    make your program deadlock and be unresponsive to user interrupts.
348
349 The following operations are guaranteed not to be interruptible:
350
351  * operations on 'IORef' from "Data.IORef"
352  * STM transactions that do not use 'retry'
353  * everything from the @Foreign@ modules
354  * everything from @Control.Exception@
355  * @tryTakeMVar@, @tryPutMVar@, @isEmptyMVar@
356  * @takeMVar@ if the @MVar@ is definitely full, and conversely @putMVar@ if the @MVar@ is definitely empty
357  * @newEmptyMVar@, @newMVar@
358  * @forkIO@, @forkIOUnmasked@, @myThreadId@
359
360 -}
361
362 {- $catchall
363
364 It is possible to catch all exceptions, by using the type 'SomeException':
365
366 > catch f (\e -> ... (e :: SomeException) ...)
367
368 HOWEVER, this is normally not what you want to do!
369
370 For example, suppose you want to read a file, but if it doesn't exist
371 then continue as if it contained \"\".  You might be tempted to just
372 catch all exceptions and return \"\" in the handler. However, this has
373 all sorts of undesirable consequences.  For example, if the user
374 presses control-C at just the right moment then the 'UserInterrupt'
375 exception will be caught, and the program will continue running under
376 the belief that the file contains \"\".  Similarly, if another thread
377 tries to kill the thread reading the file then the 'ThreadKilled'
378 exception will be ignored.
379
380 Instead, you should only catch exactly the exceptions that you really
381 want. In this case, this would likely be more specific than even
382 \"any IO exception\"; a permissions error would likely also want to be
383 handled differently. Instead, you would probably want something like:
384
385 > e <- tryJust (guard . isDoesNotExistError) (readFile f)
386 > let str = either (const "") id e
387
388 There are occassions when you really do need to catch any sort of
389 exception. However, in most cases this is just so you can do some
390 cleaning up; you aren't actually interested in the exception itself.
391 For example, if you open a file then you want to close it again,
392 whether processing the file executes normally or throws an exception.
393 However, in these cases you can use functions like 'bracket', 'finally'
394 and 'onException', which never actually pass you the exception, but
395 just call the cleanup functions at the appropriate points.
396
397 But sometimes you really do need to catch any exception, and actually
398 see what the exception is. One example is at the very top-level of a
399 program, you may wish to catch any exception, print it to a logfile or
400 the screen, and then exit gracefully. For these cases, you can use
401 'catch' (or one of the other exception-catching functions) with the
402 'SomeException' type.
403 -}
404