{-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ImplicitParams #-} {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE Trustworthy #-} {-# OPTIONS_HADDOCK not-home #-} module GHC.Internal.Exception.Type ( Exception(..) , SomeException(..) , displayExceptionWithInfo , someExceptionContext , addExceptionContext , mapExceptionContext , NoBacktrace(..) , HasExceptionContext , ExceptionContext(..) , emptyExceptionContext , mergeExceptionContext , ExceptionWithContext(..) , WhileHandling(..) , whileHandling , ArithException(..) , divZeroException, overflowException, ratioZeroDenomException , underflowException ) where import GHC.Internal.Data.OldList (lines, unlines, null) import GHC.Internal.Data.Maybe import GHC.Internal.Data.Typeable (Typeable, TypeRep, cast) import qualified GHC.Internal.Data.Typeable as Typeable import GHC.Internal.Base import GHC.Internal.Show import GHC.Internal.Exception.Context type HasExceptionContext = (?exceptionContext :: ExceptionContext) data WhileHandling = WhileHandling SomeException deriving Int -> WhileHandling -> ShowS [WhileHandling] -> ShowS WhileHandling -> String (Int -> WhileHandling -> ShowS) -> (WhileHandling -> String) -> ([WhileHandling] -> ShowS) -> Show WhileHandling forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> WhileHandling -> ShowS showsPrec :: Int -> WhileHandling -> ShowS $cshow :: WhileHandling -> String show :: WhileHandling -> String $cshowList :: [WhileHandling] -> ShowS showList :: [WhileHandling] -> ShowS Show instance ExceptionAnnotation WhileHandling where displayExceptionAnnotation :: WhileHandling -> String displayExceptionAnnotation (WhileHandling SomeException e) = String "While handling " String -> ShowS forall a. [a] -> [a] -> [a] ++ case String -> [String] lines (String -> [String]) -> String -> [String] forall a b. (a -> b) -> a -> b $ SomeException -> String forall e. Exception e => e -> String displayException SomeException e of [] -> String "" (String l1:[String] ls) -> [String] -> String unlines ([String] -> String) -> [String] -> String forall a b. (a -> b) -> a -> b $ String l1String -> [String] -> [String] forall a. a -> [a] -> [a] :[if String -> Bool forall a. [a] -> Bool null String l then String " |" else String " | " String -> ShowS forall a. [a] -> [a] -> [a] ++ String l | String l <- [String] ls] whileHandling :: Exception e => ExceptionWithContext e -> WhileHandling whileHandling :: forall e. Exception e => ExceptionWithContext e -> WhileHandling whileHandling ExceptionWithContext e e = SomeException -> WhileHandling WhileHandling (ExceptionWithContext e -> SomeException forall e. Exception e => e -> SomeException toException ExceptionWithContext e e) data SomeException = forall e. (Exception e, HasExceptionContext) => SomeException e someExceptionContext :: SomeException -> ExceptionContext someExceptionContext :: SomeException -> ExceptionContext someExceptionContext (SomeException e _) = HasExceptionContext ExceptionContext ?exceptionContext addExceptionContext :: ExceptionAnnotation a => a -> SomeException -> SomeException addExceptionContext :: forall a. ExceptionAnnotation a => a -> SomeException -> SomeException addExceptionContext a ann = (ExceptionContext -> ExceptionContext) -> SomeException -> SomeException mapExceptionContext (a -> ExceptionContext -> ExceptionContext forall a. ExceptionAnnotation a => a -> ExceptionContext -> ExceptionContext addExceptionAnnotation a ann) mapExceptionContext :: (ExceptionContext -> ExceptionContext) -> SomeException -> SomeException mapExceptionContext :: (ExceptionContext -> ExceptionContext) -> SomeException -> SomeException mapExceptionContext ExceptionContext -> ExceptionContext f se :: SomeException se@(SomeException e e) = let ?exceptionContext = ExceptionContext -> ExceptionContext f (SomeException -> ExceptionContext someExceptionContext SomeException se) in e -> SomeException forall e. (Exception e, HasExceptionContext) => e -> SomeException SomeException e 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 showsPrec Int p e e class (Typeable e, Show e) => Exception e where toException :: e -> SomeException fromException :: SomeException -> Maybe e toException e e = e -> SomeException forall e. (Exception e, HasExceptionContext) => e -> SomeException SomeException e e where ?exceptionContext = HasExceptionContext ExceptionContext emptyExceptionContext fromException (SomeException e e) = e -> Maybe e forall a b. (Typeable a, Typeable b) => a -> Maybe b cast e e displayException :: e -> String displayException = e -> String forall a. Show a => a -> String show backtraceDesired :: e -> Bool backtraceDesired e _ = Bool True instance Exception Void instance Exception SomeException where toException :: SomeException -> SomeException toException (SomeException e e) = let ?exceptionContext = HasExceptionContext ExceptionContext emptyExceptionContext in e -> SomeException forall e. (Exception e, HasExceptionContext) => e -> SomeException SomeException e e fromException :: SomeException -> Maybe SomeException fromException = SomeException -> Maybe SomeException forall a. a -> Maybe a Just backtraceDesired :: SomeException -> Bool backtraceDesired (SomeException e e) = e -> Bool forall e. Exception e => e -> Bool backtraceDesired e e displayException :: SomeException -> String displayException (SomeException e e) = e -> String forall e. Exception e => e -> String displayException e e displayExceptionWithInfo :: SomeException -> String displayExceptionWithInfo :: SomeException -> String displayExceptionWithInfo (SomeException e e) = case ExceptionContext -> String displayExceptionContext HasExceptionContext ExceptionContext ?exceptionContext of String "" -> String msg String dc -> String msg String -> ShowS forall a. [a] -> [a] -> [a] ++ String "\n\n" String -> ShowS forall a. [a] -> [a] -> [a] ++ String dc where msg :: String msg = TypeRep -> String displayExceptionType (e -> TypeRep forall a. Typeable a => a -> TypeRep Typeable.typeOf e e) String -> ShowS forall a. [a] -> [a] -> [a] ++ String "\n\n" String -> ShowS forall a. [a] -> [a] -> [a] ++ e -> String forall e. Exception e => e -> String displayException e e displayExceptionType :: TypeRep -> String displayExceptionType :: TypeRep -> String displayExceptionType TypeRep rep = String tyMsg String -> ShowS forall a. [a] -> [a] -> [a] ++ String ":" where tyMsg :: String tyMsg = TyCon -> String Typeable.tyConPackage TyCon tyCon String -> ShowS forall a. [a] -> [a] -> [a] ++ String ":" String -> ShowS forall a. [a] -> [a] -> [a] ++ TyCon -> String Typeable.tyConModule TyCon tyCon String -> ShowS forall a. [a] -> [a] -> [a] ++ String "." String -> ShowS forall a. [a] -> [a] -> [a] ++ TyCon -> String Typeable.tyConName TyCon tyCon tyCon :: TyCon tyCon = TypeRep -> TyCon Typeable.typeRepTyCon TypeRep rep newtype NoBacktrace e = NoBacktrace e deriving (Int -> NoBacktrace e -> ShowS [NoBacktrace e] -> ShowS NoBacktrace e -> String (Int -> NoBacktrace e -> ShowS) -> (NoBacktrace e -> String) -> ([NoBacktrace e] -> ShowS) -> Show (NoBacktrace e) forall e. Show e => Int -> NoBacktrace e -> ShowS forall e. Show e => [NoBacktrace e] -> ShowS forall e. Show e => NoBacktrace e -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: forall e. Show e => Int -> NoBacktrace e -> ShowS showsPrec :: Int -> NoBacktrace e -> ShowS $cshow :: forall e. Show e => NoBacktrace e -> String show :: NoBacktrace e -> String $cshowList :: forall e. Show e => [NoBacktrace e] -> ShowS showList :: [NoBacktrace e] -> ShowS Show) instance Exception e => Exception (NoBacktrace e) where fromException :: SomeException -> Maybe (NoBacktrace e) fromException = (e -> NoBacktrace e) -> Maybe e -> Maybe (NoBacktrace e) forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap e -> NoBacktrace e forall e. e -> NoBacktrace e NoBacktrace (Maybe e -> Maybe (NoBacktrace e)) -> (SomeException -> Maybe e) -> SomeException -> Maybe (NoBacktrace e) forall b c a. (b -> c) -> (a -> b) -> a -> c . SomeException -> Maybe e forall e. Exception e => SomeException -> Maybe e fromException toException :: NoBacktrace e -> SomeException toException (NoBacktrace e e) = e -> SomeException forall e. Exception e => e -> SomeException toException e e backtraceDesired :: NoBacktrace e -> Bool backtraceDesired NoBacktrace e _ = Bool False data ExceptionWithContext a = ExceptionWithContext ExceptionContext a instance Show a => Show (ExceptionWithContext a) where showsPrec :: Int -> ExceptionWithContext a -> ShowS showsPrec Int _ (ExceptionWithContext ExceptionContext _ a e) = String -> ShowS showString String "ExceptionWithContext _ " ShowS -> ShowS -> ShowS forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> ShowS forall a. Show a => a -> ShowS shows a e instance Exception a => Exception (ExceptionWithContext a) where toException :: ExceptionWithContext a -> SomeException toException (ExceptionWithContext ExceptionContext ctxt a e) = case a -> SomeException forall e. Exception e => e -> SomeException toException a e of SomeException e c -> let ?exceptionContext = HasExceptionContext ExceptionContext ctxt in e -> SomeException forall e. (Exception e, HasExceptionContext) => e -> SomeException SomeException e c fromException :: SomeException -> Maybe (ExceptionWithContext a) fromException SomeException se = do e <- SomeException -> Maybe a forall e. Exception e => SomeException -> Maybe e fromException SomeException se return (ExceptionWithContext (someExceptionContext se) e) backtraceDesired :: ExceptionWithContext a -> Bool backtraceDesired (ExceptionWithContext ExceptionContext _ a e) = a -> Bool forall e. Exception e => e -> Bool backtraceDesired a e displayException :: ExceptionWithContext a -> String displayException = SomeException -> String forall e. Exception e => e -> String displayException (SomeException -> String) -> (ExceptionWithContext a -> SomeException) -> ExceptionWithContext a -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . ExceptionWithContext a -> SomeException forall e. Exception e => e -> SomeException toException data ArithException = Overflow | Underflow | LossOfPrecision | DivideByZero | Denormal | RatioZeroDenominator deriving ( ArithException -> ArithException -> Bool (ArithException -> ArithException -> Bool) -> (ArithException -> ArithException -> Bool) -> Eq ArithException forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: ArithException -> ArithException -> Bool == :: ArithException -> ArithException -> Bool $c/= :: ArithException -> ArithException -> Bool /= :: ArithException -> ArithException -> Bool Eq , Eq ArithException Eq ArithException => (ArithException -> ArithException -> Ordering) -> (ArithException -> ArithException -> Bool) -> (ArithException -> ArithException -> Bool) -> (ArithException -> ArithException -> Bool) -> (ArithException -> ArithException -> Bool) -> (ArithException -> ArithException -> ArithException) -> (ArithException -> ArithException -> ArithException) -> Ord ArithException ArithException -> ArithException -> Bool ArithException -> ArithException -> Ordering ArithException -> ArithException -> ArithException forall a. Eq a => (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a $ccompare :: ArithException -> ArithException -> Ordering compare :: ArithException -> ArithException -> Ordering $c< :: ArithException -> ArithException -> Bool < :: ArithException -> ArithException -> Bool $c<= :: ArithException -> ArithException -> Bool <= :: ArithException -> ArithException -> Bool $c> :: ArithException -> ArithException -> Bool > :: ArithException -> ArithException -> Bool $c>= :: ArithException -> ArithException -> Bool >= :: ArithException -> ArithException -> Bool $cmax :: ArithException -> ArithException -> ArithException max :: ArithException -> ArithException -> ArithException $cmin :: ArithException -> ArithException -> ArithException min :: ArithException -> ArithException -> ArithException Ord ) divZeroException, overflowException, ratioZeroDenomException, underflowException :: SomeException divZeroException :: SomeException divZeroException = ArithException -> SomeException forall e. Exception e => e -> SomeException toException ArithException DivideByZero overflowException :: SomeException overflowException = ArithException -> SomeException forall e. Exception e => e -> SomeException toException ArithException Overflow ratioZeroDenomException :: SomeException ratioZeroDenomException = ArithException -> SomeException forall e. Exception e => e -> SomeException toException ArithException RatioZeroDenominator underflowException :: SomeException underflowException = ArithException -> SomeException forall e. Exception e => e -> SomeException 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"
RetroSearch is an open source project built by @garambo | Open a GitHub Issue
Search and Browse the WWW like it's 1997 | Search results from DuckDuckGo
HTML:
3.2
| Encoding:
UTF-8
| Version:
0.7.4