578c2ee8bad85e464146d9c7d931b6f5d811d87b
[ghc-base.git] / Control / Exception.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
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 #endif
118
119         -- ** (deprecated) Asynchronous exception control
120
121         block,
122         unblock,
123         blocked,
124
125         -- *** Applying @mask@ to an exception handler
126
127         -- $block_handler
128
129         -- *** Interruptible operations
130
131         -- $interruptible
132
133         -- * Assertions
134
135         assert,
136
137         -- * Utilities
138
139         bracket,
140         bracket_,
141         bracketOnError,
142
143         finally,
144         onException,
145
146   ) where
147
148 import Control.Exception.Base
149
150 #ifdef __GLASGOW_HASKELL__
151 import GHC.Base
152 import Data.Maybe
153 #else
154 import Prelude hiding (catch)
155 #endif
156
157 #ifdef __NHC__
158 import System (ExitCode())
159 #endif
160
161 -- | You need this when using 'catches'.
162 data Handler a = forall e . Exception e => Handler (e -> IO a)
163
164 {- |
165 Sometimes you want to catch two different sorts of exception. You could
166 do something like
167
168 > f = expr `catch` \ (ex :: ArithException) -> handleArith ex
169 >          `catch` \ (ex :: IOException)    -> handleIO    ex
170
171 However, there are a couple of problems with this approach. The first is
172 that having two exception handlers is inefficient. However, the more
173 serious issue is that the second exception handler will catch exceptions
174 in the first, e.g. in the example above, if @handleArith@ throws an
175 @IOException@ then the second exception handler will catch it.
176
177 Instead, we provide a function 'catches', which would be used thus:
178
179 > f = expr `catches` [Handler (\ (ex :: ArithException) -> handleArith ex),
180 >                     Handler (\ (ex :: IOException)    -> handleIO    ex)]
181 -}
182 catches :: IO a -> [Handler a] -> IO a
183 catches io handlers = io `catch` catchesHandler handlers
184
185 catchesHandler :: [Handler a] -> SomeException -> IO a
186 catchesHandler handlers e = foldr tryHandler (throw e) handlers
187     where tryHandler (Handler handler) res
188               = case fromException e of
189                 Just e' -> handler e'
190                 Nothing -> res
191
192 -- -----------------------------------------------------------------------------
193 -- Catching exceptions
194
195 {- $catching
196
197 There are several functions for catching and examining
198 exceptions; all of them may only be used from within the
199 'IO' monad.
200
201 Here's a rule of thumb for deciding which catch-style function to
202 use:
203
204  * If you want to do some cleanup in the event that an exception
205    is raised, use 'finally', 'bracket' or 'onException'.
206
207  * To recover after an exception and do something else, the best
208    choice is to use one of the 'try' family.
209
210  * ... unless you are recovering from an asynchronous exception, in which
211    case use 'catch' or 'catchJust'.
212
213 The difference between using 'try' and 'catch' for recovery is that in
214 'catch' the handler is inside an implicit 'block' (see \"Asynchronous
215 Exceptions\") which is important when catching asynchronous
216 exceptions, but when catching other kinds of exception it is
217 unnecessary.  Furthermore it is possible to accidentally stay inside
218 the implicit 'block' by tail-calling rather than returning from the
219 handler, which is why we recommend using 'try' rather than 'catch' for
220 ordinary exception recovery.
221
222 A typical use of 'tryJust' for recovery looks like this:
223
224 >  do r <- tryJust (guard . isDoesNotExistError) $ getEnv "HOME"
225 >     case r of
226 >       Left  e    -> ...
227 >       Right home -> ...
228
229 -}
230
231 -- -----------------------------------------------------------------------------
232 -- Asynchronous exceptions
233
234 {- $async
235
236  #AsynchronousExceptions# Asynchronous exceptions are so-called because they arise due to
237 external influences, and can be raised at any point during execution.
238 'StackOverflow' and 'HeapOverflow' are two examples of
239 system-generated asynchronous exceptions.
240
241 The primary source of asynchronous exceptions, however, is
242 'throwTo':
243
244 >  throwTo :: ThreadId -> Exception -> IO ()
245
246 'throwTo' (also 'Control.Concurrent.killThread') allows one
247 running thread to raise an arbitrary exception in another thread.  The
248 exception is therefore asynchronous with respect to the target thread,
249 which could be doing anything at the time it receives the exception.
250 Great care should be taken with asynchronous exceptions; it is all too
251 easy to introduce race conditions by the over zealous use of
252 'throwTo'.
253 -}
254
255 {- $block_handler
256 There\'s an implied 'mask' around every exception handler in a call
257 to one of the 'catch' family of functions.  This is because that is
258 what you want most of the time - it eliminates a common race condition
259 in starting an exception handler, because there may be no exception
260 handler on the stack to handle another exception if one arrives
261 immediately.  If asynchronous exceptions are masked on entering the
262 handler, though, we have time to install a new exception handler
263 before being interrupted.  If this weren\'t the default, one would have
264 to write something like
265
266 >      mask $ \restore ->
267 >           catch (restore (...))
268 >                 (\e -> handler)
269
270 If you need to unblock asynchronous exceptions again in the exception
271 handler, 'restore' can be used there too.
272
273 Note that 'try' and friends /do not/ have a similar default, because
274 there is no exception handler in this case.  Don't use 'try' for
275 recovering from an asynchronous exception.
276 -}
277
278 {- $interruptible
279
280  #interruptible#
281 Some operations are /interruptible/, which means that they can receive
282 asynchronous exceptions even in the scope of a 'mask'.  Any function
283 which may itself block is defined as interruptible; this includes
284 'Control.Concurrent.MVar.takeMVar'
285 (but not 'Control.Concurrent.MVar.tryTakeMVar'),
286 and most operations which perform
287 some I\/O with the outside world.  The reason for having
288 interruptible operations is so that we can write things like
289
290 >      mask $ \restore -> do
291 >         a <- takeMVar m
292 >         catch (restore (...))
293 >               (\e -> ...)
294
295 if the 'Control.Concurrent.MVar.takeMVar' was not interruptible,
296 then this particular
297 combination could lead to deadlock, because the thread itself would be
298 blocked in a state where it can\'t receive any asynchronous exceptions.
299 With 'Control.Concurrent.MVar.takeMVar' interruptible, however, we can be
300 safe in the knowledge that the thread can receive exceptions right up
301 until the point when the 'Control.Concurrent.MVar.takeMVar' succeeds.
302 Similar arguments apply for other interruptible operations like
303 'System.IO.openFile'.
304
305 It is useful to think of 'mask' not as a way to completely prevent
306 asynchronous exceptions, but as a filter that allows them to be raised
307 only at certain places.  The main difficulty with asynchronous
308 exceptions is that they normally can occur anywhere, but within a
309 'mask' an asynchronous exception is only raised by operations that are
310 interruptible (or call other interruptible operations).  In many cases
311 these operations may themselves raise exceptions, such as I\/O errors,
312 so the caller should be prepared to handle exceptions arising from the
313 operation anyway.
314
315 Sometimes it is too onerous to handle exceptions in the middle of a
316 critical piece of stateful code.  There are three ways to handle this
317 kind of situation:
318
319  * Use STM.  Since a transaction is always either completely executed
320    or not at all, transactions are a good way to maintain invariants
321    over state in the presence of asynchronous (and indeed synchronous)
322    exceptions.
323
324  * Use 'mask', and avoid interruptible operations.  In order to do
325    this, we have to know which operations are interruptible.  It is
326    impossible to know for any given library function whether it might
327    invoke an interruptible operation internally; so instead we give a
328    list of guaranteed-not-to-be-interruptible operations below.
329
330  * Use 'uninterruptibleMask'.  This is generally not recommended,
331    unless you can guarantee that any interruptible operations invoked
332    during the scope of 'uninterruptibleMask' can only ever block for
333    a short time.  Otherwise, 'uninterruptibleMask' is a good way to
334    make your program deadlock and be unresponsive to user interrupts.
335
336 The following operations are guaranteed not to be interruptible:
337
338  * operations on 'IORef' from "Data.IORef"
339  * STM transactions that do not use 'retry'
340  * everything from the @Foreign@ modules
341  * everything from @Control.Exception@
342  * @tryTakeMVar@, @tryPutMVar@, @isEmptyMVar@
343  * @takeMVar@ if the @MVar@ is definitely full, and conversely @putMVar@ if the @MVar@ is definitely empty
344  * @newEmptyMVar@, @newMVar@
345  * @forkIO@, @forkIOUnmasked@, @myThreadId@
346
347 -}
348
349 {- $catchall
350
351 It is possible to catch all exceptions, by using the type 'SomeException':
352
353 > catch f (\e -> ... (e :: SomeException) ...)
354
355 HOWEVER, this is normally not what you want to do!
356
357 For example, suppose you want to read a file, but if it doesn't exist
358 then continue as if it contained \"\".  You might be tempted to just
359 catch all exceptions and return \"\" in the handler. However, this has
360 all sorts of undesirable consequences.  For example, if the user
361 presses control-C at just the right moment then the 'UserInterrupt'
362 exception will be caught, and the program will continue running under
363 the belief that the file contains \"\".  Similarly, if another thread
364 tries to kill the thread reading the file then the 'ThreadKilled'
365 exception will be ignored.
366
367 Instead, you should only catch exactly the exceptions that you really
368 want. In this case, this would likely be more specific than even
369 \"any IO exception\"; a permissions error would likely also want to be
370 handled differently. Instead, you would probably want something like:
371
372 > e <- tryJust (guard . isDoesNotExistError) (readFile f)
373 > let str = either (const "") id e
374
375 There are occassions when you really do need to catch any sort of
376 exception. However, in most cases this is just so you can do some
377 cleaning up; you aren't actually interested in the exception itself.
378 For example, if you open a file then you want to close it again,
379 whether processing the file executes normally or throws an exception.
380 However, in these cases you can use functions like 'bracket', 'finally'
381 and 'onException', which never actually pass you the exception, but
382 just call the cleanup functions at the appropriate points.
383
384 But sometimes you really do need to catch any exception, and actually
385 see what the exception is. One example is at the very top-level of a
386 program, you may wish to catch any exception, print it to a logfile or
387 the screen, and then exit gracefully. For these cases, you can use
388 'catch' (or one of the other exception-catching functions) with the
389 'SomeException' type.
390 -}
391