[Git][ghc/ghc][wip/romes/exceptions-propagate] 3 commits: Fix exception backtraces from GHCi

Rodrigo Mesquita (@alt-romes) gitlab at gitlab.haskell.org
Sat Nov 16 12:19:57 UTC 2024



Rodrigo Mesquita pushed to branch wip/romes/exceptions-propagate at Glasgow Haskell Compiler / GHC


Commits:
b8c08a73 by Rodrigo Mesquita at 2024-11-16T12:19:44+00:00
Fix exception backtraces from GHCi

When running the program with `runhaskell`/`runghc` the backtrace should
match the backtrace one would get by compiling and running the program.
But currently, an exception thrown in a program interpreted with
`runhaskell` will:

    * Not include the original exception backtrace at all
    * Include the backtrace from the internal GHCi/ghc rethrowing of the
      original exception

This commit fixes this divergence by not annotating the ghc(i) backtrace
(with NoBacktrace) and making sure that the backtrace of the original
exception is serialized across the boundary and rethrown with the
appropriate context.

Fixes #25116

The !13301 MR (not this commit in particular) improves performance of
MultiLayerModules. Unfortunately, T3294 regresses on aarch64-linux-deb12
by 1% allocations. Since this patch must be merged for 9.12 ASAP, we
will not be able to investigate the slight regression on this platform
in time.

-------------------------
Metric Decrease:
    MultiLayerModulesRecomp
    MultiLayerModulesTH_OneShot
Metric Increase:
    T3294
-------------------------

- - - - -
6d1bf2e8 by Rodrigo Mesquita at 2024-11-16T12:19:45+00:00
base: Add to changelog.md CLC #285

- - - - -
7fb837de by Rodrigo Mesquita at 2024-11-16T12:19:45+00:00
Bump array and stm submodules for testsuite

The testsuites of array and stm had to be updated according to !13301.

Updates submodule array and stm.

- - - - -


18 changed files:

- ghc/GHCi/UI/Monad.hs
- libraries/array
- libraries/base/changelog.md
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/stm
- testsuite/tests/ghc-e/should_run/ghc-e005.stderr
- testsuite/tests/ghci.debugger/scripts/break009.stdout
- testsuite/tests/ghci.debugger/scripts/break011.stdout
- testsuite/tests/ghci.debugger/scripts/break017.stdout
- testsuite/tests/ghci.debugger/scripts/break024.stdout
- testsuite/tests/ghci/scripts/Defer02.stderr
- testsuite/tests/ghci/scripts/T10501.stderr
- testsuite/tests/ghci/scripts/T15325.stderr
- testsuite/tests/ghci/scripts/T5557.stdout
- testsuite/tests/ghci/scripts/ghci055.stdout
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/patsyn/should_run/ghci.stderr


Changes:

