[Git][ghc/ghc][wip/ghc-8.8-merges] 6 commits: Fix typo in 8.8.1 notes related to traceBinaryEvent

Ben Gamari gitlab at gitlab.haskell.org
Sun Jun 16 13:11:30 UTC 2019



Ben Gamari pushed to branch wip/ghc-8.8-merges at Glasgow Haskell Compiler / GHC


Commits:
ed342f36 by iustin at 2019-06-15T18:47:50Z
Fix typo in 8.8.1 notes related to traceBinaryEvent

- fixes double mention of `traceBinaryEvent#` (the second one should be `traceEvent#`, I think)
- fixes note about `traceEvent#` taking a `String` - the docs say it takes a zero-terminated ByteString.

(cherry picked from commit 63150b9e5583c5fc3252f242981b0d26f11348b2)

- - - - -
4b40bad6 by Ben Gamari at 2019-06-15T18:55:05Z
users-guide: More release notes

- - - - -
fee015b5 by Ben Gamari at 2019-06-15T19:39:03Z
PrelRules: Don't break let/app invariant in shiftRule

Previously shiftRule would rewrite as invalid shift like
```
let x = I# (uncheckedIShiftL# n 80)
in ...
```
to
```
let x = I# (error "invalid shift")
in ...
```
However, this breaks the let/app invariant as `error` is not
okay-for-speculation. There isn't an easy way to avoid this so let's not
try. Instead we just take advantage of the undefined nature of invalid
shifts and return zero.

Fixes #16742.

(cherry picked from commit 0bd3b9dd0428855b6f72f757c1214b5253aa7753)

- - - - -
7fe79797 by Ben Gamari at 2019-06-16T13:10:32Z
testsuite: Skip PartialDownsweep

This gives different results on different platforms

- - - - -
2c08ff3f by Ben Gamari at 2019-06-16T13:11:25Z
ErrUtils: Emit progress messages to eventlog

(cherry picked from commit 1bef62c38d3737b5f5d7ebbb479f3c1a12b1aa09)

- - - - -
4c5899e6 by Ben Gamari at 2019-06-16T13:11:25Z
Emit GHC timing events to eventlog

(cherry picked from commit ebfa35284741fca47719f531f0996261441f75b0)

- - - - -


10 changed files:

- compiler/coreSyn/CoreSyn.hs
- compiler/main/ErrUtils.hs
- compiler/prelude/PrelRules.hs
- compiler/prelude/PrimOp.hs
- docs/users_guide/8.8.1-notes.rst
- testsuite/tests/codeGen/should_run/T16449_2.hs
- − testsuite/tests/codeGen/should_run/T16449_2.stderr
- + testsuite/tests/codeGen/should_run/T16449_2.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/ghc-api/downsweep/all.T


Changes:

=====================================
compiler/coreSyn/CoreSyn.hs
=====================================
@@ -445,6 +445,9 @@ which will generate a @case@ if necessary
 The let/app invariant is initially enforced by mkCoreLet and mkCoreApp in
 coreSyn/MkCore.
 
+For discussion of some implications of the let/app invariant primops see
+Note [Checking versus non-checking primops] in PrimOp.
+
 Note [CoreSyn type and coercion invariant]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 We allow a /non-recursive/, /non-top-level/ let to bind type and


=====================================
compiler/main/ErrUtils.hs
=====================================
@@ -80,6 +80,7 @@ import Data.IORef
 import Data.Maybe       ( fromMaybe )
 import Data.Ord
 import Data.Time
+import Debug.Trace
 import Control.Monad
 import Control.Monad.IO.Class
 import System.IO
@@ -598,9 +599,10 @@ fatalErrorMsg'' :: FatalMessager -> String -> IO ()
 fatalErrorMsg'' fm msg = fm msg
 
 compilationProgressMsg :: DynFlags -> String -> IO ()
-compilationProgressMsg dflags msg
-  = ifVerbose dflags 1 $
-    logOutput dflags (defaultUserStyle dflags) (text msg)
+compilationProgressMsg dflags msg = do
+    traceEventIO $ "GHC progress: " ++ msg
+    ifVerbose dflags 1 $
+        logOutput dflags (defaultUserStyle dflags) (text msg)
 
 showPass :: DynFlags -> String -> IO ()
 showPass dflags what
@@ -641,10 +643,12 @@ withTiming getDFlags what force_result action
        if verbosity dflags >= 2 || dopt Opt_D_dump_timings dflags
           then do liftIO $ logInfo dflags (defaultUserStyle dflags)
                          $ text "***" <+> what <> colon
+                  liftIO $ traceEventIO $ showSDocOneLine dflags $ text "GHC:started:" <+> what
                   alloc0 <- liftIO getAllocationCounter
                   start <- liftIO getCPUTime
                   !r <- action
                   () <- pure $ force_result r
+                  liftIO $ traceEventIO $ showSDocOneLine dflags $ text "GHC:finished:" <+> what
                   end <- liftIO getCPUTime
                   alloc1 <- liftIO getAllocationCounter
                   -- recall that allocation counter counts down


=====================================
compiler/prelude/PrelRules.hs
=====================================
@@ -475,8 +475,7 @@ shiftRule shift_op
              -> return e1
              -- See Note [Guarding against silly shifts]
              | shift_len < 0 || shift_len > wordSizeInBits dflags
-             -> return $ mkRuntimeErrorApp rUNTIME_ERROR_ID wordPrimTy
-                           ("Bad shift length " ++ show shift_len)
+             -> return $ Lit $ mkLitNumberWrap dflags LitNumInt 0 (exprType e1)
 
            -- Do the shift at type Integer, but shift length is Int
            Lit (LitNumber nt x t)
