[project @ 2000-06-09 13:48:46 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelException.lhs
1 % -----------------------------------------------------------------------------
2 % $Id: PrelException.lhs,v 1.20 2000/06/09 13:49:35 simonmar Exp $
3 %
4 % (c) The GRAP/AQUA Project, Glasgow University, 1998
5 %
6
7 Exceptions and exception-handling functions.
8
9 \begin{code}
10 {-# OPTIONS -fno-implicit-prelude #-}
11
12 #ifndef __HUGS__
13 module PrelException where
14
15 import PrelList
16 import PrelBase
17 import PrelMaybe
18 import PrelShow
19 import PrelIOBase
20 import PrelST           ( STret(..) )
21 import PrelDynamic
22 import PrelGHC
23 #endif
24 \end{code}
25
26 %*********************************************************
27 %*                                                      *
28 \subsection{Exception datatype and operations}
29 %*                                                      *
30 %*********************************************************
31
32 \begin{code}
33 data Exception
34   = IOException         IOError         -- IO exceptions (from 'ioError')
35   | ArithException      ArithException  -- Arithmetic exceptions
36   | ArrayException      ArrayException  -- Array-related exceptions
37   | ErrorCall           String          -- Calls to 'error'
38   | NoMethodError       String          -- A non-existent method was invoked
39   | PatternMatchFail    String          -- A pattern match / guard failure
40   | RecSelError         String          -- Selecting a non-existent field
41   | RecConError         String          -- Field missing in record construction
42   | RecUpdError         String          -- Record doesn't contain updated field
43   | AssertionFailed     String          -- Assertions
44   | DynException        Dynamic         -- Dynamic exceptions
45   | AsyncException      AsyncException  -- Externally generated errors
46   | PutFullMVar                         -- Put on a full MVar
47   | BlockedOnDeadMVar                   -- Blocking on a dead MVar
48   | NonTermination
49
50 data ArithException
51   = Overflow
52   | Underflow
53   | LossOfPrecision
54   | DivideByZero
55   | Denormal
56   deriving (Eq, Ord)
57
58 data AsyncException
59   = StackOverflow
60   | HeapOverflow
61   | ThreadKilled
62   deriving (Eq, Ord)
63
64 data ArrayException
65   = IndexOutOfBounds    String          -- out-of-range array access
66   | UndefinedElement    String          -- evaluating an undefined element
67
68 stackOverflow, heapOverflow :: Exception -- for the RTS
69 stackOverflow = AsyncException StackOverflow
70 heapOverflow  = AsyncException HeapOverflow
71
72 instance Show ArithException where
73   showsPrec _ Overflow        = showString "arithmetic overflow"
74   showsPrec _ Underflow       = showString "arithmetic underflow"
75   showsPrec _ LossOfPrecision = showString "loss of precision"
76   showsPrec _ DivideByZero    = showString "divide by zero"
77   showsPrec _ Denormal        = showString "denormal"
78
79 instance Show AsyncException where
80   showsPrec _ StackOverflow   = showString "stack overflow"
81   showsPrec _ HeapOverflow    = showString "heap overflow"
82   showsPrec _ ThreadKilled    = showString "thread killed"
83
84 instance Show ArrayException where
85   showsPrec _ (IndexOutOfBounds s)
86         = showString "array index out of range"
87         . (if not (null s) then showString ": " . showString s
88                            else id)
89   showsPrec _ (UndefinedElement s)
90         = showString "undefined array element"
91         . (if not (null s) then showString ": " . showString s
92                            else id)
93
94 instance Show Exception where
95   showsPrec _ (IOException err)          = shows err
96   showsPrec _ (ArithException err)       = shows err
97   showsPrec _ (ArrayException err)       = shows err
98   showsPrec _ (ErrorCall err)            = showString err
99   showsPrec _ (NoMethodError err)        = showString err
100   showsPrec _ (PatternMatchFail err)     = showString err
101   showsPrec _ (RecSelError err)          = showString err
102   showsPrec _ (RecConError err)          = showString err
103   showsPrec _ (RecUpdError err)          = showString err
104   showsPrec _ (AssertionFailed err)      = showString err
105   showsPrec _ (AsyncException e)         = shows e
106   showsPrec _ (DynException _err)        = showString "unknown exception"
107   showsPrec _ (PutFullMVar)              = showString "putMVar: full MVar"
108   showsPrec _ (BlockedOnDeadMVar)        = showString "thread blocked indefinitely"
109   showsPrec _ (NonTermination)           = showString "<<loop>>"
110 \end{code}
111
112 %*********************************************************
113 %*                                                      *
114 \subsection{Primitive catch and throw}
115 %*                                                      *
116 %*********************************************************
117
118 \begin{code}
119 throw :: Exception -> a
120
121 #ifdef __HUGS__
122 throw = primRaise
123 #else
124 throw exception = raise# exception
125 #endif
126 \end{code}
127
128 catchException used to handle the passing around of the state to the
129 action and the handler.  This turned out to be a bad idea - it meant
130 that we had to wrap both arguments in thunks so they could be entered
131 as normal (remember IO returns an unboxed pair...).
132
133 Now catch# has type
134
135     catch# :: IO a -> (b -> IO a) -> IO a
136
137 (well almost; the compiler doesn't know about the IO newtype so we
138 have to work around that in the definition of catchException below).
139
140 \begin{code}
141 catchException :: IO a -> (Exception -> IO a) -> IO a
142 #ifdef __HUGS__
143 catchException m k =  ST (\s -> unST m s `primCatch'` \ err -> unST (k err) s)
144 #else
145 catchException (IO m) k =  IO $ \s -> catch# m (\ex -> unIO (k ex)) s
146 #endif
147
148 catch           :: IO a -> (IOError -> IO a) -> IO a 
149 catch m k       =  catchException m handler
150   where handler (IOException err) = k err
151         handler other             = throw other
152
153 catchNonIO      :: IO a -> (Exception -> IO a) -> IO a 
154 catchNonIO m k  =  catchException m handler
155   where handler (IOException err) = ioError err
156         handler other             = k other
157 \end{code}
158
159
160 %*********************************************************
161 %*                                                      *
162 \subsection{Try and bracket}
163 %*                                                      *
164 %*********************************************************
165
166 The construct @try comp@ exposes errors which occur within a
167 computation, and which are not fully handled.  It always succeeds.
168
169 \begin{code}
170 try            :: IO a -> IO (Either IOError a)
171 try f          =  catch (do r <- f
172                             return (Right r))
173                         (return . Left)
174
175 bracket        :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c
176 bracket before after m = do
177         x  <- before
178         rs <- try (m x)
179         after x
180         case rs of
181            Right r -> return r
182            Left  e -> ioError e
183
184 -- variant of the above where middle computation doesn't want x
185 bracket_        :: IO a -> (a -> IO b) -> IO c -> IO c
186 bracket_ before after m = do
187          x  <- before
188          rs <- try m
189          after x
190          case rs of
191             Right r -> return r
192             Left  e -> ioError e
193 \end{code}
194
195
196 %*********************************************************
197 %*                                                      *
198 \subsection{ioError}
199 %*                                                      *
200 %*********************************************************
201
202 Why is this stuff here?  To avoid recursive module dependencies of
203 course.
204
205 \begin{code}
206 ioError         :: IOError -> IO a 
207 ioError err     =  IO $ \s -> throw (IOException err) s
208         -- (ioError e) isn't an exception; we only throw
209         -- the exception when applied to a world
210 \end{code}
211
212 %*********************************************************
213 %*                                                      *
214 \subsection{Controlling asynchronous exception delivery}
215 %*                                                      *
216 %*********************************************************
217
218 \begin{code}
219 #ifndef __HUGS__
220 blockAsyncExceptions :: IO a -> IO a
221 blockAsyncExceptions (IO io) = IO $ blockAsyncExceptions# io
222
223 unblockAsyncExceptions :: IO a -> IO a
224 unblockAsyncExceptions (IO io) = IO $ unblockAsyncExceptions# io
225 #else
226 -- Not implemented yet in Hugs.
227 blockAsyncExceptions :: IO a -> IO a
228 blockAsyncExceptions (IO io) = IO io
229
230 unblockAsyncExceptions :: IO a -> IO a
231 unblockAsyncExceptions (IO io) = IO io
232 #endif
233 \end{code}
234