[commit: ghc] master: UNREG: fix CmmRegOff large offset handling on W64 platforms (b8e3499)

git at git.haskell.org git at git.haskell.org
Sun Jun 17 18:40:53 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/b8e349922b4841771a59e264183219e6cad3e942/ghc

>---------------------------------------------------------------

commit b8e349922b4841771a59e264183219e6cad3e942
Author: Sergei Trofimovich <slyfox at gentoo.org>
Date:   Sun Jun 17 12:49:51 2018 -0400

    UNREG: fix CmmRegOff large offset handling on W64 platforms
    
    Gabor noticed C warning when building unregisterised
    64-bit compiler on GHC.Integer.Types (from integer-simple).
    
    Minimised example with a warning:
    
    ```haskell
    {-# LANGUAGE MagicHash #-}
    {-# LANGUAGE NoImplicitPrelude #-}
    {-# OPTIONS_GHC -Wall #-}
    
    module M (bug) where
    
    import GHC.Prim (Word#, minusWord#, ltWord#)
    import GHC.Types (isTrue#)
    
    -- assume Word = Word64
    bug :: Word# -> Word#
    bug x = if isTrue# (x `ltWord#` 0x8000000000000000##) then 0##
            else x `minusWord#` 0x8000000000000000##
    ```
    
    ```
    $ LANG=C x86_64-UNREG-linux-gnu-ghc -O1 -c M.hs -fforce-recomp
    /tmp/ghc30219_0/ghc_1.hc: In function 'M_bug_entry':
    
    /tmp/ghc30219_0/ghc_1.hc:20:14: error:
         warning: integer constant is so large that it is unsigned
    ```
    
    It's caused by limited handling of integer literals in CmmRegOff.
    This change switches to use standard integer literal pretty-printer.
    
    C code before the change:
    
    ```c
    FN_(M_bug_entry) {
    W_ _sAg;
    _cAr:
    _sAg = *Sp;
    switch ((W_)(_sAg < 0x8000000000000000UL)) {
    case 0x1UL: goto _cAq;
    default: goto _cAp;
    }
    _cAp:
    R1.w = _sAg+-9223372036854775808;
    // ...
    ```
    
    C code after the change:
    
    ```c
    FN_(M_bug_entry) {
    W_ _sAg;
    _cAr:
    _sAg = *Sp;
    switch ((W_)(_sAg < 0x8000000000000000UL)) {
    case 0x1UL: goto _cAq;
    default: goto _cAp;
    }
    _cAp:
    R1.w = _sAg+(-0x8000000000000000UL);
    ```
    
    URL: https://mail.haskell.org/pipermail/ghc-devs/2018-June/015875.html
    Reported-by: Gabor Greif
    Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org>
    
    Test Plan: test generated code on unregisterised mips64 and amd64
    
    Reviewers: simonmar, ggreif, bgamari
    
    Reviewed By: ggreif, bgamari
    
    Subscribers: rwbarton, thomie, carter
    
    Differential Revision: https://phabricator.haskell.org/D4856


>---------------------------------------------------------------

b8e349922b4841771a59e264183219e6cad3e942
 compiler/cmm/PprC.hs | 12 ++++--------
 1 file changed, 4 insertions(+), 8 deletions(-)

diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs
index 8b30bbf..9e8ced8 100644
--- a/compiler/cmm/PprC.hs
+++ b/compiler/cmm/PprC.hs
@@ -379,14 +379,10 @@ pprExpr e = case e of
     CmmReg reg      -> pprCastReg reg
     CmmRegOff reg 0 -> pprCastReg reg
 
-    CmmRegOff reg i
-        | i < 0 && negate_ok -> pprRegOff (char '-') (-i)
-        | otherwise          -> pprRegOff (char '+') i
-      where
-        pprRegOff op i' = pprCastReg reg <> op <> int i'
-        negate_ok = negate (fromIntegral i :: Integer) <
-                    fromIntegral (maxBound::Int)
-                     -- overflow is undefined; see #7620
+    -- CmmRegOff is an alias of MO_Add
+    CmmRegOff reg i -> sdocWithDynFlags $ \dflags ->
+                       pprCastReg reg <> char '+' <>
+                       pprHexVal (fromIntegral i) (wordWidth dflags)
 
     CmmMachOp mop args -> pprMachOpApp mop args
 



More information about the ghc-commits mailing list