[Git][ghc/ghc][wip/romes/exceptions-layout] Display type and callstack of exception on handler
Rodrigo Mesquita (@alt-romes)
gitlab at gitlab.haskell.org
Tue Sep 24 10:29:41 UTC 2024
Rodrigo Mesquita pushed to branch wip/romes/exceptions-layout at Glasgow Haskell Compiler / GHC
Commits:
a971620c by Rodrigo Mesquita at 2024-09-24T11:28:50+01:00
Display type and callstack of exception on handler
This commit changes the Exception instance of SomeException to *simply*
display the underlying exception in `displayException`. The augmented
exception message that included the type and backtrace of the exception
are now only printed on a call to `displayExceptionWithInfo`.
At a surface level, existing programs should behave the same since the
`uncaughtExceptionHandler`, which is responsible for printing out uncaught
exceptions to the user, will use `displayExceptionWithInfo` by default.
However, unlike the instance's `displayException` method, the
`uncaughtExceptionHandler` can be overriden with
`setUncaughtExceptionHandler`. This makes the extra information opt-in
without fixing it the instance, which can be valuable if your program
wants to display uncaught exceptions to users in a user-facing way
(ie without backtraces).
This is what was originally agreed for CLC#231 or CLC#261 with regard to
the type of the exception information.
The call stack also becoming part of the default handler rather than the
Exception instance is an ammendment to CLC#164.
Discussion of the ammendment is part of CLC#285.
- - - - -
4 changed files:
- libraries/base/tests/T24807.stderr
- libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
Changes:
=====================================
libraries/base/tests/T24807.stderr
=====================================
@@ -1,11 +1,11 @@
-T24807: Exception:
+T24807: Uncaught exception ghc-internal:GHC.Internal.Exception.ErrorCall:
+
hi
CallStack (from HasCallStack):
error, called at T24807.hs:1:8 in main:Main
-Package: ghc-internal
-Module: GHC.Internal.Exception
-Type: ErrorCall
+
HasCallStack backtrace:
- collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:92:13 in ghc-internal:GHC.Internal.Exception
- toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:127:5 in ghc-internal:GHC.Internal.Exception
+ collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:93:13 in ghc-internal:GHC.Internal.Exception
+ toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:128:5 in ghc-internal:GHC.Internal.Exception
error, called at T24807.hs:1:8 in main:Main
+
=====================================
libraries/ghc-internal/src/GHC/Internal/Conc/Sync.hs
=====================================
@@ -952,7 +952,7 @@ uncaughtExceptionHandler = unsafePerformIO (newIORef defaultHandler)
defaultHandler se = do
(hFlush stdout) `catchAny` (\ _ -> return ())
- let exMsg = displayException se
+ let exMsg = displayExceptionWithInfo se
msg = "Uncaught exception " ++ exMsg
withCString "%s" $ \cfmt ->
withCString msg $ \cmsg ->
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception.hs
=====================================
@@ -35,6 +35,7 @@ module GHC.Internal.Exception
-- * 'SomeException'
, SomeException(..)
+ , displayExceptionWithInfo
-- * Exception context
, someExceptionContext
=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
=====================================
@@ -29,6 +29,7 @@
module GHC.Internal.Exception.Type
( Exception(..) -- Class
, SomeException(..)
+ , displayExceptionWithInfo
, someExceptionContext
, addExceptionContext
, mapExceptionContext
@@ -213,22 +214,35 @@ instance Exception SomeException where
in SomeException e
fromException = Just
backtraceDesired (SomeException e) = backtraceDesired e
- displayException (SomeException e) =
- case displayContext ?exceptionContext of
- "" -> msg
- dc -> msg ++ "\n\n" ++ dc
- where
- msg =
- displayExceptionInfo (Typeable.typeOf e)
- ++ "\n\n"
- ++ displayException e
-
- displayExceptionInfo :: TypeRep -> String
- displayExceptionInfo rep =
- tyMsg ++ ":"
- where
- tyMsg = Typeable.tyConPackage tyCon ++ ":" ++ Typeable.tyConModule tyCon ++ "." ++ Typeable.tyConName tyCon
- tyCon = Typeable.typeRepTyCon rep
+ displayException (SomeException e) = displayException e
+
+-- | Displays a 'SomeException' with additional information:
+--
+-- * The type of the underlying exception
+-- * The exception context
+--
+-- By default, 'uncaughtExceptionHandler' uses 'displayExceptionWithInfo' to print uncaught exceptions.
+-- This default can be overriden with 'setUncaughtExceptionHandler', for
+-- instance, to present custom error messages on exceptions to the user.
+--
+-- @since base-4.21
+displayExceptionWithInfo :: SomeException -> String
+displayExceptionWithInfo (SomeException e) =
+ case displayContext ?exceptionContext of
+ "" -> msg
+ dc -> msg ++ "\n\n" ++ dc
+ where
+ msg =
+ displayExceptionType (Typeable.typeOf e)
+ ++ "\n\n"
+ ++ displayException e
+
+ displayExceptionType :: TypeRep -> String
+ displayExceptionType rep =
+ tyMsg ++ ":"
+ where
+ tyMsg = Typeable.tyConPackage tyCon ++ ":" ++ Typeable.tyConModule tyCon ++ "." ++ Typeable.tyConName tyCon
+ tyCon = Typeable.typeRepTyCon rep
displayContext :: ExceptionContext -> String
displayContext (ExceptionContext anns0) = mconcat $ intersperse "\n" $ map go anns0
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a971620c7f026a0f97d883eafe9feae7be7246d6
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a971620c7f026a0f97d883eafe9feae7be7246d6
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240924/8afdffac/attachment-0001.html>
More information about the ghc-commits
mailing list