[Git][ghc/ghc][wip/T25066] 2 commits: base: Fix #25066

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Tue Sep 24 20:23:33 UTC 2024



Ben Gamari pushed to branch wip/T25066 at Glasgow Haskell Compiler / GHC


Commits:
10a1a6df by Ben Gamari at 2024-09-24T12:43:53-04:00
base: Fix #25066

As noted in #25066, the exception backtrace proposal introduced a rather
subtle performance regression due to simplification producing Core which
the demand analyser concludes may diverge with a precise exception. The
nature of the problem is more completely described in the new Note
[Hiding precise exception signature in throw].

The (rather hacky) solution we use here hides the problematic
optimisation through judicious use of `noinline`. Ultimately however we
will want a more principled solution (e.g. #23847).

- - - - -
208d8a8c by Ben Gamari at 2024-09-24T12:43:53-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -


4 changed files:

- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/tests/T25066.stderr
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs


Changes:

=====================================
libraries/base/src/Control/Exception/Backtrace.hs
=====================================
@@ -7,8 +7,43 @@
 -- Stability   :  internal
 -- Portability :  non-portable (GHC Extensions)
 --
--- Mechanisms for collecting diagnostic backtraces and their representation.
+-- This module provides the 'Backtrace'\ s type, which provides a
+-- common representation for backtrace information which can be, e.g., attached
+-- to exceptions (via the 'Control.Exception.Context.ExceptionContext' facility).
+-- These backtraces preserve useful context about the execution state of the program
+-- using a variety of means; we call these means *backtrace mechanisms*.
 --
+-- We currently support four backtrace mechanisms:
+--
+--  - 'CostCentreBacktrace' captures the current cost-centre stack
+--    using 'GHC.Stack.CCS.getCurrentCCS'.
+--  - 'HasCallStackBacktrace' captures the 'HasCallStack' 'CallStack'.
+--  - 'ExecutionBacktrace' captures the execution stack, unwound and resolved
+--    to symbols via DWARF debug information.
+--  - 'IPEBacktrace' captures the execution stack, resolved to names via info-table
+--    provenance information.
+--
+-- Each of these are useful in different situations. While 'CostCentreBacktrace's are
+-- readily mapped back to the source program, they require that the program be instrumented
+-- with cost-centres, incurring runtime cost. Similarly, 'HasCallStackBacktrace's require that
+-- the program be manually annotated with 'HasCallStack' constraints.
+--
+-- By contrast, 'IPEBacktrace's incur no runtime instrumentation but require that (at least
+-- some subset of) the program be built with GHC\'s @-finfo-table-map@ flag. Moreover, because
+-- info-table provenance information is derived after optimisation, it may be harder to relate
+-- back to the structure of the source program.
+--
+-- 'ExecutionBacktrace's are similar to 'IPEBacktrace's but use DWARF stack unwinding
+-- and symbol resolution; this allows for useful backtraces even in the presence
+-- of foreign calls, both into and out of Haskell. However, for robust stack unwinding
+-- the entirety of the program (and its dependencies, both Haskell and native) must
+-- be compiled with debugging information (e.g. using GHC\'s @-g@ flag).
+
+
+-- Note [Backtrace mechanisms]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- See module docstring above.
+
 
 module Control.Exception.Backtrace
     ( -- * Backtrace mechanisms


=====================================
libraries/base/tests/T25066.stderr
=====================================
@@ -5,7 +5,7 @@ T25066.$fShowMyException:
 T25066.$tc'MyException:
 T25066.$tcMyException:
 T25066.$trModule:
-T25066.g: x
+T25066.g: b
 
 
 
@@ -15,6 +15,6 @@ T25066.$fShowMyException:
 T25066.$tc'MyException:
 T25066.$tcMyException:
 T25066.$trModule:
-T25066.g: x
+T25066.g: b
 
 


=====================================
libraries/ghc-internal/src/GHC/Internal/Exception.hs
=====================================
@@ -81,9 +81,86 @@ import GHC.Internal.Exception.Type
 throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e.
          (HasCallStack, Exception e) => e -> a
 throw e =
-    let !se = unsafePerformIO (toExceptionWithBacktrace e)
+    -- Note the absolutely crucial bang "!" on this binding!
+    --   See Note [Capturing the backtrace in throw]
+    -- Note also the absolutely crucial `noinine` in the RHS!
+    --   See Note [Hiding precise exception signature in throw]
+    let se :: SomeException
+        !se = noinline (unsafePerformIO (toExceptionWithBacktrace e))
     in raise# se
 
+-- Note [Capturing the backtrace in throw]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- When `throw` captures a backtrace, it must be the backtrace *at the moment
+-- that `throw` is called*.   That is why the binding of `se` is marked strict,
+-- via the `!`:
+--
+--     !se = <rhs>
+--
+-- GHC can capture /four/ different sorts of backtraces (See Note [Backtrace
+-- mechanisms] in "Control.Exception.Backtrace" for details). One of them
+-- (`CallStack` constraints) does not need this strict-binding treatment,
+-- because the `CallStack` constraint is captured in the thunk. However, the
+-- other two (DWARF stack unwinding, and native Haskell stack unwinding) are
+-- much more fragile, and can only be captured right at the call of `throw`.
+--
+-- However, making `se` strict has downsides: see
+-- Note [Hiding precise exception signature in throw] below.
+--
+--
+-- Note [Hiding precise exception signature in throw]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- In 'throw' we use `unsafePerformIO . toExceptionWithBacktrace' to collect
+-- the backtraces which will be attached as the exception's 'ExceptionContext'.
+-- We must ensure that this is evaluated immediately in `throw` since
+-- `toExceptionWithBacktrace` must capture the execution state at the moment
+-- that the exception is thrown (see Note [Capturing the backtrace in throw]).
+-- Unfortunately, unless we take particular care this can lead to a
+-- catastrophic regression in 'throw's demand signature which will infect
+-- all callers (#25066)
+--
+-- Specifically, GHC's demand analysis has an approximate heuristic for tracking
+-- whether divergent functions diverge with precise or imprecise exceptions (namely
+-- the 'ExnOrDiv' and 'Diverges' constructors of 'GHC.Types.Demand.Divergence',
+-- respectively). This is because we can take considerably more liberties in
+-- optimising around functions which are known not to diverge via precise
+-- exception (see Note [Precise exceptions and strictness analysis]).
+-- For this reason, it is important that 'throw' have a 'Diverges' divergence
+-- type.
+--
+-- Unfortunately, this is broken if we allow `unsafePerformIO` to inline. Specifically,
+-- if we allow this inlining we will end up with Core of the form:
+--
+--   throw = \e ->
+--     case runRW# (\s -> ... toExceptionWithBacktrace e s ...) of
+--       se -> raise# se
+--
+-- so far this is fine; the demand analyzer's divergence heuristic
+-- will give 'throw' the expected 'Diverges' divergence.
+--
+-- However, the simplifier will subsequently notice that `raise#` can be fruitfully
+-- floated into the body of the `runRW#`:
+--
+--   throw = \e ->
+--     runRW# (\s -> case toExceptionWithBacktrace e s of
+--                     (# s', se #) -> raise# se)
+--
+-- This is problematic as one of the demand analyser's heuristics examines
+-- `case` scrutinees, looking for those that result in a `RealWorld#` token
+-- (see Note [Which scrutinees may throw precise exceptions], test (1)). The
+-- `case toExceptionWithBacktrace e of ...` here fails this check, causing the
+-- heuristic to conclude that `throw` may indeed diverge with a precise
+-- exception. This resulted in the significant performance regression noted in
+-- #25066.
+--
+-- To avoid this, we use `noinline` to ensure that `unsafePerformIO` does not unfold,
+-- meaning that the `raise#` cannot be floated under the `toExceptionWithBacktrace`
+-- case analysis.
+--
+-- Ultimately this is a bit of a horrible hack; the right solution would be to have
+-- primops which allow more precise guidance of the demand analyser's heuristic
+-- (e.g. #23847).
+
 -- | @since base-4.20.0.0
 toExceptionWithBacktrace :: (HasCallStack, Exception e)
                          => e -> IO SomeException


=====================================
libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
=====================================
@@ -33,7 +33,7 @@ data BacktraceMechanism
   = CostCentreBacktrace
   -- | collect 'HasCallStack' backtraces
   | HasCallStackBacktrace
-  -- | collect backtraces from native execution stack unwinding
+  -- | collect backtraces via native execution stack unwinding (e.g. using DWARF debug information)
   | ExecutionBacktrace
   -- | collect backtraces from Info Table Provenance Entries
   | IPEBacktrace



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8945337e0d4c400040c3257cfc4a70889c7b05a5...208d8a8c192a55a3884c4f210da20a1c0cea3448

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8945337e0d4c400040c3257cfc4a70889c7b05a5...208d8a8c192a55a3884c4f210da20a1c0cea3448
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/7835e67e/attachment-0001.html>


More information about the ghc-commits mailing list