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