[commit: ghc] master: Also suppress uniques in cmm dumps with `-dsuppress-uniques`. (aa77c60)

git at git.haskell.org git at git.haskell.org
Tue Jun 5 00:45:03 UTC 2018


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

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

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

commit aa77c602e910cb9a4e17022464c0341fd731f3e0
Author: klebinger.andreas at gmx.at <klebinger.andreas at gmx.at>
Date:   Mon Jun 4 17:50:21 2018 -0400

    Also suppress uniques in cmm dumps with `-dsuppress-uniques`.
    
    Allows easier structural comparison of Cmm code.
    
    Before:
    ```
           cxCH: // global
               _suEU::P64 = R1;
               if ((Sp + -16) < SpLim) (likely: False) goto cxCI; else goto
    cxCJ;
    ```
    
    After
    ```
           _lbl_: // global
               __locVar_::P64 = R1;
               if ((Sp + -16) < SpLim) (likely: False) goto cxBf; else goto
    cxBg;
    ```
    
    Test Plan: Looking at dumps, ci
    
    Reviewers: bgamari, simonmar
    
    Reviewed By: bgamari
    
    Subscribers: rwbarton, thomie, carter
    
    Differential Revision: https://phabricator.haskell.org/D4786


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

aa77c602e910cb9a4e17022464c0341fd731f3e0
 compiler/cmm/PprCmm.hs     | 6 +++++-
 compiler/cmm/PprCmmExpr.hs | 9 +++++++--
 2 files changed, 12 insertions(+), 3 deletions(-)

diff --git a/compiler/cmm/PprCmm.hs b/compiler/cmm/PprCmm.hs
index 51deb8c..90f26e4 100644
--- a/compiler/cmm/PprCmm.hs
+++ b/compiler/cmm/PprCmm.hs
@@ -185,9 +185,13 @@ pprNode node = pp_node <+> pp_debug
     pp_node :: SDoc
     pp_node = sdocWithDynFlags $ \dflags -> case node of
       -- label:
-      CmmEntry id tscope -> ppr id <> colon <+>
+      CmmEntry id tscope -> lbl <> colon <+>
          (sdocWithDynFlags $ \dflags ->
            ppUnless (gopt Opt_SuppressTicks dflags) (text "//" <+> ppr tscope))
+          where
+            lbl = if gopt Opt_SuppressUniques dflags
+                then text "_lbl_"
+                else ppr id
 
       -- // text
       CmmComment s -> text "//" <+> ftext s
diff --git a/compiler/cmm/PprCmmExpr.hs b/compiler/cmm/PprCmmExpr.hs
index 4538556..7bf73f1 100644
--- a/compiler/cmm/PprCmmExpr.hs
+++ b/compiler/cmm/PprCmmExpr.hs
@@ -43,6 +43,7 @@ import GhcPrelude
 import CmmExpr
 
 import Outputable
+import DynFlags
 
 import Data.Maybe
 import Numeric ( fromRat )
@@ -226,14 +227,18 @@ pprReg r
 -- We only print the type of the local reg if it isn't wordRep
 --
 pprLocalReg :: LocalReg -> SDoc
-pprLocalReg (LocalReg uniq rep)
+pprLocalReg (LocalReg uniq rep) = sdocWithDynFlags $ \dflags ->
 --   = ppr rep <> char '_' <> ppr uniq
 -- Temp Jan08
-   = char '_' <> ppr uniq <>
+    char '_' <> pprUnique dflags uniq <>
        (if isWord32 rep -- && not (isGcPtrType rep) -- Temp Jan08               -- sigh
                     then dcolon <> ptr <> ppr rep
                     else dcolon <> ptr <> ppr rep)
    where
+     pprUnique dflags unique =
+        if gopt Opt_SuppressUniques dflags
+            then text "_locVar_"
+            else ppr unique
      ptr = empty
          --if isGcPtrType rep
          --      then doubleQuotes (text "ptr")



More information about the ghc-commits mailing list