[commit: ghc] master: Kill two instances of uniqSetToList (4426c5f)

git at git.haskell.org git at git.haskell.org
Tue Jun 7 13:29:56 UTC 2016


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

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

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

commit 4426c5ffe5dfc00da4e203ae8fe9323a427c479e
Author: Bartosz Nitka <niteria at gmail.com>
Date:   Tue Jun 7 05:36:43 2016 -0700

    Kill two instances of uniqSetToList
    
    There should be no performance impact of switching to the
    deterministic set here.
    
    GHC Trac: #4012


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

4426c5ffe5dfc00da4e203ae8fe9323a427c479e
 compiler/cmm/PprC.hs    |  3 ++-
 compiler/ghci/Linker.hs | 17 ++++++++---------
 2 files changed, 10 insertions(+), 10 deletions(-)

diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs
index 4bb256a..331dd67 100644
--- a/compiler/cmm/PprC.hs
+++ b/compiler/cmm/PprC.hs
@@ -42,6 +42,7 @@ import FastString
 import Outputable
 import Platform
 import UniqSet
+import UniqFM
 import Unique
 import Util
 
@@ -984,7 +985,7 @@ is_cishCC JavaScriptCallConv = False
 --
 pprTempAndExternDecls :: [CmmBlock] -> (SDoc{-temps-}, SDoc{-externs-})
 pprTempAndExternDecls stmts
-  = (vcat (map pprTempDecl (uniqSetToList temps)),
+  = (pprUFM temps (vcat . map pprTempDecl),
      vcat (map (pprExternDecl False{-ToDo-}) (Map.keys lbls)))
   where (temps, lbls) = runTE (mapM_ te_BB stmts)
 
diff --git a/compiler/ghci/Linker.hs b/compiler/ghci/Linker.hs
index 2df8840..f018a2e 100644
--- a/compiler/ghci/Linker.hs
+++ b/compiler/ghci/Linker.hs
@@ -47,7 +47,6 @@ import Util
 import ErrUtils
 import SrcLoc
 import qualified Maybes
-import UniqSet
 import UniqDSet
 import FastString
 import Platform
@@ -576,7 +575,7 @@ getLinkDeps hsc_env hpt pls replace_osuf span mods
         -- 1.  Find the dependent home-pkg-modules/packages from each iface
         -- (omitting modules from the interactive package, which is already linked)
       ; (mods_s, pkgs_s) <- follow_deps (filterOut isInteractiveModule mods)
-                                        emptyUniqSet emptyUniqSet;
+                                        emptyUniqDSet emptyUniqDSet;
 
       ; let {
         -- 2.  Exclude ones already linked
@@ -604,11 +603,11 @@ getLinkDeps hsc_env hpt pls replace_osuf span mods
         -- dependencies of that.  Hence we need to traverse the dependency
         -- tree recursively.  See bug #936, testcase ghci/prog007.
     follow_deps :: [Module]             -- modules to follow
-                -> UniqSet ModuleName         -- accum. module dependencies
-                -> UniqSet UnitId          -- accum. package dependencies
+                -> UniqDSet ModuleName         -- accum. module dependencies
+                -> UniqDSet UnitId          -- accum. package dependencies
                 -> IO ([ModuleName], [UnitId]) -- result
     follow_deps []     acc_mods acc_pkgs
-        = return (uniqSetToList acc_mods, uniqSetToList acc_pkgs)
+        = return (uniqDSetToList acc_mods, uniqDSetToList acc_pkgs)
     follow_deps (mod:mods) acc_mods acc_pkgs
         = do
           mb_iface <- initIfaceCheck hsc_env $
@@ -628,12 +627,12 @@ getLinkDeps hsc_env hpt pls replace_osuf span mods
                     where is_boot (m,True)  = Left m
                           is_boot (m,False) = Right m
 
-            boot_deps' = filter (not . (`elementOfUniqSet` acc_mods)) boot_deps
-            acc_mods'  = addListToUniqSet acc_mods (moduleName mod : mod_deps)
-            acc_pkgs'  = addListToUniqSet acc_pkgs $ map fst pkg_deps
+            boot_deps' = filter (not . (`elementOfUniqDSet` acc_mods)) boot_deps
+            acc_mods'  = addListToUniqDSet acc_mods (moduleName mod : mod_deps)
+            acc_pkgs'  = addListToUniqDSet acc_pkgs $ map fst pkg_deps
           --
           if pkg /= this_pkg
-             then follow_deps mods acc_mods (addOneToUniqSet acc_pkgs' pkg)
+             then follow_deps mods acc_mods (addOneToUniqDSet acc_pkgs' pkg)
              else follow_deps (map (mkModule this_pkg) boot_deps' ++ mods)
                               acc_mods' acc_pkgs'
         where



More information about the ghc-commits mailing list