a04c66a6004072797e3fb7c7d5883a965e3237b6
[ghc-hetmet.git] / ghc / lib / std / PrelException.lhs
1 % -----------------------------------------------------------------------------
2 % $Id: PrelException.lhs,v 1.16 2000/04/10 13:35:45 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 failed
40   | NonExhaustiveGuards String          -- A guard match failed
41   | RecSelError         String          -- Selecting a non-existent field
42   | RecConError         String          -- Field missing in record construction
43   | RecUpdError         String          -- Record doesn't contain updated field
44   | AssertionFailed     String          -- Assertions
45   | DynException        Dynamic         -- Dynamic exceptions
46   | AsyncException      AsyncException  -- Externally generated errors
47   | PutFullMVar                         -- Put on a full MVar
48   | BlockedOnDeadMVar                   -- Blocking on a dead MVar
49   | NonTermination
50
51 data ArithException
52   = Overflow
53   | Underflow
54   | LossOfPrecision
55   | DivideByZero
56   | Denormal
57   deriving (Eq, Ord)
58
59 data AsyncException
60   = StackOverflow
61   | HeapOverflow
62   | ThreadKilled
63   deriving (Eq, Ord)
64
65 data ArrayException
66   = IndexOutOfBounds    String          -- out-of-range array access
67   | UndefinedElement    String          -- evaluating an undefined element
68
69 stackOverflow, heapOverflow :: Exception -- for the RTS
70 stackOverflow = AsyncException StackOverflow
71 heapOverflow  = AsyncException HeapOverflow
72
73 instance Show ArithException where
74   showsPrec _ Overflow        = showString "arithmetic overflow"
75   showsPrec _ Underflow       = showString "arithmetic underflow"
76   showsPrec _ LossOfPrecision = showString "loss of precision"
77   showsPrec _ DivideByZero    = showString "divide by zero"
78   showsPrec _ Denormal        = showString "denormal"
79
80 instance Show AsyncException where
81   showsPrec _ StackOverflow   = showString "stack overflow"
82   showsPrec _ HeapOverflow    = showString "heap overflow"
83   showsPrec _ ThreadKilled    = showString "thread killed"
84
85 instance Show ArrayException where
86   showsPrec _ (IndexOutOfBounds s)
87         = showString "array index out of range"
88         . (if not (null s) then showString ": " . showString s
89                            else id)
90   showsPrec _ (UndefinedElement s)
91         = showString "undefined array element"
92         . (if not (null s) then showString ": " . showString s
93                            else id)
94
95 instance Show Exception where
96   showsPrec _ (IOException err)          = shows err
97   showsPrec _ (ArithException err)       = shows err
98   showsPrec _ (ArrayException err)       = shows err
99   showsPrec _ (ErrorCall err)            = showString err
100   showsPrec _ (NoMethodError err)        = showString err
101   showsPrec _ (PatternMatchFail err)     = showString err
102   showsPrec _ (NonExhaustiveGuards err)  = showString err
103   showsPrec _ (RecSelError err)          = showString err
104   showsPrec _ (RecConError err)          = showString err
105   showsPrec _ (RecUpdError err)          = showString err
106   showsPrec _ (AssertionFailed err)      = showString err
107   showsPrec _ (AsyncException e)         = shows e
108   showsPrec _ (DynException _err)        = showString "unknown exception"
109   showsPrec _ (PutFullMVar)              = showString "putMVar: full MVar"
110   showsPrec _ (BlockedOnDeadMVar)        = showString "thread blocked indefinitely"
111   showsPrec _ (NonTermination)           = showString "<<loop>>"
112 \end{code}
113
114 %*********************************************************
115 %*                                                      *
116 \subsection{Primitive catch and throw}
117 %*                                                      *
118 %*********************************************************
119
120 \begin{code}
121 throw :: Exception -> a
122
123 #ifdef __HUGS__
124 throw = primRaise
125 #else
126 throw exception = raise# exception
127 #endif
128 \end{code}
129
130 catchException used to handle the passing around of the state to the
131 action and the handler.  This turned out to be a bad idea - it meant
132 that we had to wrap both arguments in thunks so they could be entered
133 as normal (remember IO returns an unboxed pair...).
134
135 Now catch# has type
136
137     catch# :: IO a -> (b -> IO a) -> IO a
138
139 (well almost; the compiler doesn't know about the IO newtype so we
140 have to work around that in the definition of catchException below).
141
142 \begin{code}
143 catchException :: IO a -> (Exception -> IO a) -> IO a
144 #ifdef __HUGS__
145 catchException m k =  ST (\s -> unST m s `primCatch'` \ err -> unST (k err) s)
146 #else
147 catchException (IO m) k =  IO $ \s -> catch# m (\ex -> unIO (k ex)) s
148 #endif
149
150 catch           :: IO a -> (IOError -> IO a) -> IO a 
151 catch m k       =  catchException m handler
152   where handler (IOException err) = k err
153         handler other             = throw other
154
155 catchNonIO      :: IO a -> (Exception -> IO a) -> IO a 
156 catchNonIO m k  =  catchException m handler
157   where handler (IOException err) = ioError err
158         handler other             = k other
159 \end{code}
160
161
162 %*********************************************************
163 %*                                                      *
164 \subsection{Try and bracket}
165 %*                                                      *
166 %*********************************************************
167
168 The construct @try comp@ exposes errors which occur within a
169 computation, and which are not fully handled.  It always succeeds.
170
171 \begin{code}
172 try            :: IO a -> IO (Either IOError a)
173 try f          =  catch (do r <- f
174                             return (Right r))
175                         (return . Left)
176
177 bracket        :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c
178 bracket before after m = do
179         x  <- before
180         rs <- try (m x)
181         after x
182         case rs of
183            Right r -> return r
184            Left  e -> ioError e
185
186 -- variant of the above where middle computation doesn't want x
187 bracket_        :: IO a -> (a -> IO b) -> IO c -> IO c
188 bracket_ before after m = do
189          x  <- before
190          rs <- try m
191          after x
192          case rs of
193             Right r -> return r
194             Left  e -> ioError e
195 \end{code}
196
197
198 %*********************************************************
199 %*                                                      *
200 \subsection{ioError}
201 %*                                                      *
202 %*********************************************************
203
204 Why is this stuff here?  To avoid recursive module dependencies of
205 course.
206
207 \begin{code}
208 ioError         :: IOError -> IO a 
209 ioError err     =  IO $ \s -> throw (IOException err) s
210         -- (ioError e) isn't an exception; we only throw
211         -- the exception when applied to a world
212 \end{code}
213