[Git][ghc/ghc][wip/T16742] PrelRules: Don't break let/app invariant in shiftRule
Ben Gamari
gitlab at gitlab.haskell.org
Mon Jun 10 13:31:41 UTC 2019
Ben Gamari pushed to branch wip/T16742 at Glasgow Haskell Compiler / GHC
Commits:
67df8551 by Ben Gamari at 2019-06-10T13:31:31Z
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.
- - - - -
1 changed file:
- compiler/prelude/PrelRules.hs
Changes:
=====================================
compiler/prelude/PrelRules.hs
=====================================
@@ -180,8 +180,8 @@ primOpRules nm XorOp = mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor)
, equalArgs >> retLit zerow ]
primOpRules nm NotOp = mkPrimOpRule nm 1 [ unaryLit complementOp
, inversePrimOp NotOp ]
-primOpRules nm SllOp = mkPrimOpRule nm 2 [ shiftRule (const Bits.shiftL) ]
-primOpRules nm SrlOp = mkPrimOpRule nm 2 [ shiftRule shiftRightLogical ]
+primOpRules nm SllOp = mkPrimOpRule nm 2 [ shiftRule (const Bits.shiftL) wordPrimTy ]
+primOpRules nm SrlOp = mkPrimOpRule nm 2 [ shiftRule shiftRightLogical wordPrimTy ]
-- coercions
primOpRules nm Word2IntOp = mkPrimOpRule nm 1 [ liftLitDynFlags word2IntLit
@@ -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 $ mkLitNumberWrap dflags nt 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 and transform the invalid shift into an "obviously
+incorrect" value.
There are two cases:
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/67df855119f629fbf4d3518529364695e4476355
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/67df855119f629fbf4d3518529364695e4476355
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/20190610/2c2a2180/attachment-0001.html>
More information about the ghc-commits
mailing list