[Git][ghc/ghc][wip/supersven/riscv64-ncg] Just narrow all CmmLit . CmmInt to the expected width

Sven Tennie (@supersven) gitlab at gitlab.haskell.org
Thu Jul 6 16:54:51 UTC 2023



Sven Tennie pushed to branch wip/supersven/riscv64-ncg at Glasgow Haskell Compiler / GHC


Commits:
960d0af5 by Sven Tennie at 2023-07-06T18:52:24+02:00
Just narrow all CmmLit . CmmInt to the expected width

There may appear immediates that don't fit the size. Just truncate them
with narrowU. Otherwise, some bit operations fail for the highest bit.

- - - - -


1 changed file:

- compiler/GHC/CmmToAsm/RV64/CodeGen.hs


Changes:

=====================================
compiler/GHC/CmmToAsm/RV64/CodeGen.hs
=====================================
@@ -504,42 +504,13 @@ getRegister' config plat expr =
     CmmLit lit ->
       case lit of
         CmmInt 0 w -> pure $ Fixed (intFormat w) zero_reg nilOL
-        CmmInt i w | isEncodeableInWidth w i ->
+        CmmInt i w ->
                      -- narrowU is important: Negative immediates may be
                      -- sign-extended on load!
                      let imm = OpImm . ImmInteger $ narrowU w i
                      in
                         pure (Any (intFormat w) (\dst -> unitOL $ annExpr expr (MOV (OpReg w dst) imm)))
 
-        -- i does not fit. Be careful to keep the sign.
-        CmmInt i w ->
-          let -- select all but the sign (most significant) bit
-              mask = allOneMask (maxBitNo - 1)
-              numBits = i .&. mask
-              truncatedI = numBits .|. signBit i
-              imm = OpImm . ImmInteger $ narrowU w truncatedI
-          in
-            pure $
-               Any
-                  (intFormat w)
-                  ( \dst ->
-                      toOL
-                        [ annExpr
-                            expr
-                            (MOV (OpReg w dst) imm)
-                        ]
-                  )
-          where
-            allOneMask :: Int -> Integer
-            allOneMask 0 = bit 0
-            allOneMask n = bit n .|. allOneMask (n - 1)
-
-            signBit :: Integer -> Integer
-            signBit i | signum i < 0 = bit maxBitNo
-            signBit _i = 0
-
-            maxBitNo = widthInBits w - 1
-
         -- floatToBytes (fromRational f)
         CmmFloat 0 w   -> do
           (op, imm_code) <- litToImm' lit



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/960d0af5760fb9e0e244066e4c5ceffc25016117

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/960d0af5760fb9e0e244066e4c5ceffc25016117
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/20230706/e0ec7683/attachment-0001.html>


More information about the ghc-commits mailing list