@@ -701,7 +700,27 @@ can't constant fold it, but if it gets to the assember we get
      Error: operand type mismatch for `shl'
 
 So the best thing to do is to rewrite the shift with a call to error,
-when the second arg is stupid.
+when the second arg is large. However, in general we cannot do this; consider
+this case
+
+    let x = I# (uncheckedIShiftL# n 80)
+    in ...
+
+Here x contains an invalid shift and consequently we would like to rewrite it
+as follows:
+
+    let x = I# (error "invalid shift)
+    in ...
+
+This was originally done in the fix to #16449 but this breaks the let/app
+invariant (see Note [CoreSyn let/app invariant] in CoreSyn) as noted in #16742.
+For the reasons discussed in Note [Checking versus non-checking primops] (in
+the PrimOp module) there is no safe way rewrite the argument of I# such that
+it bottoms.
+
+Consequently we instead take advantage of the fact that large shifts are
+undefined behavior (see associated documentation in primops.txt.pp) and
+transform the invalid shift into an "obviously incorrect" value.
 
 There are two cases:
 


=====================================
compiler/prelude/PrimOp.hs
=====================================
@@ -304,6 +304,27 @@ primOpOutOfLine :: PrimOp -> Bool
 *                                                                      *
 ************************************************************************
 
+Note [Checking versus non-checking primops]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+  In GHC primops break down into two classes:
+
+   a. Checking primops behave, for instance, like division. In this
+      case the primop may throw an exception (e.g. division-by-zero)
+      and is consequently is marked with the can_fail flag described below.
+      The ability to fail comes at the expense of precluding some optimizations.
+
+   b. Non-checking primops behavior, for instance, like addition. While
+      addition can overflow it does not produce an exception. So can_fail is
+      set to False, and we get more optimisation opportunities.  But we must
+      never throw an exception, so we cannot rewrite to a call to error.
+
+  It is important that a non-checking primop never be transformed in a way that
+  would cause it to bottom. Doing so would violate Core's let/app invariant
+  (see Note [CoreSyn let/app invariant] in CoreSyn) which is critical to
+  the simplifier's ability to float without fear of changing program meaning.
+
+
 Note [PrimOp can_fail and has_side_effects]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 Both can_fail and has_side_effects mean that the primop has


=====================================
docs/users_guide/8.8.1-notes.rst
=====================================
@@ -13,9 +13,11 @@ Highlights
 
 The highlights, since the 8.6.1 release, are:
 
-- Many, many bug fixes.
+- GHC now supports :ref:`visible type applications <visible-type-application>`.
+- Type variables in type family instances and rewrite rules can now be explicitly ``forall``-bound.
 - A new code layout algorithm for x86.
-
+- The final phase of the ``MonadFail`` proposal has been implemented.
+- Many, many bug fixes.
 
 Full details
 ------------
@@ -31,7 +33,8 @@ Language
 
 - GHC now allows explicitly binding type variables in type family instances and
   rewrite rules, as described in
-  `GHC proposal #7 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0007-instance-foralls.rst>`__. For instance: ::
+  `GHC proposal #7 <https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0007-instance-foralls.rst>`__.
+  For instance: ::
 
     type family G a b where
       forall x y. G [x] (Proxy y) = Double
@@ -178,8 +181,9 @@ Template Haskell
 ~~~~~~~~~~~~~~~~~~~~
 
 - GHC now exposes a new primop, ``traceBinaryEvent#``. This primop writes
-  eventlog events similar to ``traceBinaryEvent#`` but allows the user to pass
-  the event payload as a binary blob instead of a ``String``.
+  eventlog events similar to ``traceEvent#`` but allows the user to pass
+  the event payload as a binary blob instead of a zero-terminated
+  ``ByteString``.
 
 - The ``StableName#`` type parameter now has a phantom role instead of
   a representational one. There is really no reason to care about the


=====================================
testsuite/tests/codeGen/should_run/T16449_2.hs
=====================================
@@ -5,5 +5,9 @@ module Main where
 import GHC.Prim
 import GHC.Int
 
+-- Test that large unchecked shifts, which constitute undefined behavior, do
+-- not crash the compiler and instead evaluate to 0.
+-- See Note [Guarding against silly shifts] in PrelRules.
+
 -- Shift should be larger than the word size (e.g. 64 on 64-bit) for this test.
 main = print (I# (uncheckedIShiftL# 1# 1000#))


=====================================
testsuite/tests/codeGen/should_run/T16449_2.stderr deleted
=====================================
@@ -1 +0,0 @@
-T16449_2: Bad shift length 1000


=====================================
testsuite/tests/codeGen/should_run/T16449_2.stdout
=====================================
@@ -0,0 +1,2 @@
+0
+


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -192,4 +192,4 @@ test('T15892',
         # happen, so -G1 -A32k:
         extra_run_opts('+RTS -G1 -A32k -RTS') ],
      compile_and_run, ['-O'])
-test('T16449_2', exit_code(1), compile_and_run, [''])
+test('T16449_2', exit_code(0), compile_and_run, [''])


=====================================
testsuite/tests/ghc-api/downsweep/all.T
=====================================
@@ -1,6 +1,7 @@
 test('PartialDownsweep',
      [ extra_run_opts('"' + config.libdir + '"')
      , when(opsys('darwin'), skip) # use_specs doesn't exist on this branch yet
+     , skip # platform dependence
      ],
      compile_and_run,
      ['-package ghc'])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/5fc451d3fc47fed9b5d7782b27ceefc7965c5372...4c5899e65f1fe7053011a88af73b560a4b233e88

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/5fc451d3fc47fed9b5d7782b27ceefc7965c5372...4c5899e65f1fe7053011a88af73b560a4b233e88
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/20190616/6b86d951/attachment-0001.html>


More information about the ghc-commits mailing list