=====================================
ghc/GHCi/UI/Monad.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE FlexibleInstances, DeriveFunctor, DerivingVia #-}
+{-# LANGUAGE FlexibleInstances, DeriveFunctor, DerivingVia, CPP #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
 -----------------------------------------------------------------------------
@@ -212,7 +212,14 @@ data CommandResult
    deriving Show
 
 cmdSuccess :: MonadThrow m => CommandResult -> m (Maybe Bool)
-cmdSuccess CommandComplete{ cmdResult = Left e } = throwM e
+cmdSuccess CommandComplete{ cmdResult = Left e } =
+  {- Don't add a backtrace from ghci/ghc to the exception from the user program! -}
+#if MIN_VERSION_base(4,21,0)
+  throwM (NoBacktrace e)
+#else
+  -- NoBacktrace is not available in older compilers
+  throwM e
+#endif
 cmdSuccess CommandComplete{ cmdResult = Right r } = return r
 cmdSuccess CommandIncomplete = return $ Just True
 


=====================================
libraries/array
=====================================
@@ -1 +1 @@
-Subproject commit c9cb2c1e8762aa83b6e77af82c87a55e03e990e4
+Subproject commit 18dd1439815e43c3e8142cca7b4735c8ad9850ab


=====================================
libraries/base/changelog.md
=====================================
@@ -39,6 +39,17 @@
       `onException`, such as `base`, or the `exceptions` package.
   * Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
   * Make `Debug.Trace.{traceEventIO,traceMarkerIO}` faster when tracing is disabled. See [CLC proposal #291](https://github.com/haskell/core-libraries-committee/issues/291).
+  * The exception messages were improved according to [CLC proposal #285](https://github.com/haskell/core-libraries-committee/issues/285). In particular:
+      * Improve the message of the uncaught exception handler
+      * Make `displayException (SomeException e) = displayException e`. The
+          additional information that is printed when exceptions are surfaced to
+          the top-level is added by `uncaughtExceptionHandler`.
+      * Get rid of the HasCallStack mechanism manually propagated by `ErrorCall`
+          in favour of the more general HasCallStack exception backtrace
+          mechanism, to remove duplicate call stacks for uncaught exceptions.
+      * Freeze the callstack of `error`, `undefined`, `throwIO`, `ioException`,
+          `ioError` to prevent leaking the implementation of these error functions
+          into the callstack.
 
 ## 4.20.0.0 May 2024
   * Shipped with GHC 9.10.1


=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -1,6 +1,6 @@
 {-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, ScopedTypeVariables,
-    GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards
-    #-}
+    GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards,
+    CPP #-}
 {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-}
 
 -- |
@@ -40,6 +40,9 @@ import GHC.Fingerprint
 import GHC.Conc (pseq, par)
 import Control.Concurrent
 import Control.Exception
+#if MIN_VERSION_base(4,20,0)
+import Control.Exception.Context
+#endif
 import Data.Binary
 import Data.Binary.Get
 import Data.Binary.Put
@@ -442,7 +445,15 @@ toSerializableException :: SomeException -> SerializableException
 toSerializableException ex
   | Just UserInterrupt <- fromException ex  = EUserInterrupt
   | Just (ec::ExitCode) <- fromException ex = (EExitCode ec)
-  | otherwise = EOtherException (show (ex :: SomeException))
+  | otherwise = EOtherException $
+#if MIN_VERSION_base(4,20,0)
+      -- Exception plus backtrace as seen in `displayExceptionWithInfo`
+      case displayExceptionContext (someExceptionContext ex) of
+        "" -> displayException (ex :: SomeException)
+        cx -> displayException (ex :: SomeException) ++ "\n\n" ++ cx
+#else
+      show (ex :: SomeException)
+#endif
 
 fromSerializableException :: SerializableException -> SomeException
 fromSerializableException EUserInterrupt = toException UserInterrupt


=====================================
libraries/ghci/GHCi/Run.hs
=====================================
@@ -252,7 +252,7 @@ sandboxIO opts io = do
 --
 rethrow :: EvalOpts -> IO a -> IO a
 rethrow EvalOpts{..} io =
-  catch io $ \se -> do
+  catchNoPropagate io $ \(ExceptionWithContext cx se) -> do
     -- If -fbreak-on-error, we break unconditionally,
     --  but with care of not breaking twice
     if breakOnError && not breakOnException
@@ -263,7 +263,7 @@ rethrow EvalOpts{..} io =
                Just UserInterrupt -> return ()
                -- In any other case, we don't want to break
                _ -> poke exceptionFlag 0
-    throwIO se
+    rethrowIO (ExceptionWithContext cx se)
 
 --
 -- While we're waiting for the sandbox thread to return a result, if


=====================================
libraries/stm
=====================================
@@ -1 +1 @@
-Subproject commit cb861ea10065f229bbc5b6a1e2b9bde998f18184
+Subproject commit 07df1050ab5d45244f718eee8a512bb18e7066f6


=====================================
testsuite/tests/ghc-e/should_run/ghc-e005.stderr
=====================================
@@ -2,17 +2,21 @@ ghc-e005-prog: Uncaught exception ghc-internal:GHC.Internal.Exception.ErrorCall:
 
 foo
 
+HasCallStack backtrace:
+  error, called at ghc-e005.hs:12:10 in main:Main
+
+
 HasCallStack backtrace:
   throwIO, called at libraries/exceptions/src/Control/Monad/Catch.hs:371:12 in exceptions-0.10.7-inplace:Control.Monad.Catch
   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
   throwM, called at compiler/GHC/Driver/Monad.hs:167:54 in ghc-9.13-inplace:GHC.Driver.Monad
   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
-  throwM, called at ghc/GHCi/UI/Monad.hs:288:15 in ghc-bin-9.13.20240930-inplace:GHCi.UI.Monad
+  throwM, called at ghc/GHCi/UI/Monad.hs:295:15 in ghc-bin-9.13.20241115-inplace:GHCi.UI.Monad
   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
   throwM, called at libraries/exceptions/src/Control/Monad/Catch.hs:490:21 in exceptions-0.10.7-inplace:Control.Monad.Catch
   throwM, called at libraries/haskeline/System/Console/Haskeline/InputT.hs:53:39 in haskeline-0.8.2.1-inplace:System.Console.Haskeline.InputT
-  throwM, called at ghc/GHCi/UI/Monad.hs:215:52 in ghc-bin-9.13.20240930-inplace:GHCi.UI.Monad
+  throwM, called at ghc/GHCi/UI/Monad.hs:221:3 in ghc-bin-9.13.20241115-inplace:GHCi.UI.Monad
 


=====================================
testsuite/tests/ghci.debugger/scripts/break009.stdout
=====================================
@@ -2,3 +2,10 @@ Breakpoint 0 activated at Test6.hs:5:8-11
 Stopped in Main.main, Test6.hs:5:8-11
 _result :: a = _
 *** Exception: Prelude.head: empty list
+
+HasCallStack backtrace:
+  error, called at libraries/ghc-internal/src/GHC/Internal/List.hs:2036:3 in ghc-internal:GHC.Internal.List
+  errorEmptyList, called at libraries/ghc-internal/src/GHC/Internal/List.hs:96:11 in ghc-internal:GHC.Internal.List
+  badHead, called at libraries/ghc-internal/src/GHC/Internal/List.hs:90:28 in ghc-internal:GHC.Internal.List
+  head, called at Test6.hs:1:8 in main:Main
+


=====================================
testsuite/tests/ghci.debugger/scripts/break011.stdout
=====================================
@@ -1,4 +1,8 @@
 *** Exception: foo
+
+HasCallStack backtrace:
+  error, called at <interactive>:2:1 in interactive:Ghci1
+
 Stopped in <exception thrown>, <unknown>
 _exception :: e = _
 Stopped in <exception thrown>, <unknown>
@@ -20,8 +24,16 @@ _exception = SomeException (ErrorCall "foo")
 _result :: a = _
 _exception :: SomeException = SomeException (ErrorCall "foo")
 *** Exception: foo
+
+HasCallStack backtrace:
+  error, called at Test7.hs:2:18 in main:Main
+
 Stopped in <exception thrown>, <unknown>
 _exception :: e = _
 Stopped in <exception thrown>, <unknown>
 _exception :: e = _
 *** Exception: foo
+
+HasCallStack backtrace:
+  error, called at Test7.hs:2:18 in main:Main
+


=====================================
testsuite/tests/ghci.debugger/scripts/break017.stdout
=====================================
@@ -11,5 +11,9 @@ Printing 1
 as = 'b' : 'c' : (_t1::[Char])
 Forcing
 *** Exception: Prelude.undefined
+
+HasCallStack backtrace:
+  undefined, called at <interactive>:3:17 in interactive:Ghci1
+
 Printing 2
 as = 'b' : 'c' : (_t2::[Char])


=====================================
testsuite/tests/ghci.debugger/scripts/break024.stdout
=====================================
@@ -6,6 +6,10 @@ _exception = SomeException
                   Nothing GHC.Internal.IO.Exception.UserError [] "error" Nothing
                   Nothing)
 *** Exception: user error (error)
+
+HasCallStack backtrace:
+  ioError, called at break024.hs:3:22 in main:Main
+
 Stopped in <exception thrown>, <unknown>
 _exception :: e = _
 _exception = SomeException


=====================================
testsuite/tests/ghci/scripts/Defer02.stderr
=====================================
@@ -1,4 +1,3 @@
-
 Defer01.hs:10:40: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
     • Couldn't match type ‘Char’ with ‘[Char]’
       Expected: String
@@ -61,6 +60,7 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
       In the first argument of ‘(>>)’, namely ‘putChar’
       In the expression: putChar >> putChar 'p'
       In an equation for ‘l’: l = putChar >> putChar 'p'
+
 *** Exception: Defer01.hs:10:40: error: [GHC-83865]
     • Couldn't match type ‘Char’ with ‘[Char]’
       Expected: String
@@ -69,17 +69,34 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
       In the second argument of ‘(>>)’, namely ‘putStr ','’
       In the expression: putStr "Hello World" >> putStr ','
 (deferred type error)
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+
 *** Exception: Defer01.hs:13:5: error: [GHC-83865]
     • Couldn't match expected type ‘Int’ with actual type ‘Char’
     • In the expression: 'p'
       In an equation for ‘a’: a = 'p'
 (deferred type error)
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+
 *** Exception: Defer01.hs:17:9: error: [GHC-39999]
     • No instance for ‘Eq B’ arising from a use of ‘==’
     • In the expression: x == x
       In an equation for ‘b’: b x = x == x
 (deferred type error)
 
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+
 <interactive>:10:11: error: [GHC-83865]
     • Couldn't match type ‘Bool’ with ‘Int’
       Expected: C Int
@@ -87,12 +104,19 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
     • In the first argument of ‘c’, namely ‘(C2 True)’
       In the first argument of ‘print’, namely ‘(c (C2 True))’
       In the expression: print (c (C2 True))
+
 *** Exception: Defer01.hs:27:5: error: [GHC-39999]
     • No instance for ‘Num (a -> a)’ arising from the literal ‘1’
         (maybe you haven't applied a function to enough arguments?)
     • In the expression: 1
       In an equation for ‘d’: d = 1
 (deferred type error)
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+
 *** Exception: Defer01.hs:30:5: error: [GHC-83865]
     • Couldn't match expected type ‘Char -> t’ with actual type ‘Char’
     • The function ‘e’ is applied to one visible argument,
@@ -101,6 +125,12 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
       In an equation for ‘f’: f = e 'q'
     • Relevant bindings include f :: t (bound at Defer01.hs:30:1)
 (deferred type error)
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+
 *** Exception: Defer01.hs:33:8: error: [GHC-25897]
     • Couldn't match expected type ‘Char’ with actual type ‘a’
       ‘a’ is a rigid type variable bound by
@@ -114,6 +144,12 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
         x :: a (bound at Defer01.hs:33:3)
         h :: a -> (Char, Char) (bound at Defer01.hs:33:1)
 (deferred type error)
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+
 *** Exception: Defer01.hs:38:17: error: [GHC-83865]
     • Couldn't match expected type ‘Bool’ with actual type ‘T a’
     • In the first argument of ‘not’, namely ‘(K a)’
@@ -123,17 +159,29 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
         a :: a (bound at Defer01.hs:38:3)
         i :: a -> () (bound at Defer01.hs:38:1)
 (deferred type error)
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+
 *** Exception: Defer01.hs:42:5: error: [GHC-39999]
     • No instance for ‘MyClass a1’ arising from a use of ‘myOp’
     • In the expression: myOp 23
       In an equation for ‘j’: j = myOp 23
 (deferred type error)
 
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+
 <interactive>:16:8: error: [GHC-18872]
     • Couldn't match type ‘Int’ with ‘Bool’ arising from a use of ‘k’
     • In the first argument of ‘print’, namely ‘(k 2)’
       In the expression: print (k 2)
       In an equation for ‘it’: it = print (k 2)
+
 *** Exception: Defer01.hs:49:5: error: [GHC-83865]
     • Couldn't match expected type: IO a0
                   with actual type: Char -> IO ()
@@ -142,3 +190,9 @@ Defer01.hs:49:5: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
       In the expression: putChar >> putChar 'p'
       In an equation for ‘l’: l = putChar >> putChar 'p'
 (deferred type error)
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+


=====================================
testsuite/tests/ghci/scripts/T10501.stderr
=====================================
@@ -1,2 +1,13 @@
 *** Exception: Prelude.head: empty list
+
+HasCallStack backtrace:
+  error, called at libraries/ghc-internal/src/GHC/Internal/List.hs:2036:3 in ghc-internal:GHC.Internal.List
+  errorEmptyList, called at libraries/ghc-internal/src/GHC/Internal/List.hs:96:11 in ghc-internal:GHC.Internal.List
+  badHead, called at libraries/ghc-internal/src/GHC/Internal/List.hs:90:28 in ghc-internal:GHC.Internal.List
+  head, called at <interactive>:1:10 in interactive:Ghci1
+
 *** Exception: Prelude.undefined
+
+HasCallStack backtrace:
+  undefined, called at <interactive>:1:17 in interactive:Ghci1
+


=====================================
testsuite/tests/ghci/scripts/T15325.stderr
=====================================
@@ -1,4 +1,3 @@
-
 T15325.hs:11:7: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
     • No instance for ‘PolyList e0’ arising from a use of ‘f’
     • In the expression: f 0
@@ -17,8 +16,15 @@ T15325.hs:11:9: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
     • In the first argument of ‘f’, namely ‘0’
       In the expression: f 0
       In an equation for ‘plh’: plh = f 0
+
 *** Exception: T15325.hs:11:7: error: [GHC-39999]
     • No instance for ‘PolyList e0’ arising from a use of ‘f’
     • In the expression: f 0
       In an equation for ‘plh’: plh = f 0
 (deferred type error)
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:435:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+


=====================================
testsuite/tests/ghci/scripts/T5557.stdout
=====================================
@@ -1,2 +1,10 @@
 *** Exception: Prelude.undefined
+
+HasCallStack backtrace:
+  undefined, called at <interactive>:2:12 in interactive:Ghci1
+
 *** Exception: Prelude.undefined
+
+HasCallStack backtrace:
+  undefined, called at <interactive>:3:12 in interactive:Ghci1
+


=====================================
testsuite/tests/ghci/scripts/ghci055.stdout
=====================================
@@ -1,3 +1,7 @@
 *** Exception: Prelude.undefined
+
+HasCallStack backtrace:
+  undefined, called at <interactive>:1:7 in interactive:Ghci1
+
 x :: a = _
 y :: Int = 3


=====================================
testsuite/tests/interface-stability/base-exports.stdout
=====================================
@@ -249,6 +249,8 @@ module Control.Exception where
   data MaskingState = Unmasked | MaskedInterruptible | MaskedUninterruptible
   type NestedAtomically :: *
   data NestedAtomically = NestedAtomically
+  type NoBacktrace :: * -> *
+  newtype NoBacktrace e = NoBacktrace e
   type NoMethodError :: *
   newtype NoMethodError = NoMethodError GHC.Internal.Base.String
   type NonTermination :: *


=====================================
testsuite/tests/patsyn/should_run/ghci.stderr
=====================================
@@ -1,2 +1,8 @@
 *** Exception: <interactive>:5:5-35: Non-exhaustive patterns in function foo
 
+
+HasCallStack backtrace:
+  collectBacktraces, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:168:13 in ghc-internal:GHC.Internal.Exception
+  toExceptionWithBacktrace, called at libraries/ghc-internal/src/GHC/Internal/Exception.hs:88:42 in ghc-internal:GHC.Internal.Exception
+  throw, called at libraries/ghc-internal/src/GHC/Internal/Control/Exception/Base.hs:434:30 in ghc-internal:GHC.Internal.Control.Exception.Base
+



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/27e03dfd2f6c5c9442a1518ce8c1ed1a78daa833...7fb837dea74ce699bc71f3a152699d18ab80bd4e

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/27e03dfd2f6c5c9442a1518ce8c1ed1a78daa833...7fb837dea74ce699bc71f3a152699d18ab80bd4e
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/20241116/09df19e0/attachment-0001.html>


More information about the ghc-commits mailing list