[Git][ghc/ghc][master] 4 commits: testsuite: Normalise trailing digits from hole fits output

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Sat Oct 12 03:43:47 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
d029f170 by Ben Gamari at 2024-10-11T23:43:17-04:00
testsuite: Normalise trailing digits from hole fits output

The type variables in the holes fit output from
`abstract_refinement_hole_fits` is quite sensitive to compiler
configuration. Specifically, a slight change in the inlining
behavior of `throw` changes type variable naming in `(>>=)` and a few
others.

Ideally we would make hole fits output more deterministic but in the
meantime we simply normalise this difference away as it not relevant
to the test's goal.

- - - - -
da5d7d0d by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Add test for #25066

- - - - -
eb7ddae1 by Ben Gamari at 2024-10-11T23:43:17-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).

Fixes #255066

CLC proposal: https://github.com/haskell/core-libraries-committee/issues/290

Metric Decrease:
    T9872d

- - - - -
0060ece7 by Ben Gamari at 2024-10-11T23:43:17-04:00
base: Improve documentation of Control.Exception.Backtrace

- - - - -


8 changed files:

- libraries/base/changelog.md
- libraries/base/src/Control/Exception/Backtrace.hs
- + libraries/base/tests/T25066.hs
- + libraries/base/tests/T25066.stderr
- libraries/base/tests/all.T
- libraries/ghc-internal/src/GHC/Internal/Exception.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- testsuite/tests/typecheck/should_compile/all.T


Changes:

=====================================
libraries/base/changelog.md
=====================================
@@ -2,6 +2,8 @@
 
 ## 4.22.0.0 *TBA*
   * Restrict `Data.List.NonEmpty.unzip` to `NonEmpty (a, b) -> (NonEmpty a, NonEmpty b)`. ([CLC proposal #86](https://github.com/haskell/core-libraries-committee/issues/86))
+  * Modify the implementation of `Control.Exception.throw` to avoid call-sites being inferred as diverging via precise exception.
+    ([GHC #25066](https://gitlab.haskell.org/ghc/ghc/-/issues/25066), [CLC proposal #290](https://github.com/haskell/core-libraries-committee/issues/290))
 
 ## 4.21.0.0 *TBA*
   * `GHC.Desugar` has been deprecated and should be removed in GHC 9.14. ([CLC proposal #216](https://github.com/haskell/core-libraries-committee/issues/216))


=====================================
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.hs
=====================================
@@ -0,0 +1,15 @@
+-- | Check that the demand signature of 'throw' doesn't suggest that it will
+-- throw a precise exception. Specifically, `g` should have a `b` divergence
+-- type in its demand signature.
+
+module T25066 (g) where
+
+import Control.Exception
+
+data MyException = MyException
+  deriving (Show)
+
+instance Exception MyException
+
+g :: a
+g = throw MyException


=====================================
libraries/base/tests/T25066.stderr
=====================================
@@ -0,0 +1,20 @@
+
+==================== Demand signatures ====================
+T25066.$fExceptionMyException:
+T25066.$fShowMyException:
+T25066.$tc'MyException:
+T25066.$tcMyException:
+T25066.$trModule:
+T25066.g: b
+
+
+
+==================== Demand signatures ====================
+T25066.$fExceptionMyException:
+T25066.$fShowMyException:
+T25066.$tc'MyException:
+T25066.$tcMyException:
+T25066.$trModule:
+T25066.g: b
+
+


=====================================
libraries/base/tests/all.T
=====================================
@@ -325,3 +325,4 @@ test('T23697',
   ], makefile_test, ['T23697'])
 test('stimesEndo', normal, compile_and_run, [''])
 test('T24807', exit_code(1), compile_and_run, [''])
+test('T25066', [only_ways(['optasm']), grep_errmsg('T25066.g')], compile, ['-ddump-dmd-signatures'])


=====================================
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


=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -1,8 +1,17 @@
+import re
+
 # Args to vtc are: extra compile flags
 
 def f( name, opts ):
   opts.extra_hc_opts = '-fno-warn-incomplete-patterns'
 
+def normalise_type_vars(s):
+  """
+  Normalise away the trailing digits from type variable OccNames
+  in hole fits error messages as these tend to be non-deterministic.
+  """
+  return re.sub(r'([a-z])[0-9]+', r'\1', s)
+
 setTestOpts(f)
 
 test('tc001', normal, compile, [''])
@@ -392,7 +401,7 @@ test('local_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-ho
 test('subsumption_sort_hole_fits', normalise_version('ghc-internal', 'base'), compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fsort-by-subsumption-hole-fits'])
 test('valid_hole_fits_interactions', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits'])
 test('refinement_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2'])
-test('abstract_refinement_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2 -fabstract-refinement-hole-fits -funclutter-valid-hole-fits'])
+test('abstract_refinement_hole_fits', normalise_errmsg_fun(normalise_type_vars), compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2 -fabstract-refinement-hole-fits -funclutter-valid-hole-fits'])
 test('free_monad_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2 -funclutter-valid-hole-fits'])
 test('constraint_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits -fno-max-refinement-hole-fits -frefinement-level-hole-fits=2 -funclutter-valid-hole-fits'])
 test('type_in_type_hole_fits', normal, compile, ['-fdefer-type-errors -fno-max-valid-hole-fits'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8584504b68418eaa12f1332a22ccb7d354aacc00...0060ece762d7a936daf28195676b6162c30dc845

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8584504b68418eaa12f1332a22ccb7d354aacc00...0060ece762d7a936daf28195676b6162c30dc845
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/20241011/de787e2f/attachment-0001.html>


More information about the ghc-commits mailing list