4dce281d50174cbbbe711b2e57c51197e8714514
[ghc-base.git] / GHC / Exception.lhs
1 \begin{code}
2 {-# OPTIONS_GHC -XNoImplicitPrelude #-}
3 {-# OPTIONS_HADDOCK hide #-}
4 -----------------------------------------------------------------------------
5 -- |
6 -- Module      :  GHC.Exception
7 -- Copyright   :  (c) The University of Glasgow, 1998-2002
8 -- License     :  see libraries/base/LICENSE
9 -- 
10 -- Maintainer  :  cvs-ghc@haskell.org
11 -- Stability   :  internal
12 -- Portability :  non-portable (GHC extensions)
13 --
14 -- Exceptions and exception-handling functions.
15 -- 
16 -----------------------------------------------------------------------------
17
18 -- #hide
19 module GHC.Exception where
20
21 import Data.Maybe
22 import {-# SOURCE #-} Data.Typeable (Typeable, cast)
23 import GHC.Base
24 import GHC.Show
25 \end{code}
26
27 %*********************************************************
28 %*                                                      *
29 \subsection{Exceptions}
30 %*                                                      *
31 %*********************************************************
32
33 \begin{code}
34 {- |
35 The @SomeException@ type is the root of the exception type hierarchy.
36 When an exception of type @e@ is thrown, behind the scenes it is
37 encapsulated in a @SomeException@.
38 -}
39 data SomeException = forall e . Exception e => SomeException e
40     deriving Typeable
41
42 instance Show SomeException where
43     showsPrec p (SomeException e) = showsPrec p e
44
45 {- |
46 Any type that you wish to throw or catch as an exception must be an
47 instance of the @Exception@ class. The simplest case is a new exception
48 type directly below the root:
49
50 > data MyException = ThisException | ThatException
51 >     deriving (Show, Typeable)
52 >
53 > instance Exception MyException
54
55 The default method definitions in the @Exception@ class do what we need
56 in this case. You can now throw and catch @ThisException@ and
57 @ThatException@ as exceptions:
58
59 @
60 *Main> throw ThisException `catch` \e -> putStrLn (\"Caught \" ++ show (e :: MyException))
61 Caught ThisException
62 @
63
64 In more complicated examples, you may wish to define a whole hierarchy
65 of exceptions:
66
67 > ---------------------------------------------------------------------
68 > -- Make the root exception type for all the exceptions in a compiler
69 >
70 > data SomeCompilerException = forall e . Exception e => SomeCompilerException e
71 >     deriving Typeable
72 >
73 > instance Show SomeCompilerException where
74 >     show (SomeCompilerException e) = show e
75 >
76 > instance Exception SomeCompilerException
77 >
78 > compilerExceptionToException :: Exception e => e -> SomeException
79 > compilerExceptionToException = toException . SomeCompilerException
80 >
81 > compilerExceptionFromException :: Exception e => SomeException -> Maybe e
82 > compilerExceptionFromException x = do
83 >     SomeCompilerException a <- fromException x
84 >     cast a
85 >
86 > ---------------------------------------------------------------------
87 > -- Make a subhierarchy for exceptions in the frontend of the compiler
88 >
89 > data SomeFrontendException = forall e . Exception e => SomeFrontendException e
90 >     deriving Typeable
91 >
92 > instance Show SomeFrontendException where
93 >     show (SomeFrontendException e) = show e
94 >
95 > instance Exception SomeFrontendException where
96 >     toException = compilerExceptionToException
97 >     fromException = compilerExceptionFromException
98 >
99 > frontendExceptionToException :: Exception e => e -> SomeException
100 > frontendExceptionToException = toException . SomeFrontendException
101 >
102 > frontendExceptionFromException :: Exception e => SomeException -> Maybe e
103 > frontendExceptionFromException x = do
104 >     SomeFrontendException a <- fromException x
105 >     cast a
106 >
107 > ---------------------------------------------------------------------
108 > -- Make an exception type for a particular frontend compiler exception
109 >
110 > data MismatchedParentheses = MismatchedParentheses
111 >     deriving (Typeable, Show)
112 >
113 > instance Exception MismatchedParentheses where
114 >     toException   = frontendExceptionToException
115 >     fromException = frontendExceptionFromException
116
117 We can now catch a @MismatchedParentheses@ exception as
118 @MismatchedParentheses@, @SomeFrontendException@ or
119 @SomeCompilerException@, but not other types, e.g. @IOException@:
120
121 @
122 *Main> throw MismatchedParentheses `catch` \e -> putStrLn (\"Caught \" ++ show (e :: MismatchedParentheses))
123 Caught MismatchedParentheses
124 *Main> throw MismatchedParentheses `catch` \e -> putStrLn (\"Caught \" ++ show (e :: SomeFrontendException))
125 Caught MismatchedParentheses
126 *Main> throw MismatchedParentheses `catch` \e -> putStrLn (\"Caught \" ++ show (e :: SomeCompilerException))
127 Caught MismatchedParentheses
128 *Main> throw MismatchedParentheses `catch` \e -> putStrLn (\"Caught \" ++ show (e :: IOException))
129 *** Exception: MismatchedParentheses
130 @
131
132 -}
133 class (Typeable e, Show e) => Exception e where
134     toException   :: e -> SomeException
135     fromException :: SomeException -> Maybe e
136
137     toException = SomeException
138     fromException (SomeException e) = cast e
139
140 instance Exception SomeException where
141     toException se = se
142     fromException = Just
143 \end{code}
144
145 %*********************************************************
146 %*                                                      *
147 \subsection{Primitive throw}
148 %*                                                      *
149 %*********************************************************
150
151 \begin{code}
152 -- | Throw an exception.  Exceptions may be thrown from purely
153 -- functional code, but may only be caught within the 'IO' monad.
154 throw :: Exception e => e -> a
155 throw e = raise# (toException e)
156 \end{code}
157
158 \begin{code}
159 -- |This is thrown when the user calls 'error'. The @String@ is the
160 -- argument given to 'error'.
161 data ErrorCall = ErrorCall String
162     deriving Typeable
163
164 instance Exception ErrorCall
165
166 instance Show ErrorCall where
167     showsPrec _ (ErrorCall err) = showString err
168
169 -----
170
171 -- |Arithmetic exceptions.
172 data ArithException
173   = Overflow
174   | Underflow
175   | LossOfPrecision
176   | DivideByZero
177   | Denormal
178   deriving (Eq, Ord, Typeable)
179
180 instance Exception ArithException
181
182 instance Show ArithException where
183   showsPrec _ Overflow        = showString "arithmetic overflow"
184   showsPrec _ Underflow       = showString "arithmetic underflow"
185   showsPrec _ LossOfPrecision = showString "loss of precision"
186   showsPrec _ DivideByZero    = showString "divide by zero"
187   showsPrec _ Denormal        = showString "denormal"
188
189 \end{code}