summaryrefslogtreecommitdiff
path: root/compiler/iface
diff options
context:
space:
mode:
authorIan Lynagh <igloo@earth.li>2010-09-14 20:17:03 +0000
committerIan Lynagh <igloo@earth.li>2010-09-14 20:17:03 +0000
commite95ee1f718c6915c478005aad8af81705357d6ab (patch)
tree0b19fdfd9d02b195b371e0f6ef8d413936113519 /compiler/iface
parent83a8fc9f6e04436784693a2188a58eac9c3e9664 (diff)
downloadhaskell-e95ee1f718c6915c478005aad8af81705357d6ab.tar.gz
Remove (most of) the FiniteMap wrapper
We still have insertList, insertListWith, deleteList which aren't in Data.Map, and foldRightWithKey which works around the fold(r)WithKey addition and deprecation.
Diffstat (limited to 'compiler/iface')
-rw-r--r--compiler/iface/IfaceEnv.lhs12
-rw-r--r--compiler/iface/MkIface.lhs40
2 files changed, 27 insertions, 25 deletions
diff --git a/compiler/iface/IfaceEnv.lhs b/compiler/iface/IfaceEnv.lhs
index 84a6474077..a1bcbb4f40 100644
--- a/compiler/iface/IfaceEnv.lhs
+++ b/compiler/iface/IfaceEnv.lhs
@@ -31,7 +31,6 @@ import Module
import UniqFM
import FastString
import UniqSupply
-import FiniteMap
import BasicTypes
import SrcLoc
import MkId
@@ -40,6 +39,7 @@ import Outputable
import Exception ( evaluate )
import Data.IORef ( atomicModifyIORef, readIORef )
+import qualified Data.Map as Map
\end{code}
@@ -176,14 +176,14 @@ newIPName occ_name_ip =
ipcache = nsIPs name_cache
key = occ_name_ip -- Ensures that ?x and %x get distinct Names
in
- case lookupFM ipcache key of
+ case Map.lookup key ipcache of
Just name_ip -> (name_cache, name_ip)
Nothing -> (new_ns, name_ip)
where
(us', us1) = splitUniqSupply (nsUniqs name_cache)
uniq = uniqFromSupply us1
name_ip = mapIPName (mkIPName uniq) occ_name_ip
- new_ipcache = addToFM ipcache key name_ip
+ new_ipcache = Map.insert key name_ip ipcache
new_ns = name_cache {nsUniqs = us', nsIPs = new_ipcache}
\end{code}
@@ -220,9 +220,9 @@ extendOrigNameCache nc name
extendNameCache :: OrigNameCache -> Module -> OccName -> Name -> OrigNameCache
extendNameCache nc mod occ name
- = extendModuleEnv_C combine nc mod (unitOccEnv occ name)
+ = extendModuleEnvWith combine nc mod (unitOccEnv occ name)
where
- combine occ_env _ = extendOccEnv occ_env occ name
+ combine _ occ_env = extendOccEnv occ_env occ name
getNameCache :: TcRnIf a b NameCache
getNameCache = do { HscEnv { hsc_NC = nc_var } <- getTopEnv;
@@ -254,7 +254,7 @@ initNameCache :: UniqSupply -> [Name] -> NameCache
initNameCache us names
= NameCache { nsUniqs = us,
nsNames = initOrigNames names,
- nsIPs = emptyFM }
+ nsIPs = Map.empty }
initOrigNames :: [Name] -> OrigNameCache
initOrigNames names = foldl extendOrigNameCache emptyModuleEnv names
diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs
index fa9e0ec14c..68c6cf16a6 100644
--- a/compiler/iface/MkIface.lhs
+++ b/compiler/iface/MkIface.lhs
@@ -87,7 +87,6 @@ import BasicTypes hiding ( SuccessFlag(..) )
import UniqFM
import Unique
import Util hiding ( eqListBy )
-import FiniteMap
import FastString
import Maybes
import ListSetOps
@@ -97,6 +96,8 @@ import Bag
import Control.Monad
import Data.List
+import Data.Map (Map)
+import qualified Data.Map as Map
import Data.IORef
import System.FilePath
\end{code}
@@ -523,7 +524,7 @@ addFingerprints hsc_env mb_old_fingerprint iface0 new_decls
-- wiki/Commentary/Compiler/RecompilationAvoidance
-- put the declarations in a canonical order, sorted by OccName
- let sorted_decls = eltsFM $ listToFM $
+ let sorted_decls = Map.elems $ Map.fromList $
[(ifName d, e) | e@(_, d) <- decls_w_hashes]
-- the ABI hash depends on:
@@ -860,10 +861,10 @@ mk_usage_info pit hsc_env this_mod direct_imports used_names
| otherwise
= case nameModule_maybe name of
Nothing -> pprPanic "mkUsageInfo: internal name?" (ppr name)
- Just mod -> -- We use this fiddly lambda function rather than
- -- (++) as the argument to extendModuleEnv_C to
+ Just mod -> -- This lambda function is really just a
+ -- specialised (++); originally came about to
-- avoid quadratic behaviour (trac #2680)
- extendModuleEnv_C (\xs _ -> occ:xs) mv_map mod [occ]
+ extendModuleEnvWith (\_ xs -> occ:xs) mv_map mod [occ]
where occ = nameOccName name
-- We want to create a Usage for a home module if
@@ -897,7 +898,7 @@ mk_usage_info pit hsc_env this_mod direct_imports used_names
usg_mod_name = moduleName mod,
usg_mod_hash = mod_hash,
usg_exports = export_hash,
- usg_entities = fmToList ent_hashs }
+ usg_entities = Map.toList ent_hashs }
where
maybe_iface = lookupIfaceByModule dflags hpt pit mod
-- In one-shot mode, the interfaces for home-package
@@ -914,13 +915,13 @@ mk_usage_info pit hsc_env this_mod direct_imports used_names
used_occs = lookupModuleEnv ent_map mod `orElse` []
- -- Making a FiniteMap here ensures that (a) we remove duplicates
+ -- Making a Map here ensures that (a) we remove duplicates
-- when we have usages on several subordinates of a single parent,
-- and (b) that the usages emerge in a canonical order, which
- -- is why we use FiniteMap rather than OccEnv: FiniteMap works
+ -- is why we use Map rather than OccEnv: Map works
-- using Ord on the OccNames, which is a lexicographic ordering.
- ent_hashs :: FiniteMap OccName Fingerprint
- ent_hashs = listToFM (map lookup_occ used_occs)
+ ent_hashs :: Map OccName Fingerprint
+ ent_hashs = Map.fromList (map lookup_occ used_occs)
lookup_occ occ =
case hash_env occ of
@@ -960,10 +961,10 @@ mkIfaceExports :: [AvailInfo]
-> [(Module, [GenAvailInfo OccName])]
-- Group by module and sort by occurrence
mkIfaceExports exports
- = [ (mod, eltsFM avails)
+ = [ (mod, Map.elems avails)
| (mod, avails) <- sortBy (stableModuleCmp `on` fst)
(moduleEnvToList groupFM)
- -- NB. the fmToList is in a random order,
+ -- NB. the Map.toList is in a random order,
-- because Ord Module is not a predictable
-- ordering. Hence we perform a final sort
-- using the stable Module ordering.
@@ -971,20 +972,21 @@ mkIfaceExports exports
where
-- Group by the module where the exported entities are defined
-- (which may not be the same for all Names in an Avail)
- -- Deliberately use FiniteMap rather than UniqFM so we
+ -- Deliberately use Map rather than UniqFM so we
-- get a canonical ordering
- groupFM :: ModuleEnv (FiniteMap FastString (GenAvailInfo OccName))
+ groupFM :: ModuleEnv (Map FastString (GenAvailInfo OccName))
groupFM = foldl add emptyModuleEnv exports
- add_one :: ModuleEnv (FiniteMap FastString (GenAvailInfo OccName))
+ add_one :: ModuleEnv (Map FastString (GenAvailInfo OccName))
-> Module -> GenAvailInfo OccName
- -> ModuleEnv (FiniteMap FastString (GenAvailInfo OccName))
+ -> ModuleEnv (Map FastString (GenAvailInfo OccName))
add_one env mod avail
- = extendModuleEnv_C plusFM env mod
- (unitFM (occNameFS (availName avail)) avail)
+ -- XXX Is there a need to flip Map.union here?
+ = extendModuleEnvWith (flip Map.union) env mod
+ (Map.singleton (occNameFS (availName avail)) avail)
-- NB: we should not get T(X) and T(Y) in the export list
- -- else the plusFM will simply discard one! They
+ -- else the Map.union will simply discard one! They
-- should have been combined by now.
add env (Avail n)
= ASSERT( isExternalName n )