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