[Git][ghc/ghc][master] Don't use LEA with 8-bit registers (#18614)
Marge Bot
gitlab at gitlab.haskell.org
Wed Nov 4 21:48:48 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00
Don't use LEA with 8-bit registers (#18614)
- - - - -
3 changed files:
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- + testsuite/tests/codeGen/should_compile/T18614.hs
- testsuite/tests/codeGen/should_compile/all.T
Changes:
=====================================
compiler/GHC/CmmToAsm/X86/CodeGen.hs
=====================================
@@ -1052,7 +1052,9 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps
--------------------
add_code :: Width -> CmmExpr -> CmmExpr -> NatM Register
add_code rep x (CmmLit (CmmInt y _))
- | is32BitInteger y = add_int rep x y
+ | is32BitInteger y
+ , rep /= W8 -- LEA doesn't support byte size (#18614)
+ = add_int rep x y
add_code rep x y = trivialCode rep (ADD format) (Just (ADD format)) x y
where format = intFormat rep
-- TODO: There are other interesting patterns we want to replace
@@ -1061,7 +1063,9 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps
--------------------
sub_code :: Width -> CmmExpr -> CmmExpr -> NatM Register
sub_code rep x (CmmLit (CmmInt y _))
- | is32BitInteger (-y) = add_int rep x (-y)
+ | is32BitInteger (-y)
+ , rep /= W8 -- LEA doesn't support byte size (#18614)
+ = add_int rep x (-y)
sub_code rep x y = trivialCode rep (SUB (intFormat rep)) Nothing x y
-- our three-operand add instruction:
=====================================
testsuite/tests/codeGen/should_compile/T18614.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE MagicHash, UnboxedTuples #-}
+{-# OPTIONS_GHC -O #-}
+
+module Main where
+
+import GHC.Exts
+
+main = pure ()
+
+test :: Word8# -> Word8#
+test x = x `plusWord8#` narrowWord8# 1##
=====================================
testsuite/tests/codeGen/should_compile/all.T
=====================================
@@ -101,3 +101,5 @@ test('T15570',
compile, ['-Wno-overflowed-literals'])
# skipped with CmmToC because it generates a warning:
# warning: integer constant is so large that it is unsigned
+
+test('T18614', normal, compile, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81560981fd9af7ea21b2592c405e9e22af838aab
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81560981fd9af7ea21b2592c405e9e22af838aab
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/20201104/3233d38a/attachment-0001.html>
More information about the ghc-commits
mailing list