Remove unused imports in Control.Exception
[ghc-base.git] / Control / Exception.hs
1 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
2
3 #include "Typeable.h"
4
5 -----------------------------------------------------------------------------
6 -- |
7 -- Module      :  Control.Exception
8 -- Copyright   :  (c) The University of Glasgow 2001
9 -- License     :  BSD-style (see the file libraries/base/LICENSE)
10 -- 
11 -- Maintainer  :  libraries@haskell.org
12 -- Stability   :  experimental
13 -- Portability :  non-portable (extended exceptions)
14 --
15 -- This module provides support for raising and catching both built-in
16 -- and user-defined exceptions.
17 --
18 -- In addition to exceptions thrown by 'IO' operations, exceptions may
19 -- be thrown by pure code (imprecise exceptions) or by external events
20 -- (asynchronous exceptions), but may only be caught in the 'IO' monad.
21 -- For more details, see:
22 --
23 --  * /A semantics for imprecise exceptions/, by Simon Peyton Jones,
24 --    Alastair Reid, Tony Hoare, Simon Marlow, Fergus Henderson,
25 --    in /PLDI'99/.
26 --
27 --  * /Asynchronous exceptions in Haskell/, by Simon Marlow, Simon Peyton
28 --    Jones, Andy Moran and John Reppy, in /PLDI'01/.
29 --
30 -----------------------------------------------------------------------------
31
32 module Control.Exception (
33
34         -- * The Exception type
35         SomeException(..),
36         Exception(..),          -- instance Eq, Ord, Show, Typeable
37         IOException,            -- instance Eq, Ord, Show, Typeable
38         ArithException(..),     -- instance Eq, Ord, Show, Typeable
39         ArrayException(..),     -- instance Eq, Ord, Show, Typeable
40         AssertionFailed(..),
41         AsyncException(..),     -- instance Eq, Ord, Show, Typeable
42         NonTermination(..), nonTermination,
43         BlockedOnDeadMVar(..),
44         BlockedIndefinitely(..),
45         NestedAtomically(..), nestedAtomically,
46         Deadlock(..),
47         NoMethodError(..),
48         PatternMatchFail(..),
49         RecConError(..),
50         RecSelError(..),
51         RecUpdError(..),
52         ErrorCall(..),
53
54         -- * Throwing exceptions
55         throwIO,        -- :: Exception -> IO a
56         throw,          -- :: Exception -> a
57         ioError,        -- :: IOError -> IO a
58 #ifdef __GLASGOW_HASKELL__
59         throwTo,        -- :: ThreadId -> Exception -> a
60 #endif
61
62         -- * Catching Exceptions
63
64         -- |There are several functions for catching and examining
65         -- exceptions; all of them may only be used from within the
66         -- 'IO' monad.
67
68         -- ** The @catch@ functions
69         catch,     -- :: IO a -> (Exception -> IO a) -> IO a
70         catches, Handler(..),
71         catchAny,
72         catchJust, -- :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a
73
74         -- ** The @handle@ functions
75         handle,    -- :: (Exception -> IO a) -> IO a -> IO a
76         handleAny,
77         handleJust,-- :: (Exception -> Maybe b) -> (b -> IO a) -> IO a -> IO a
78
79         -- ** The @try@ functions
80         try,       -- :: IO a -> IO (Either Exception a)
81         tryJust,   -- :: (Exception -> Maybe b) -> a    -> IO (Either b a)
82         ignoreExceptions,
83         onException,
84
85         -- ** The @evaluate@ function
86         evaluate,  -- :: a -> IO a
87
88         -- ** The @mapException@ function
89         mapException,           -- :: (Exception -> Exception) -> a -> a
90
91         -- * Asynchronous Exceptions
92
93         -- $async
94
95         -- ** Asynchronous exception control
96
97         -- |The following two functions allow a thread to control delivery of
98         -- asynchronous exceptions during a critical region.
99
100         block,          -- :: IO a -> IO a
101         unblock,        -- :: IO a -> IO a
102         blocked,        -- :: IO Bool
103
104         -- *** Applying @block@ to an exception handler
105
106         -- $block_handler
107
108         -- *** Interruptible operations
109
110         -- $interruptible
111
112         -- * Assertions
113
114         assert,         -- :: Bool -> a -> a
115
116         -- * Utilities
117
118         bracket,        -- :: IO a -> (a -> IO b) -> (a -> IO c) -> IO ()
119         bracket_,       -- :: IO a -> IO b -> IO c -> IO ()
120         bracketOnError,
121
122         finally,        -- :: IO a -> IO b -> IO a
123
124         recSelError, recConError, irrefutPatError, runtimeError,
125         nonExhaustiveGuardsError, patError, noMethodBindingError,
126         assertError,
127   ) where
128
129 #ifdef __GLASGOW_HASKELL__
130 import GHC.Base
131 import GHC.IOBase
132 import GHC.List
133 import GHC.Show
134 import GHC.IOBase as ExceptionBase
135 import GHC.Exception hiding ( Exception )
136 import GHC.Conc         ( ThreadId(ThreadId) )
137 #endif
138
139 #ifdef __HUGS__
140 import Hugs.Exception   as ExceptionBase
141 #endif
142
143 import Data.Dynamic
144 import Data.Either
145 import Data.Maybe
146
147 #ifdef __NHC__
148 import qualified System.IO.Error as H'98 (catch)
149 import System.IO.Error (ioError)
150 import IO              (bracket)
151 import DIOError         -- defn of IOError type
152 import System          (ExitCode())
153
154 -- minimum needed for nhc98 to pretend it has Exceptions
155 data Exception   = IOException    IOException
156                  | ArithException ArithException
157                  | ArrayException ArrayException
158                  | AsyncException AsyncException
159                  | ExitException  ExitCode
160                  deriving Show
161 type IOException = IOError
162 data ArithException
163 data ArrayException
164 data AsyncException
165 instance Show ArithException
166 instance Show ArrayException
167 instance Show AsyncException
168
169 catch    :: IO a -> (Exception -> IO a) -> IO a
170 a `catch` b = a `H'98.catch` (b . IOException)
171
172 throwIO  :: Exception -> IO a
173 throwIO (IOException e) = ioError e
174 throwIO _               = ioError (UserError "Control.Exception.throwIO"
175                                              "unknown exception")
176 throw    :: Exception -> a
177 throw     = unsafePerformIO . throwIO
178
179 evaluate :: a -> IO a
180 evaluate x = x `seq` return x
181
182 assert :: Bool -> a -> a
183 assert True  x = x
184 assert False _ = throw (IOException (UserError "" "Assertion failed"))
185 #endif
186
187 #ifndef __GLASGOW_HASKELL__
188 -- Dummy definitions for implementations lacking asynchonous exceptions
189
190 block   :: IO a -> IO a
191 block    = id
192 unblock :: IO a -> IO a
193 unblock  = id
194 blocked :: IO Bool
195 blocked  = return False
196 #endif
197
198 -----------------------------------------------------------------------------
199 -- Catching exceptions
200
201 -- |This is the simplest of the exception-catching functions.  It
202 -- takes a single argument, runs it, and if an exception is raised
203 -- the \"handler\" is executed, with the value of the exception passed as an
204 -- argument.  Otherwise, the result is returned as normal.  For example:
205 --
206 -- >   catch (openFile f ReadMode) 
207 -- >       (\e -> hPutStr stderr ("Couldn't open "++f++": " ++ show e))
208 --
209 -- For catching exceptions in pure (non-'IO') expressions, see the
210 -- function 'evaluate'.
211 --
212 -- Note that due to Haskell\'s unspecified evaluation order, an
213 -- expression may return one of several possible exceptions: consider
214 -- the expression @error \"urk\" + 1 \`div\` 0@.  Does
215 -- 'catch' execute the handler passing
216 -- @ErrorCall \"urk\"@, or @ArithError DivideByZero@?
217 --
218 -- The answer is \"either\": 'catch' makes a
219 -- non-deterministic choice about which exception to catch.  If you
220 -- call it again, you might get a different exception back.  This is
221 -- ok, because 'catch' is an 'IO' computation.
222 --
223 -- Note that 'catch' catches all types of exceptions, and is generally
224 -- used for \"cleaning up\" before passing on the exception using
225 -- 'throwIO'.  It is not good practice to discard the exception and
226 -- continue, without first checking the type of the exception (it
227 -- might be a 'ThreadKilled', for example).  In this case it is usually better
228 -- to use 'catchJust' and select the kinds of exceptions to catch.
229 --
230 -- Also note that the "Prelude" also exports a function called
231 -- 'Prelude.catch' with a similar type to 'Control.Exception.catch',
232 -- except that the "Prelude" version only catches the IO and user
233 -- families of exceptions (as required by Haskell 98).  
234 --
235 -- We recommend either hiding the "Prelude" version of 'Prelude.catch'
236 -- when importing "Control.Exception": 
237 --
238 -- > import Prelude hiding (catch)
239 --
240 -- or importing "Control.Exception" qualified, to avoid name-clashes:
241 --
242 -- > import qualified Control.Exception as C
243 --
244 -- and then using @C.catch@
245 --
246 #ifndef __NHC__
247 catch   :: Exception e
248         => IO a         -- ^ The computation to run
249         -> (e -> IO a)  -- ^ Handler to invoke if an exception is raised
250         -> IO a
251 catch = ExceptionBase.catchException
252
253 catches :: IO a -> [Handler a] -> IO a
254 catches io handlers = io `catch` catchesHandler handlers
255
256 catchesHandler :: [Handler a] -> SomeException -> IO a
257 catchesHandler handlers e = foldr tryHandler (throw e) handlers
258     where tryHandler (Handler handler) res
259               = case fromException e of
260                 Just e' -> handler e'
261                 Nothing -> res
262
263 data Handler a = forall e . Exception e => Handler (e -> IO a)
264 #endif
265 -- | The function 'catchJust' is like 'catch', but it takes an extra
266 -- argument which is an /exception predicate/, a function which
267 -- selects which type of exceptions we\'re interested in.
268 --
269 -- >   result <- catchJust errorCalls thing_to_try handler
270 --
271 -- Any other exceptions which are not matched by the predicate
272 -- are re-raised, and may be caught by an enclosing
273 -- 'catch' or 'catchJust'.
274 catchJust
275         :: Exception e
276         => (e -> Maybe b)         -- ^ Predicate to select exceptions
277         -> IO a                   -- ^ Computation to run
278         -> (b -> IO a)            -- ^ Handler
279         -> IO a
280 catchJust p a handler = catch a handler'
281   where handler' e = case p e of 
282                         Nothing -> throw e
283                         Just b  -> handler b
284
285 -- | A version of 'catch' with the arguments swapped around; useful in
286 -- situations where the code for the handler is shorter.  For example:
287 --
288 -- >   do handle (\e -> exitWith (ExitFailure 1)) $
289 -- >      ...
290 handle     :: Exception e => (e -> IO a) -> IO a -> IO a
291 handle     =  flip catch
292
293 handleAny  :: (forall e . Exception e => e -> IO a) -> IO a -> IO a
294 handleAny  =  flip catchAny
295
296 -- | A version of 'catchJust' with the arguments swapped around (see
297 -- 'handle').
298 handleJust :: Exception e => (e -> Maybe b) -> (b -> IO a) -> IO a -> IO a
299 handleJust p =  flip (catchJust p)
300
301 -----------------------------------------------------------------------------
302 -- 'mapException'
303
304 -- | This function maps one exception into another as proposed in the
305 -- paper \"A semantics for imprecise exceptions\".
306
307 -- Notice that the usage of 'unsafePerformIO' is safe here.
308
309 mapException :: Exception e => (e -> e) -> a -> a
310 mapException f v = unsafePerformIO (catch (evaluate v)
311                                           (\x -> throw (f x)))
312
313 -----------------------------------------------------------------------------
314 -- 'try' and variations.
315
316 -- | Similar to 'catch', but returns an 'Either' result which is
317 -- @('Right' a)@ if no exception was raised, or @('Left' e)@ if an
318 -- exception was raised and its value is @e@.
319 --
320 -- >  try a = catch (Right `liftM` a) (return . Left)
321 --
322 -- Note: as with 'catch', it is only polite to use this variant if you intend
323 -- to re-throw the exception after performing whatever cleanup is needed.
324 -- Otherwise, 'tryJust' is generally considered to be better.
325 --
326 -- Also note that "System.IO.Error" also exports a function called
327 -- 'System.IO.Error.try' with a similar type to 'Control.Exception.try',
328 -- except that it catches only the IO and user families of exceptions
329 -- (as required by the Haskell 98 @IO@ module).
330
331 try :: Exception e => IO a -> IO (Either e a)
332 try a = catch (a >>= \ v -> return (Right v)) (\e -> return (Left e))
333
334 -- | A variant of 'try' that takes an exception predicate to select
335 -- which exceptions are caught (c.f. 'catchJust').  If the exception
336 -- does not match the predicate, it is re-thrown.
337 tryJust :: Exception e => (e -> Maybe b) -> IO a -> IO (Either b a)
338 tryJust p a = do
339   r <- try a
340   case r of
341         Right v -> return (Right v)
342         Left  e -> case p e of
343                         Nothing -> throw e
344                         Just b  -> return (Left b)
345
346 ignoreExceptions :: IO () -> IO ()
347 ignoreExceptions io = io `catchAny` \_ -> return ()
348
349 onException :: IO a -> IO () -> IO a
350 onException io what = io `catch` \e -> do what
351                                           throw (e :: SomeException)
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 mode = bracket (openFile name mode) hClose
374 --
375 #ifndef __NHC__
376 bracket 
377         :: IO a         -- ^ computation to run first (\"acquire resource\")
378         -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
379         -> (a -> IO c)  -- ^ computation to run in-between
380         -> IO c         -- returns the value from the in-between computation
381 bracket before after thing =
382   block (do
383     a <- before 
384     r <- catchAny
385            (unblock (thing a))
386            (\e -> do { after a; throw e })
387     after a
388     return r
389  )
390 #endif
391
392 -- | A specialised variant of 'bracket' with just a computation to run
393 -- afterward.
394 -- 
395 finally :: IO a         -- ^ computation to run first
396         -> IO b         -- ^ computation to run afterward (even if an exception 
397                         -- was raised)
398         -> IO a         -- returns the value from the first computation
399 a `finally` sequel =
400   block (do
401     r <- catchAny
402              (unblock a)
403              (\e -> do { sequel; throw e })
404     sequel
405     return r
406   )
407
408 -- | A variant of 'bracket' where the return value from the first computation
409 -- is not required.
410 bracket_ :: IO a -> IO b -> IO c -> IO c
411 bracket_ before after thing = bracket before (const after) (const thing)
412
413 -- | Like bracket, but only performs the final action if there was an 
414 -- exception raised by the in-between computation.
415 bracketOnError
416         :: IO a         -- ^ computation to run first (\"acquire resource\")
417         -> (a -> IO b)  -- ^ computation to run last (\"release resource\")
418         -> (a -> IO c)  -- ^ computation to run in-between
419         -> IO c         -- returns the value from the in-between computation
420 bracketOnError before after thing =
421   block (do
422     a <- before 
423     catchAny
424         (unblock (thing a))
425         (\e -> do { after a; throw e })
426  )
427
428 -- -----------------------------------------------------------------------------
429 -- Asynchronous exceptions
430
431 {- $async
432
433  #AsynchronousExceptions# Asynchronous exceptions are so-called because they arise due to
434 external influences, and can be raised at any point during execution.
435 'StackOverflow' and 'HeapOverflow' are two examples of
436 system-generated asynchronous exceptions.
437
438 The primary source of asynchronous exceptions, however, is
439 'throwTo':
440
441 >  throwTo :: ThreadId -> Exception -> IO ()
442
443 'throwTo' (also 'throwDynTo' and 'Control.Concurrent.killThread') allows one
444 running thread to raise an arbitrary exception in another thread.  The
445 exception is therefore asynchronous with respect to the target thread,
446 which could be doing anything at the time it receives the exception.
447 Great care should be taken with asynchronous exceptions; it is all too
448 easy to introduce race conditions by the over zealous use of
449 'throwTo'.
450 -}
451
452 {- $block_handler
453 There\'s an implied 'block' around every exception handler in a call
454 to one of the 'catch' family of functions.  This is because that is
455 what you want most of the time - it eliminates a common race condition
456 in starting an exception handler, because there may be no exception
457 handler on the stack to handle another exception if one arrives
458 immediately.  If asynchronous exceptions are blocked on entering the
459 handler, though, we have time to install a new exception handler
460 before being interrupted.  If this weren\'t the default, one would have
461 to write something like
462
463 >      block (
464 >           catch (unblock (...))
465 >                      (\e -> handler)
466 >      )
467
468 If you need to unblock asynchronous exceptions again in the exception
469 handler, just use 'unblock' as normal.
470
471 Note that 'try' and friends /do not/ have a similar default, because
472 there is no exception handler in this case.  If you want to use 'try'
473 in an asynchronous-exception-safe way, you will need to use
474 'block'.
475 -}
476
477 {- $interruptible
478
479 Some operations are /interruptible/, which means that they can receive
480 asynchronous exceptions even in the scope of a 'block'.  Any function
481 which may itself block is defined as interruptible; this includes
482 'Control.Concurrent.MVar.takeMVar'
483 (but not 'Control.Concurrent.MVar.tryTakeMVar'),
484 and most operations which perform
485 some I\/O with the outside world.  The reason for having
486 interruptible operations is so that we can write things like
487
488 >      block (
489 >         a <- takeMVar m
490 >         catch (unblock (...))
491 >               (\e -> ...)
492 >      )
493
494 if the 'Control.Concurrent.MVar.takeMVar' was not interruptible,
495 then this particular
496 combination could lead to deadlock, because the thread itself would be
497 blocked in a state where it can\'t receive any asynchronous exceptions.
498 With 'Control.Concurrent.MVar.takeMVar' interruptible, however, we can be
499 safe in the knowledge that the thread can receive exceptions right up
500 until the point when the 'Control.Concurrent.MVar.takeMVar' succeeds.
501 Similar arguments apply for other interruptible operations like
502 'System.IO.openFile'.
503 -}
504
505 #if !(__GLASGOW_HASKELL__ || __NHC__)
506 assert :: Bool -> a -> a
507 assert True x = x
508 assert False _ = throw (AssertionFailed "")
509 #endif
510
511 recSelError, recConError, irrefutPatError, runtimeError,
512              nonExhaustiveGuardsError, patError, noMethodBindingError
513         :: Addr# -> a   -- All take a UTF8-encoded C string
514
515 recSelError              s = throw (RecSelError (unpackCStringUtf8# s)) -- No location info unfortunately
516 runtimeError             s = error (unpackCStringUtf8# s)               -- No location info unfortunately
517
518 nonExhaustiveGuardsError s = throw (PatternMatchFail (untangle s "Non-exhaustive guards in"))
519 irrefutPatError          s = throw (PatternMatchFail (untangle s "Irrefutable pattern failed for pattern"))
520 recConError              s = throw (RecConError      (untangle s "Missing field in record construction"))
521 noMethodBindingError     s = throw (NoMethodError    (untangle s "No instance nor default method for class operation"))
522 patError                 s = throw (PatternMatchFail (untangle s "Non-exhaustive patterns in"))
523
524 -----
525
526 data PatternMatchFail = PatternMatchFail String
527 INSTANCE_TYPEABLE0(PatternMatchFail,patternMatchFailTc,"PatternMatchFail")
528
529 instance Exception PatternMatchFail
530
531 instance Show PatternMatchFail where
532     showsPrec _ (PatternMatchFail err) = showString err
533
534 -----
535
536 data RecSelError = RecSelError String
537 INSTANCE_TYPEABLE0(RecSelError,recSelErrorTc,"RecSelError")
538
539 instance Exception RecSelError
540
541 instance Show RecSelError where
542     showsPrec _ (RecSelError err) = showString err
543
544 -----
545
546 data RecConError = RecConError String
547 INSTANCE_TYPEABLE0(RecConError,recConErrorTc,"RecConError")
548
549 instance Exception RecConError
550
551 instance Show RecConError where
552     showsPrec _ (RecConError err) = showString err
553
554 -----
555
556 data RecUpdError = RecUpdError String
557 INSTANCE_TYPEABLE0(RecUpdError,recUpdErrorTc,"RecUpdError")
558
559 instance Exception RecUpdError
560
561 instance Show RecUpdError where
562     showsPrec _ (RecUpdError err) = showString err
563
564 -----
565
566 data NoMethodError = NoMethodError String
567 INSTANCE_TYPEABLE0(NoMethodError,noMethodErrorTc,"NoMethodError")
568
569 instance Exception NoMethodError
570
571 instance Show NoMethodError where
572     showsPrec _ (NoMethodError err) = showString err
573
574 -----
575
576 data AssertionFailed = AssertionFailed String
577 INSTANCE_TYPEABLE0(AssertionFailed,assertionFailedTc,"AssertionFailed")
578
579 instance Exception AssertionFailed
580
581 instance Show AssertionFailed where
582     showsPrec _ (AssertionFailed err) = showString err
583
584 -----
585
586 data NonTermination = NonTermination
587 INSTANCE_TYPEABLE0(NonTermination,nonTerminationTc,"NonTermination")
588
589 instance Exception NonTermination
590
591 instance Show NonTermination where
592     showsPrec _ NonTermination = showString "<<loop>>"
593
594 -- GHC's RTS calls this
595 nonTermination :: SomeException
596 nonTermination = toException NonTermination
597
598 -----
599
600 data NestedAtomically = NestedAtomically
601 INSTANCE_TYPEABLE0(NestedAtomically,nestedAtomicallyTc,"NestedAtomically")
602
603 instance Exception NestedAtomically
604
605 instance Show NestedAtomically where
606     showsPrec _ NestedAtomically = showString "Control.Concurrent.STM.atomically was nested"
607
608 -- GHC's RTS calls this
609 nestedAtomically :: SomeException
610 nestedAtomically = toException NestedAtomically
611
612 -----
613
614 instance Exception Dynamic
615
616 -----
617
618 assertError :: Addr# -> Bool -> a -> a
619 assertError str pred v
620   | pred      = v
621   | otherwise = throw (AssertionFailed (untangle str "Assertion failed"))
622
623 {-
624 (untangle coded message) expects "coded" to be of the form
625         "location|details"
626 It prints
627         location message details
628 -}
629 untangle :: Addr# -> String -> String
630 untangle coded message
631   =  location
632   ++ ": " 
633   ++ message
634   ++ details
635   ++ "\n"
636   where
637     coded_str = unpackCStringUtf8# coded
638
639     (location, details)
640       = case (span not_bar coded_str) of { (loc, rest) ->
641         case rest of
642           ('|':det) -> (loc, ' ' : det)
643           _         -> (loc, "")
644         }
645     not_bar c = c /= '|'
646
647 -- XXX From GHC.Conc
648 throwTo :: Exception e => ThreadId -> e -> IO ()
649 throwTo (ThreadId id) ex = IO $ \ s ->
650    case (killThread# id (toException ex) s) of s1 -> (# s1, () #)
651