[commit: ghc] master: StgSyn: Remove unused StgLiveVars types (9df9490)

git at git.haskell.org git at git.haskell.org
Wed Aug 3 08:51:36 UTC 2016


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

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

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

commit 9df9490c4b30bdbd3e0031f7bf2ccd9ba8d867a2
Author: Ömer Sinan Ağacan <omeragacan at gmail.com>
Date:   Wed Aug 3 08:50:31 2016 +0000

    StgSyn: Remove unused StgLiveVars types


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

9df9490c4b30bdbd3e0031f7bf2ccd9ba8d867a2
 compiler/stgSyn/StgSyn.hs | 19 ++-----------------
 1 file changed, 2 insertions(+), 17 deletions(-)

diff --git a/compiler/stgSyn/StgSyn.hs b/compiler/stgSyn/StgSyn.hs
index 2f29f1e..60147bc 100644
--- a/compiler/stgSyn/StgSyn.hs
+++ b/compiler/stgSyn/StgSyn.hs
@@ -13,7 +13,6 @@ generation.
 
 module StgSyn (
         GenStgArg(..),
-        GenStgLiveVars,
 
         GenStgBinding(..), GenStgExpr(..), GenStgRhs(..),
         GenStgAlt, AltType(..),
@@ -25,7 +24,7 @@ module StgSyn (
         combineStgBinderInfo,
 
         -- a set of synonyms for the most common (only :-) parameterisation
-        StgArg, StgLiveVars,
+        StgArg,
         StgBinding, StgExpr, StgRhs, StgAlt,
 
         -- StgOp
@@ -37,8 +36,7 @@ module StgSyn (
         stgArgType,
         stripStgTicksTop,
 
-        pprStgBinding, pprStgBindings,
-        pprStgLVs
+        pprStgBinding, pprStgBindings
     ) where
 
 #include "HsVersions.h"
@@ -62,8 +60,6 @@ import PrimOp      ( PrimOp, PrimCall )
 import TyCon       ( PrimRep(..), TyCon )
 import Type        ( Type )
 import RepType     ( typePrimRep )
-import UniqFM
-import UniqSet
 import Unique      ( Unique )
 import Util
 
@@ -176,8 +172,6 @@ There is no constructor for a lone variable; it would appear as
 @StgApp var []@.
 -}
 
-type GenStgLiveVars occ = UniqSet occ
-
 data GenStgExpr bndr occ
   = StgApp
         occ             -- function
@@ -560,7 +554,6 @@ This happens to be the only one we use at the moment.
 
 type StgBinding  = GenStgBinding  Id Id
 type StgArg      = GenStgArg      Id
-type StgLiveVars = GenStgLiveVars Id
 type StgExpr     = GenStgExpr     Id Id
 type StgRhs      = GenStgRhs      Id Id
 type StgAlt      = GenStgAlt      Id Id
@@ -762,14 +755,6 @@ instance Outputable AltType where
   ppr (AlgAlt tc)     = text "Alg"    <+> ppr tc
   ppr (PrimAlt tc)    = text "Prim"   <+> ppr tc
 
-pprStgLVs :: Outputable occ => GenStgLiveVars occ -> SDoc
-pprStgLVs lvs
-  = getPprStyle $ \ sty ->
-    if userStyle sty || isEmptyUniqSet lvs then
-        empty
-    else
-        hcat [text "{-lvs:", pprUFM lvs interpp'SP, text "-}"]
-
 pprStgRhs :: (OutputableBndr bndr, Outputable bdee, Ord bdee)
           => GenStgRhs bndr bdee -> SDoc
 



More information about the ghc-commits mailing list