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

Ben Gamari (@bgamari) gitlab at gitlab.haskell.org
Thu Sep 19 23:19:31 UTC 2024



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


Commits:
440d9c60 by Ben Gamari at 2024-09-19T19:19:24-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).

- - - - -


2 changed files:

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


Changes:

=====================================
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,61 @@ 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)
+    -- See Note [Hiding precise exception signature in throw]
+    let !se = noinline (unsafePerformIO (toExceptionWithBacktrace e))
     in raise# se
 
+-- 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. 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 the `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 ...` case 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



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/440d9c6077b56858d4f3637d6c9480bbb7d2ff3d

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/440d9c6077b56858d4f3637d6c9480bbb7d2ff3d
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/20240919/dcb10d49/attachment-0001.html>


More information about the ghc-commits mailing list