[Git][ghc/ghc][wip/T16742] PrelRules: Don't break let/app invariant in shiftRule

Ben Gamari gitlab at gitlab.haskell.org
Tue Jun 11 05:16:25 UTC 2019



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


Commits:
6f76f041 by Ben Gamari at 2019-06-11T05:16:16Z
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.

- - - - -


5 changed files:

- compiler/prelude/PrelRules.hs
- 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


Changes:

=====================================
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,23 @@ 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.
+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:
 


=====================================
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
=====================================
@@ -196,4 +196,4 @@ test('T15892',
         extra_run_opts('+RTS -G1 -A32k -RTS') ],
      compile_and_run, ['-O'])
 test('T16617', normal, compile_and_run, [''])
-test('T16449_2', exit_code(1), compile_and_run, [''])
+test('T16449_2', exit_code(0), compile_and_run, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/6f76f041ba358fd25435b47b588878bd2cabbe89

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/6f76f041ba358fd25435b47b588878bd2cabbe89
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/20190611/43d3ecb3/attachment-0001.html>


More information about the ghc-commits mailing list