{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude
, ExistentialQuantification
, MagicHash
, RecordWildCards
, PatternSynonyms
#-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.Exception.Type
( Exception(..)
, SomeException(..), ArithException(..)
, divZeroException, overflowException, ratioZeroDenomException
, underflowException
) where
import Data.Maybe
import Data.Typeable (Typeable, cast)
import GHC.Base
import GHC.Show
data SomeException = forall e . Exception e => SomeException e
instance Show SomeException where
showsPrec :: Int -> SomeException -> ShowS
showsPrec Int
p (SomeException e
e) = Int -> e -> ShowS
forall a. Show a => Int -> a -> ShowS
Evidence bound by a superclass of: Exception of the constraint type forall e. Exception e => Show e
Evidence bound by a pattern of the constraint type Exception e
showsPrec Int
p e
e
class (Typeable e, Show e) => Exception e where
toException :: e -> SomeException
fromException :: SomeException -> Maybe e
toException = e -> SomeException
forall e. Exception e => e -> SomeException
Evidence bound by a type signature of the constraint type Exception e
SomeException
fromException (SomeException e
e) = e -> Maybe e
forall a b. (Typeable a, Typeable b) => a -> Maybe b
Evidence bound by a superclass of: Exception of the constraint type forall e. Exception e => Typeable e
Evidence bound by a type signature of the constraint type Exception e
Evidence bound by a superclass of: Exception of the constraint type forall e. Exception e => Typeable e
Evidence bound by a pattern of the constraint type Exception e
cast e
e
displayException :: e -> String
displayException = e -> String
forall a. Show a => a -> String
Evidence bound by a superclass of: Exception of the constraint type forall e. Exception e => Show e
Evidence bound by a type signature of the constraint type Exception e
show
instance Exception SomeException where
toException :: SomeException -> SomeException
toException SomeException
se = SomeException
se
fromException :: SomeException -> Maybe SomeException
fromException = SomeException -> Maybe SomeException
forall a. a -> Maybe a
Just
displayException :: SomeException -> String
displayException (SomeException e
e) = e -> String
forall e. Exception e => e -> String
Evidence bound by a pattern of the constraint type Exception e
displayException e
e
data ArithException
= Overflow
| Underflow
| LossOfPrecision
| DivideByZero
| Denormal
| RatioZeroDenominator
deriving ( Eq
, Ord
)
divZeroException, overflowException, ratioZeroDenomException, underflowException :: SomeException
divZeroException :: SomeException
divZeroException = ArithException -> SomeException
forall e. Exception e => e -> SomeException
Instance of class: Exception of the constraint type Exception ArithException
toException ArithException
DivideByZero
overflowException :: SomeException
overflowException = ArithException -> SomeException
forall e. Exception e => e -> SomeException
Instance of class: Exception of the constraint type Exception ArithException
toException ArithException
Overflow
ratioZeroDenomException :: SomeException
ratioZeroDenomException = ArithException -> SomeException
forall e. Exception e => e -> SomeException
Instance of class: Exception of the constraint type Exception ArithException
toException ArithException
RatioZeroDenominator
underflowException :: SomeException
underflowException = ArithException -> SomeException
forall e. Exception e => e -> SomeException
Instance of class: Exception of the constraint type Exception ArithException
toException ArithException
Underflow
instance Exception ArithException
instance Show ArithException where
showsPrec :: Int -> ArithException -> ShowS
showsPrec Int
_ ArithException
Overflow = String -> ShowS
showString String
"arithmetic overflow"
showsPrec Int
_ ArithException
Underflow = String -> ShowS
showString String
"arithmetic underflow"
showsPrec Int
_ ArithException
LossOfPrecision = String -> ShowS
showString String
"loss of precision"
showsPrec Int
_ ArithException
DivideByZero = String -> ShowS
showString String
"divide by zero"
showsPrec Int
_ ArithException
Denormal = String -> ShowS
showString String
"denormal"
showsPrec Int
_ ArithException
RatioZeroDenominator = String -> ShowS
showString String
"Ratio has zero denominator"