Make Data.Typeable imports and exports more explicit
[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 data SomeException = forall e . Exception e => SomeException e
35     deriving Typeable
36
37 instance Show SomeException where
38     showsPrec p (SomeException e) = showsPrec p e
39
40 class (Typeable e, Show e) => Exception e where
41     toException   :: e -> SomeException
42     fromException :: SomeException -> Maybe e
43
44     toException = SomeException
45     fromException (SomeException e) = cast e
46
47 instance Exception SomeException where
48     toException se = se
49     fromException = Just
50 \end{code}
51
52 %*********************************************************
53 %*                                                      *
54 \subsection{Primitive throw}
55 %*                                                      *
56 %*********************************************************
57
58 \begin{code}
59 -- | Throw an exception.  Exceptions may be thrown from purely
60 -- functional code, but may only be caught within the 'IO' monad.
61 throw :: Exception e => e -> a
62 throw e = raise# (toException e)
63 \end{code}
64
65 \begin{code}
66 data ErrorCall = ErrorCall String
67     deriving Typeable
68
69 instance Exception ErrorCall
70
71 instance Show ErrorCall where
72     showsPrec _ (ErrorCall err) = showString err
73
74 -----
75
76 -- |The type of arithmetic exceptions
77 data ArithException
78   = Overflow
79   | Underflow
80   | LossOfPrecision
81   | DivideByZero
82   | Denormal
83   deriving (Eq, Ord, Typeable)
84
85 instance Exception ArithException
86
87 instance Show ArithException where
88   showsPrec _ Overflow        = showString "arithmetic overflow"
89   showsPrec _ Underflow       = showString "arithmetic underflow"
90   showsPrec _ LossOfPrecision = showString "loss of precision"
91   showsPrec _ DivideByZero    = showString "divide by zero"
92   showsPrec _ Denormal        = showString "denormal"
93
94 \end{code}