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