[commit: ghc] wip/ghc-8.0-det: Use UniqFM for SigOf (560b7af)

git at git.haskell.org git at git.haskell.org
Mon Jul 25 14:59:26 UTC 2016


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

On branch  : wip/ghc-8.0-det
Link       : http://ghc.haskell.org/trac/ghc/changeset/560b7af436b347d6b3f5ecc5a73eef54472f83bd/ghc

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

commit 560b7af436b347d6b3f5ecc5a73eef54472f83bd
Author: Bartosz Nitka <niteria at gmail.com>
Date:   Mon Jun 13 07:35:32 2016 -0700

    Use UniqFM for SigOf
    
    Summary:
    The Ord instance for ModuleName is currently implemented in
    terms of Uniques causing potential determinism problems.
    I plan to change it to use the actual FastStrings and in
    preparation for that I'm switching to UniqFM where it's
    possible (you need *one* Unique per key, and you can't get
    the keys back), so that the performance doesn't suffer.
    
    Test Plan: ./validate
    
    Reviewers: simonmar, austin, ezyang, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D2320
    
    GHC Trac Issues: #4012
    
    (cherry picked from commit 586d55815401c54f4687d053fb033e53865e0bf1)


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

560b7af436b347d6b3f5ecc5a73eef54472f83bd
 compiler/main/DynFlags.hs | 9 +++++----
 1 file changed, 5 insertions(+), 4 deletions(-)

diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index f6598b9..0a944b7 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -164,6 +164,7 @@ import CmdLineParser
 import Constants
 import Panic
 import Util
+import UniqFM
 import Maybes
 import MonadUtils
 import qualified Pretty
@@ -629,10 +630,10 @@ instance Show SafeHaskellMode where
 instance Outputable SafeHaskellMode where
     ppr = text . show
 
-type SigOf = Map ModuleName Module
+type SigOf = ModuleNameEnv Module
 
 getSigOf :: DynFlags -> ModuleName -> Maybe Module
-getSigOf dflags n = Map.lookup n (sigOf dflags)
+getSigOf dflags n = lookupUFM (sigOf dflags) n
 
 -- | Contains not only a collection of 'GeneralFlag's but also a plethora of
 -- information relating to the compilation of a single file or GHC session
@@ -1438,7 +1439,7 @@ defaultDynFlags mySettings =
         ghcMode                 = CompManager,
         ghcLink                 = LinkBinary,
         hscTarget               = defaultHscTarget (sTargetPlatform mySettings),
-        sigOf                   = Map.empty,
+        sigOf                   = emptyUFM,
         verbosity               = 0,
         optLevel                = 0,
         debugLevel              = 0,
@@ -1981,7 +1982,7 @@ parseSigOf :: String -> SigOf
 parseSigOf str = case filter ((=="").snd) (readP_to_S parse str) of
     [(r, "")] -> r
     _ -> throwGhcException $ CmdLineError ("Can't parse -sig-of: " ++ str)
-  where parse = Map.fromList <$> sepBy parseEntry (R.char ',')
+  where parse = listToUFM <$> sepBy parseEntry (R.char ',')
         parseEntry = do
             n <- tok $ parseModuleName
             -- ToDo: deprecate this 'is' syntax?



More information about the ghc-commits mailing list