Skip to content
Commits on Source (2)
  • Ben Gamari's avatar
    PrelRules: Don't break let/app invariant in shiftRule · fee015b5
    Ben Gamari authored
    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 0bd3b9dd)
    fee015b5
  • Ben Gamari's avatar
    testsuite: Skip PartialDownsweep · 7fe79797
    Ben Gamari authored
    This gives different results on different platforms
    7fe79797
...@@ -445,6 +445,9 @@ which will generate a @case@ if necessary ...@@ -445,6 +445,9 @@ which will generate a @case@ if necessary
The let/app invariant is initially enforced by mkCoreLet and mkCoreApp in The let/app invariant is initially enforced by mkCoreLet and mkCoreApp in
coreSyn/MkCore. 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] Note [CoreSyn type and coercion invariant]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We allow a /non-recursive/, /non-top-level/ let to bind type and We allow a /non-recursive/, /non-top-level/ let to bind type and
......
...@@ -475,8 +475,7 @@ shiftRule shift_op ...@@ -475,8 +475,7 @@ shiftRule shift_op
-> return e1 -> return e1
-- See Note [Guarding against silly shifts] -- See Note [Guarding against silly shifts]
| shift_len < 0 || shift_len > wordSizeInBits dflags | shift_len < 0 || shift_len > wordSizeInBits dflags
-> return $ mkRuntimeErrorApp rUNTIME_ERROR_ID wordPrimTy -> return $ Lit $ mkLitNumberWrap dflags LitNumInt 0 (exprType e1)
("Bad shift length " ++ show shift_len)
-- Do the shift at type Integer, but shift length is Int -- Do the shift at type Integer, but shift length is Int
Lit (LitNumber nt x t) Lit (LitNumber nt x t)
...@@ -701,7 +700,27 @@ can't constant fold it, but if it gets to the assember we get ...@@ -701,7 +700,27 @@ can't constant fold it, but if it gets to the assember we get
Error: operand type mismatch for `shl' Error: operand type mismatch for `shl'
So the best thing to do is to rewrite the shift with a call to error, 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: There are two cases:
......
...@@ -304,6 +304,27 @@ primOpOutOfLine :: PrimOp -> Bool ...@@ -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] Note [PrimOp can_fail and has_side_effects]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Both can_fail and has_side_effects mean that the primop has Both can_fail and has_side_effects mean that the primop has
......
...@@ -5,5 +5,9 @@ module Main where ...@@ -5,5 +5,9 @@ module Main where
import GHC.Prim import GHC.Prim
import GHC.Int 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. -- Shift should be larger than the word size (e.g. 64 on 64-bit) for this test.
main = print (I# (uncheckedIShiftL# 1# 1000#)) main = print (I# (uncheckedIShiftL# 1# 1000#))
...@@ -192,4 +192,4 @@ test('T15892', ...@@ -192,4 +192,4 @@ test('T15892',
# happen, so -G1 -A32k: # happen, so -G1 -A32k:
extra_run_opts('+RTS -G1 -A32k -RTS') ], extra_run_opts('+RTS -G1 -A32k -RTS') ],
compile_and_run, ['-O']) compile_and_run, ['-O'])
test('T16449_2', exit_code(1), compile_and_run, ['']) test('T16449_2', exit_code(0), compile_and_run, [''])
test('PartialDownsweep', test('PartialDownsweep',
[ extra_run_opts('"' + config.libdir + '"') [ extra_run_opts('"' + config.libdir + '"')
, when(opsys('darwin'), skip) # use_specs doesn't exist on this branch yet , when(opsys('darwin'), skip) # use_specs doesn't exist on this branch yet
, skip # platform dependence
], ],
compile_and_run, compile_and_run,
['-package ghc']) ['-package ghc'])
......