[Git][ghc/ghc][master] Fix rewriting invalid shifts to errors

Marge Bot gitlab at gitlab.haskell.org
Sat Jun 1 15:19:02 UTC 2019



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


Commits:
1503da32 by Ömer Sinan Ağacan at 2019-06-01T15:18:57Z
Fix rewriting invalid shifts to errors

Fixes #16449.

5341edf3 removed a code in rewrite rules for bit shifts, which broke the
"silly shift guard", causing generating invalid bit shifts or heap
overflow in compile time while trying to evaluate those invalid bit
shifts.

The "guard" is explained in Note [Guarding against silly shifts] in
PrelRules.hs.

More specifically, this was the breaking change:

    --- a/compiler/prelude/PrelRules.hs
    +++ b/compiler/prelude/PrelRules.hs
    @@ -474,12 +474,11 @@ shiftRule shift_op
            ; case e1 of
                _ | shift_len == 0
                  -> return e1
    -             | shift_len < 0 || wordSizeInBits dflags < shift_len
    -             -> return (mkRuntimeErrorApp rUNTIME_ERROR_ID wordPrimTy
    -                                        ("Bad shift length" ++ show shift_len))

This patch reverts this change.

Two new tests added:

- T16449_1: The original reproducer in #16449. This was previously
  casing a heap overflow in compile time when CmmOpt tries to evaluate
  the large (invalid) bit shift in compile time, using `Integer` as the
  result type. Now it builds as expected. We now generate an error for
  the shift as expected.

- T16449_2: Tests code generator for large (invalid) bit shifts.

- - - - -


6 changed files:

- compiler/prelude/PrelRules.hs
- + testsuite/tests/codeGen/should_compile/T16449_1.hs
- testsuite/tests/codeGen/should_compile/all.T
- + testsuite/tests/codeGen/should_run/T16449_2.hs
- + testsuite/tests/codeGen/should_run/T16449_2.stderr
- testsuite/tests/codeGen/should_run/all.T


Changes:

=====================================
compiler/prelude/PrelRules.hs
=====================================
@@ -467,13 +467,16 @@ shiftRule :: (DynFlags -> Integer -> Int -> Integer) -> RuleM CoreExpr
 -- Used for shift primops
 --    ISllOp, ISraOp, ISrlOp :: Word# -> Int# -> Word#
 --    SllOp, SrlOp           :: Word# -> Int# -> Word#
--- See Note [Guarding against silly shifts]
 shiftRule shift_op
   = do { dflags <- getDynFlags
        ; [e1, Lit (LitNumber LitNumInt shift_len _)] <- getArgs
        ; case e1 of
            _ | shift_len == 0
              -> 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)
 
            -- Do the shift at type Integer, but shift length is Int
            Lit (LitNumber nt x t)


=====================================
testsuite/tests/codeGen/should_compile/T16449_1.hs
=====================================
@@ -0,0 +1,8 @@
+module T16449_1 where
+
+import Data.Bits (setBit)
+
+f :: Int
+f = foldl setter 0 $ zip [0..] [()]
+  where
+    setter v (ix, _) = setBit v ix


=====================================
testsuite/tests/codeGen/should_compile/all.T
=====================================
@@ -59,3 +59,5 @@ test('T15155',
 
 test('T15155l', when(unregisterised(), skip),
      makefile_test, [])
+
+test('T16449_1', normal, compile, [''])


=====================================
testsuite/tests/codeGen/should_run/T16449_2.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE MagicHash #-}
+
+module Main where
+
+import GHC.Prim
+import GHC.Int
+
+-- 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
=====================================
@@ -0,0 +1 @@
+T16449_2: Bad shift length 1000


=====================================
testsuite/tests/codeGen/should_run/all.T
=====================================
@@ -195,3 +195,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, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/1503da32d26fb59fb6ebb620bfd0f8c08638f627

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/1503da32d26fb59fb6ebb620bfd0f8c08638f627
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/20190601/569655bf/attachment-0001.html>


More information about the ghc-commits mailing list