Skip to content
Snippets Groups Projects
Commit 35bbc251 authored by Ben Gamari's avatar Ben Gamari Committed by Marge Bot
Browse files

cmm: Disallow shifts larger than shiftee

Previously primops.txt.pp stipulated that the word-size shift primops
were only defined for shift offsets in [0, word_size). However, there
was no further guidance for the definition of Cmm's sub-word size shift
MachOps.

Here we fix this by explicitly disallowing (checked in many cases by
CmmLint) shift operations where the shift offset is larger than the
shiftee. This is consistent with LLVM's shift operations, avoiding the
miscompilation noted in #20637.
parent 78b78ac4
No related branches found
No related tags found
No related merge requests found
...@@ -98,6 +98,7 @@ lintCmmExpr (CmmLoad expr rep) = do ...@@ -98,6 +98,7 @@ lintCmmExpr (CmmLoad expr rep) = do
lintCmmExpr expr@(CmmMachOp op args) = do lintCmmExpr expr@(CmmMachOp op args) = do
platform <- getPlatform platform <- getPlatform
tys <- mapM lintCmmExpr args tys <- mapM lintCmmExpr args
lintShiftOp op (zip args tys)
if map (typeWidth . cmmExprType platform) args == machOpArgReps platform op if map (typeWidth . cmmExprType platform) args == machOpArgReps platform op
then cmmCheckMachOp op args tys then cmmCheckMachOp op args tys
else cmmLintMachOpErr expr (map (cmmExprType platform) args) (machOpArgReps platform op) else cmmLintMachOpErr expr (map (cmmExprType platform) args) (machOpArgReps platform op)
...@@ -110,6 +111,22 @@ lintCmmExpr expr = ...@@ -110,6 +111,22 @@ lintCmmExpr expr =
do platform <- getPlatform do platform <- getPlatform
return (cmmExprType platform expr) return (cmmExprType platform expr)
-- | Check for obviously out-of-bounds shift operations
lintShiftOp :: MachOp -> [(CmmExpr, CmmType)] -> CmmLint ()
lintShiftOp op [(_, arg_ty), (CmmLit (CmmInt n _), _)]
| isShiftOp op
, n >= fromIntegral (widthInBits (typeWidth arg_ty))
= cmmLintErr (text "Shift operation" <+> pprMachOp op
<+> text "has out-of-range offset" <+> ppr n
<> text ". This will result in undefined behavior")
lintShiftOp _ _ = return ()
isShiftOp :: MachOp -> Bool
isShiftOp (MO_Shl _) = True
isShiftOp (MO_U_Shr _) = True
isShiftOp (MO_S_Shr _) = True
isShiftOp _ = False
-- Check for some common byte/word mismatches (eg. Sp + 1) -- Check for some common byte/word mismatches (eg. Sp + 1)
cmmCheckMachOp :: MachOp -> [CmmExpr] -> [CmmType] -> CmmLint CmmType cmmCheckMachOp :: MachOp -> [CmmExpr] -> [CmmType] -> CmmLint CmmType
cmmCheckMachOp op [lit@(CmmLit (CmmInt { })), reg@(CmmReg _)] tys cmmCheckMachOp op [lit@(CmmLit (CmmInt { })), reg@(CmmReg _)] tys
......
...@@ -102,6 +102,8 @@ data MachOp ...@@ -102,6 +102,8 @@ data MachOp
| MO_Or Width | MO_Or Width
| MO_Xor Width | MO_Xor Width
| MO_Not Width | MO_Not Width
-- Shifts. The shift amount must be in [0,widthInBits).
| MO_Shl Width | MO_Shl Width
| MO_U_Shr Width -- unsigned shift right | MO_U_Shr Width -- unsigned shift right
| MO_S_Shr Width -- signed shift right | MO_S_Shr Width -- signed shift right
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment