[commit: ghc] wip/orf-reboot: Revert "Use NameEnv instead of list for storing used GREs; not clear if this helps performance" (0071c36)

git at git.haskell.org git at git.haskell.org
Mon Oct 12 06:36:59 UTC 2015


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

On branch  : wip/orf-reboot
Link       : http://ghc.haskell.org/trac/ghc/changeset/0071c36756c533f769cfd232f6f22d9ef85aeb7b/ghc

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

commit 0071c36756c533f769cfd232f6f22d9ef85aeb7b
Author: Adam Gundry <adam at well-typed.com>
Date:   Mon Oct 5 16:08:34 2015 +0100

    Revert "Use NameEnv instead of list for storing used GREs; not clear if this helps performance"
    
    This reverts commit d1e7a92e9d92c986f37c25462b27b6a2b03274f8.


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

0071c36756c533f769cfd232f6f22d9ef85aeb7b
 compiler/basicTypes/RdrName.hs  | 2 +-
 compiler/rename/RnEnv.hs        | 4 ++--
 compiler/rename/RnNames.hs      | 2 +-
 compiler/typecheck/TcRnMonad.hs | 2 +-
 compiler/typecheck/TcRnTypes.hs | 2 +-
 5 files changed, 6 insertions(+), 6 deletions(-)

diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs
index c0c1b26..84f8d8f 100644
--- a/compiler/basicTypes/RdrName.hs
+++ b/compiler/basicTypes/RdrName.hs
@@ -43,7 +43,7 @@ module RdrName (
         localRdrEnvElts, delLocalRdrEnvList,
 
         -- * Global mapping of 'RdrName' to 'GlobalRdrElt's
-        GlobalRdrEnv, emptyGlobalRdrEnv, mkGlobalRdrEnv, plusGlobalRdrEnv, plusGRE,
+        GlobalRdrEnv, emptyGlobalRdrEnv, mkGlobalRdrEnv, plusGlobalRdrEnv,
         lookupGlobalRdrEnv, extendGlobalRdrEnv, greOccName, shadowNames,
         pprGlobalRdrEnv, globalRdrEnvElts,
         lookupGRE_RdrName, lookupGRE_Name, lookupGRE_Field_Name, getGRE_NameQualifier_maybes,
diff --git a/compiler/rename/RnEnv.hs b/compiler/rename/RnEnv.hs
index 68501da..d204974 100644
--- a/compiler/rename/RnEnv.hs
+++ b/compiler/rename/RnEnv.hs
@@ -949,7 +949,7 @@ addUsedGRE warn_if_deprec gre
   = do { unless (isLocalGRE gre) $
          do { env <- getGblEnv
             ; traceRn (text "addUsedGRE 1" <+> ppr gre)
-            ; updMutVar (tcg_used_gres env) (\ env -> extendNameEnv_C plusGRE env (gre_name gre) gre) }
+            ; updMutVar (tcg_used_gres env) (gre :) }
 
        ; when warn_if_deprec $
          warnIfDeprecated gre }
@@ -960,7 +960,7 @@ addUsedGREs :: [GlobalRdrElt] -> RnM ()
 addUsedGREs gres
   = do { env <- getGblEnv
        ; traceRn (text "addUsedGREs 2" <+> ppr gres)
-       ; updMutVar (tcg_used_gres env) (\ env -> extendNameEnvList_C plusGRE env [ (gre_name gre, gre) | gre <- gres, not (isLocalGRE gre)]) }
+       ; updMutVar (tcg_used_gres env) (filter (not . isLocalGRE) gres ++) }
 
 warnIfDeprecated :: GlobalRdrElt -> RnM ()
 warnIfDeprecated gre@(GRE { gre_name = name, gre_imp = iss })
diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index cf048b1..f2e90e5 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -1502,7 +1502,7 @@ type ImportDeclUsage
 
 warnUnusedImportDecls :: TcGblEnv -> RnM ()
 warnUnusedImportDecls gbl_env
-  = do { uses <- fmap nameEnvElts $ readMutVar (tcg_used_gres gbl_env)
+  = do { uses <- readMutVar (tcg_used_gres gbl_env)
        ; let user_imports = filterOut (ideclImplicit . unLoc) (tcg_rn_imports gbl_env)
                             -- This whole function deals only with *user* imports
                             -- both for warning about unnecessary ones, and for
diff --git a/compiler/typecheck/TcRnMonad.hs b/compiler/typecheck/TcRnMonad.hs
index dc002b9..1f77bd2 100644
--- a/compiler/typecheck/TcRnMonad.hs
+++ b/compiler/typecheck/TcRnMonad.hs
@@ -82,7 +82,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
  = do { errs_var     <- newIORef (emptyBag, emptyBag) ;
         tvs_var      <- newIORef emptyVarSet ;
         keep_var     <- newIORef emptyNameSet ;
-        used_gre_var <- newIORef emptyNameEnv ;
+        used_gre_var <- newIORef [] ;
         th_var       <- newIORef False ;
         th_splice_var<- newIORef False ;
         infer_var    <- newIORef (True, emptyBag) ;
diff --git a/compiler/typecheck/TcRnTypes.hs b/compiler/typecheck/TcRnTypes.hs
index 51db27f..abcf761 100644
--- a/compiler/typecheck/TcRnTypes.hs
+++ b/compiler/typecheck/TcRnTypes.hs
@@ -383,7 +383,7 @@ data TcGblEnv
           -- here about transative trusted packaage requirements.
 
         tcg_dus :: DefUses,   -- ^ What is defined in this module and what is used.
-        tcg_used_gres :: TcRef (NameEnv GlobalRdrElt),
+        tcg_used_gres :: TcRef [GlobalRdrElt],
           -- See Note [Tracking unused binding and imports]
 
         tcg_keep :: TcRef NameSet,



More information about the ghc-commits mailing list