Don't look for actual OldException.Exception exceptions
[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 -----------------------------------------------------------------------------
29
30 module Control.Exception (
31
32         -- * The Exception type
33 #ifdef __HUGS__
34         SomeException,
35 #else
36         SomeException(..),
37 #endif
38         Exception(..),          -- class
39         IOException,            -- instance Eq, Ord, Show, Typeable, Exception
40         ArithException(..),     -- instance Eq, Ord, Show, Typeable, Exception
41         ArrayException(..),     -- instance Eq, Ord, Show, Typeable, Exception
42         AssertionFailed(..),
43         AsyncException(..),     -- instance Eq, Ord, Show, Typeable, Exception
44
45 #if __GLASGOW_HASKELL__ || __HUGS__
46         NonTermination(..),
47         NestedAtomically(..),
48 #endif
49 #ifdef __NHC__
50         System.ExitCode(),      -- instance Exception
51 #endif
52
53         BlockedOnDeadMVar(..),
54         BlockedIndefinitely(..),
55         Deadlock(..),
56         NoMethodError(..),
57         PatternMatchFail(..),
58         RecConError(..),
59         RecSelError(..),
60         RecUpdError(..),
61         ErrorCall(..),
62
63         -- * Throwing exceptions
64         throwIO,        -- :: Exception -> IO a
65         throw,          -- :: Exception -> a
66         ioError,        -- :: IOError -> IO a
67 #ifdef __GLASGOW_HASKELL__
68         throwTo,        -- :: ThreadId -> Exception -> a
69 #endif
70
71         -- * Catching Exceptions
72
73         -- |There are several functions for catching and examining
74         -- exceptions; all of them may only be used from within the
75         -- 'IO' monad.
76
77         -- ** The @catch@ functions
78         catch,     -- :: IO a -> (Exception -> IO a) -> IO a
79         catches, Handler(..),
80         catchJust, -- :: (Exception -> Maybe b) -> IO a -> (b -> IO a) -> IO a
81
82         -- ** The @handle@ functions
83         handle,    -- :: (Exception -> IO a) -> IO a -> IO a
84         handleJust,-- :: (Exception -> Maybe b) -> (b -> IO a) -> IO a -> IO a
85
86         -- ** The @try@ functions
87         try,       -- :: IO a -> IO (Either Exception a)
88         tryJust,   -- :: (Exception -> Maybe b) -> a    -> IO (Either b a)
89         onException,
90
91         -- ** The @evaluate@ function
92         evaluate,  -- :: a -> IO a
93
94         -- ** The @mapException@ function
95         mapException,           -- :: (Exception -> Exception) -> a -> a
96
97         -- * Asynchronous Exceptions
98
99         -- $async
100
101         -- ** Asynchronous exception control
102
103         -- |The following two functions allow a thread to control delivery of
104         -- asynchronous exceptions during a critical region.
105
106         block,          -- :: IO a -> IO a
107         unblock,        -- :: IO a -> IO a
108         blocked,        -- :: IO Bool
109
110         -- *** Applying @block@ to an exception handler
111
112         -- $block_handler
113
114         -- *** Interruptible operations
115
116         -- $interruptible
117
118         -- * Assertions
119
120         assert,         -- :: Bool -> a -> a
121
122         -- * Utilities
123
124         bracket,        -- :: IO a -> (a -> IO b) -> (a -> IO c) -> IO ()
125         bracket_,       -- :: IO a -> IO b -> IO c -> IO ()
126         bracketOnError,
127
128         finally,        -- :: IO a -> IO b -> IO a
129   ) where
130
131 import Control.Exception.Base
132
133 #ifdef __GLASGOW_HASKELL__
134 import GHC.Base
135 import GHC.IOBase
136 import Data.Maybe
137 #else
138 import Prelude hiding (catch)
139 #endif
140
141 #ifdef __NHC__
142 import System (ExitCode())
143 #endif
144
145 data Handler a = forall e . Exception e => Handler (e -> IO a)
146
147 catches :: IO a -> [Handler a] -> IO a
148 catches io handlers = io `catch` catchesHandler handlers
149
150 catchesHandler :: [Handler a] -> SomeException -> IO a
151 catchesHandler handlers e = foldr tryHandler (throw e) handlers
152     where tryHandler (Handler handler) res
153               = case fromException e of
154                 Just e' -> handler e'
155                 Nothing -> res
156
157 -- -----------------------------------------------------------------------------
158 -- Asynchronous exceptions
159
160 {- $async
161
162  #AsynchronousExceptions# Asynchronous exceptions are so-called because they arise due to
163 external influences, and can be raised at any point during execution.
164 'StackOverflow' and 'HeapOverflow' are two examples of
165 system-generated asynchronous exceptions.
166
167 The primary source of asynchronous exceptions, however, is
168 'throwTo':
169
170 >  throwTo :: ThreadId -> Exception -> IO ()
171
172 'throwTo' (also 'throwDynTo' and 'Control.Concurrent.killThread') allows one
173 running thread to raise an arbitrary exception in another thread.  The
174 exception is therefore asynchronous with respect to the target thread,
175 which could be doing anything at the time it receives the exception.
176 Great care should be taken with asynchronous exceptions; it is all too
177 easy to introduce race conditions by the over zealous use of
178 'throwTo'.
179 -}
180
181 {- $block_handler
182 There\'s an implied 'block' around every exception handler in a call
183 to one of the 'catch' family of functions.  This is because that is
184 what you want most of the time - it eliminates a common race condition
185 in starting an exception handler, because there may be no exception
186 handler on the stack to handle another exception if one arrives
187 immediately.  If asynchronous exceptions are blocked on entering the
188 handler, though, we have time to install a new exception handler
189 before being interrupted.  If this weren\'t the default, one would have
190 to write something like
191
192 >      block (
193 >           catch (unblock (...))
194 >                      (\e -> handler)
195 >      )
196
197 If you need to unblock asynchronous exceptions again in the exception
198 handler, just use 'unblock' as normal.
199
200 Note that 'try' and friends /do not/ have a similar default, because
201 there is no exception handler in this case.  If you want to use 'try'
202 in an asynchronous-exception-safe way, you will need to use
203 'block'.
204 -}
205
206 {- $interruptible
207
208 Some operations are /interruptible/, which means that they can receive
209 asynchronous exceptions even in the scope of a 'block'.  Any function
210 which may itself block is defined as interruptible; this includes
211 'Control.Concurrent.MVar.takeMVar'
212 (but not 'Control.Concurrent.MVar.tryTakeMVar'),
213 and most operations which perform
214 some I\/O with the outside world.  The reason for having
215 interruptible operations is so that we can write things like
216
217 >      block (
218 >         a <- takeMVar m
219 >         catch (unblock (...))
220 >               (\e -> ...)
221 >      )
222
223 if the 'Control.Concurrent.MVar.takeMVar' was not interruptible,
224 then this particular
225 combination could lead to deadlock, because the thread itself would be
226 blocked in a state where it can\'t receive any asynchronous exceptions.
227 With 'Control.Concurrent.MVar.takeMVar' interruptible, however, we can be
228 safe in the knowledge that the thread can receive exceptions right up
229 until the point when the 'Control.Concurrent.MVar.takeMVar' succeeds.
230 Similar arguments apply for other interruptible operations like
231 'System.IO.openFile'.
232 -}