summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorMatthew Pickering <matthewtpickering@gmail.com>2021-05-03 15:18:36 +0100
committerMatthew Pickering <matthewtpickering@gmail.com>2021-05-03 15:18:36 +0100
commit3b8f8ed6072738a7dee3732f19350251f7a0d8b5 (patch)
tree0df92299d8c69748551e9d2c8078338c1b34b726
parent3ec78a30dfe530b52c0e7abd129ffe928836589a (diff)
downloadhaskell-3b8f8ed6072738a7dee3732f19350251f7a0d8b5.tar.gz
Remove transitive dependency fields (dep_mods and dep_pkgs)
-rw-r--r--compiler/GHC/HsToCore/Usage.hs16
-rw-r--r--compiler/GHC/Iface/Load.hs12
-rw-r--r--compiler/GHC/Iface/Recomp.hs7
-rw-r--r--compiler/GHC/Rename/Names.hs45
-rw-r--r--compiler/GHC/Tc/Module.hs6
-rw-r--r--compiler/GHC/Tc/Types.hs28
-rw-r--r--compiler/GHC/Unit/Module/Deps.hs30
7 files changed, 41 insertions, 103 deletions
diff --git a/compiler/GHC/HsToCore/Usage.hs b/compiler/GHC/HsToCore/Usage.hs
index ee145e5b7d..6473eb1408 100644
--- a/compiler/GHC/HsToCore/Usage.hs
+++ b/compiler/GHC/HsToCore/Usage.hs
@@ -43,7 +43,6 @@ import qualified Data.Set as Set
import GHC.Linker.Types
import GHC.Types.SrcLoc
import GHC.Utils.Monad
-import GHC.Driver.Ppr
{- Note [Module self-dependency]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -79,10 +78,7 @@ mkDependencies iuid pluginModules
let (dep_plgins, ms) = unzip [ (moduleName mn, mn) | mn <- pluginModules ]
plugin_dep_pkgs = filter (/= iuid) (map (toUnitId . moduleUnit) ms)
th_used <- readIORef th_var
- let dep_mods = modDepsElts (delFromUFM (imp_dep_mods imports)
- (moduleName mod))
-
- direct_mods = modDepsElts (delFromUFM (imp_direct_dep_mods imports) (moduleName mod))
+ let direct_mods = modDepsElts (delFromUFM (imp_direct_dep_mods imports) (moduleName mod))
-- M.hi-boot can be in the imp_dep_mods, but we must remove
-- it before recording the modules on which this one depends!
-- (We want to retain M.hi-boot in imp_dep_mods so that
@@ -94,27 +90,19 @@ mkDependencies iuid pluginModules
-- We must also remove self-references from imp_orphs. See
-- Note [Module self-dependency]
- raw_pkgs = foldr Set.insert (imp_dep_pkgs imports) plugin_dep_pkgs
direct_pkgs_0 = foldr Set.insert (imp_dep_direct_pkgs imports) plugin_dep_pkgs
direct_pkgs
| th_used = Set.insert thUnitId direct_pkgs_0
| otherwise = direct_pkgs_0
- pkgs | th_used = Set.insert thUnitId raw_pkgs
- | otherwise = raw_pkgs
-
-- Set the packages required to be Safe according to Safe Haskell.
-- See Note [Tracking Trust Transitively] in GHC.Rename.Names
- sorted_pkgs = sort (Set.toList pkgs)
sorted_direct_pkgs = sort (Set.toList direct_pkgs)
trust_pkgs = imp_trust_pkgs imports
- dep_pkgs' = map (\x -> (x, x `Set.member` trust_pkgs)) sorted_pkgs
direct_dep_pkgs' = map (\x -> (x, x `Set.member` trust_pkgs)) sorted_direct_pkgs
- return Deps { dep_mods = dep_mods,
- dep_direct_mods = direct_mods,
- dep_pkgs = dep_pkgs',
+ return Deps { dep_direct_mods = direct_mods,
dep_direct_pkgs = direct_dep_pkgs',
dep_orphs = dep_orphs,
dep_plgins = dep_plgins,
diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs
index a363cd73f0..03627641aa 100644
--- a/compiler/GHC/Iface/Load.hs
+++ b/compiler/GHC/Iface/Load.hs
@@ -1232,12 +1232,14 @@ pprUsageImport usage usg_mod'
-- | Pretty-print unit dependencies
pprDeps :: UnitState -> Dependencies -> SDoc
-pprDeps unit_state (Deps { dep_mods = mods, dep_direct_mods = dmods, dep_pkgs = pkgs, dep_orphs = orphs,
- dep_finsts = finsts, dep_plgins = plugins })
+pprDeps unit_state (Deps { dep_direct_mods = dmods
+ , dep_orphs = orphs
+ , dep_direct_pkgs = pkgs
+ , dep_finsts = finsts
+ , dep_plgins = plugins })
= pprWithUnitState unit_state $
- vcat [text "module dependencies:" <+> fsep (map ppr_mod mods),
- text "direct module dependencies:" <+> fsep (map ppr_mod dmods),
- text "package dependencies:" <+> fsep (map ppr_pkg pkgs),
+ vcat [text "direct module dependencies:" <+> fsep (map ppr_mod dmods),
+ text "direct package dependencies:" <+> fsep (map ppr_pkg pkgs),
text "orphans:" <+> fsep (map ppr orphs),
text "plugins:" <+> fsep (map ppr plugins),
text "family instance modules:" <+> fsep (map ppr finsts)
diff --git a/compiler/GHC/Iface/Recomp.hs b/compiler/GHC/Iface/Recomp.hs
index 28e08872a3..96600ab3f7 100644
--- a/compiler/GHC/Iface/Recomp.hs
+++ b/compiler/GHC/Iface/Recomp.hs
@@ -1119,7 +1119,8 @@ addFingerprints hsc_env iface0
-- Used for the stability check for modules which use TH
fingerprintSources :: HscEnv -> Dependencies -> Fingerprint
fingerprintSources hsc_env deps =
- let mod_hashes = map (mi_src_hash . hm_iface) $ mapMaybe (lookupHpt (hsc_HPT hsc_env). gwib_mod) (dep_mods deps)
+ -- TODO: MP
+ let mod_hashes = map (mi_src_hash . hm_iface) $ mapMaybe (lookupHpt (hsc_HPT hsc_env). gwib_mod) []
in fingerprintFingerprints mod_hashes
@@ -1198,9 +1199,7 @@ getOrphanHashes hsc_env mods = do
sortDependencies :: Dependencies -> Dependencies
sortDependencies d
- = Deps { dep_mods = sortBy (lexicalCompareFS `on` (moduleNameFS . gwib_mod)) (dep_mods d),
- dep_direct_mods = sortBy (lexicalCompareFS `on` (moduleNameFS . gwib_mod)) (dep_direct_mods d),
- dep_pkgs = sortBy (compare `on` fst) (dep_pkgs d),
+ = Deps { dep_direct_mods = sortBy (lexicalCompareFS `on` (moduleNameFS . gwib_mod)) (dep_direct_mods d),
dep_direct_pkgs = sort (dep_direct_pkgs d),
dep_orphs = sortBy stableModuleCmp (dep_orphs d),
dep_finsts = sortBy stableModuleCmp (dep_finsts d),
diff --git a/compiler/GHC/Rename/Names.hs b/compiler/GHC/Rename/Names.hs
index a11d8ba8f7..4ad024d7be 100644
--- a/compiler/GHC/Rename/Names.hs
+++ b/compiler/GHC/Rename/Names.hs
@@ -466,55 +466,32 @@ calculateAvails home_unit iface mod_safe' want_boot imported_by =
-- Does this import mean we now require our own pkg
-- to be trusted? See Note [Trust Own Package]
ptrust = trust == Sf_Trustworthy || trust_pkg
+ pkg_trust_req
+ | isHomeUnit home_unit pkg = ptrust
+ | otherwise = False
+
+ dependent_pkgs = if isHomeUnit home_unit pkg
+ then S.empty
+ else S.fromList [ipkg]
- (dependent_mods, dependent_pkgs, pkg_trust_req)
- | isHomeUnit home_unit pkg =
- -- Imported module is from the home package
- -- Take its dependent modules and add imp_mod itself
- -- TODO: This module is always just deleted from the set
- -- Take its dependent packages unchanged
- --
- -- NB: (dep_mods deps) might include a hi-boot file
- -- for the module being compiled, CM. Do *not* filter
- -- this out (as we used to), because when we've
- -- finished dealing with the direct imports we want to
- -- know if any of them depended on CM.hi-boot, in
- -- which case we should do the hi-boot consistency
- -- check. See GHC.Iface.Load.loadHiBootInterface
- ( GWIB { gwib_mod = moduleName imp_mod, gwib_isBoot = want_boot } : dep_mods deps
- , dep_pkgs deps
- , ptrust
- )
-
- | otherwise =
- -- Imported module is from another package
- -- Dump the dependent modules
- -- Add the package imp_mod comes from to the dependent packages
- ASSERT2( not (ipkg `elem` (map fst $ dep_pkgs deps))
- , ppr ipkg <+> ppr (dep_pkgs deps) )
- ([], (ipkg, False) : dep_pkgs deps, False)
in ImportAvails {
imp_mods = unitModuleEnv (mi_module iface) [imported_by],
imp_orphs = orphans,
imp_finsts = finsts,
- imp_dep_mods = mkModDeps dependent_mods,
imp_direct_dep_mods = mkModDeps $ if isHomeUnit home_unit pkg
then [GWIB (moduleName imp_mod) want_boot]
else [],
- imp_dep_pkgs = S.fromList . map fst $ dependent_pkgs,
- imp_dep_direct_pkgs = if isHomeUnit home_unit pkg
- then S.empty
- else S.fromList [ipkg],
+ imp_dep_direct_pkgs = dependent_pkgs,
-- Add in the imported modules trusted package
-- requirements. ONLY do this though if we import the
-- module as a safe import.
-- See Note [Tracking Trust Transitively]
-- and Note [Trust Transitive Property]
- imp_trust_pkgs = if mod_safe'
- then S.fromList . map fst $ filter snd dependent_pkgs
- else S.empty,
+ -- MP: This simplifies to [] for direct imports.. not sure that
+ -- was ever correct
+ imp_trust_pkgs = S.empty,
-- Do we require our own pkg to be trusted?
-- See Note [Trust Own Package]
imp_trust_own_pkg = pkg_trust_req
diff --git a/compiler/GHC/Tc/Module.hs b/compiler/GHC/Tc/Module.hs
index 9ed7544f20..c31e7925d7 100644
--- a/compiler/GHC/Tc/Module.hs
+++ b/compiler/GHC/Tc/Module.hs
@@ -400,7 +400,7 @@ tcRnImports hsc_env import_decls
tcg_hpc = hpc_info
}) $ do {
- ; traceRn "rn1" (ppr (imp_dep_mods imports))
+ ; traceRn "rn1" (ppr (imp_direct_dep_mods imports))
-- Fail if there are any errors so far
-- The error printing (if needed) takes advantage
-- of the tcg_env we have now set
@@ -2951,9 +2951,7 @@ pprTcGblEnv (TcGblEnv { tcg_type_env = type_env,
, text "Dependent modules:" <+>
pprUFM (imp_direct_dep_mods imports) (ppr . sort)
, text "Dependent packages:" <+>
- ppr (S.toList $ imp_dep_pkgs imports)]
--- , text "Direct Dependent packages:" <+>
--- ppr (S.toList $ imp_dep_direct_pkgs imports)]
+ ppr (S.toList $ imp_dep_direct_pkgs imports)]
-- The use of sort is just to reduce unnecessary
-- wobbling in testsuite output
diff --git a/compiler/GHC/Tc/Types.hs b/compiler/GHC/Tc/Types.hs
index 7baf98317a..5aacaa6471 100644
--- a/compiler/GHC/Tc/Types.hs
+++ b/compiler/GHC/Tc/Types.hs
@@ -1339,25 +1339,11 @@ data ImportAvails
-- future).
imp_direct_dep_mods :: ModuleNameEnv ModuleNameWithIsBoot,
- imp_dep_mods :: ModuleNameEnv ModuleNameWithIsBoot,
- -- ^ Home-package modules needed by the module being compiled
- --
- -- It doesn't matter whether any of these dependencies
- -- are actually /used/ when compiling the module; they
- -- are listed if they are below it at all. For
- -- example, suppose M imports A which imports X. Then
- -- compiling M might not need to consult X.hi, but X
- -- is still listed in M's dependencies.
-
- imp_dep_pkgs :: Set UnitId,
- -- ^ Packages needed by the module being compiled, whether directly,
- -- or via other modules in this package, or via modules imported
- -- from other packages.
+ -- ^ Home-package modules directly imported by the module being compiled.
imp_dep_direct_pkgs :: Set UnitId,
-- ^ Packages needed by the module being compiled, whether directly,
- -- or via other modules in this package, or via modules imported
- -- from other packages.
+ -- or via other modules in this package.
imp_trust_pkgs :: Set UnitId,
-- ^ This is strictly a subset of imp_dep_pkgs and records the
@@ -1400,9 +1386,7 @@ modDepsElts = sort . nonDetEltsUFM
emptyImportAvails :: ImportAvails
emptyImportAvails = ImportAvails { imp_mods = emptyModuleEnv,
- imp_dep_mods = emptyUFM,
- imp_direct_dep_mods = emptyUFM,
- imp_dep_pkgs = S.empty,
+ imp_direct_dep_mods = emptyUFM,
imp_dep_direct_pkgs = S.empty,
imp_trust_pkgs = S.empty,
imp_trust_own_pkg = False,
@@ -1417,19 +1401,17 @@ emptyImportAvails = ImportAvails { imp_mods = emptyModuleEnv,
plusImportAvails :: ImportAvails -> ImportAvails -> ImportAvails
plusImportAvails
(ImportAvails { imp_mods = mods1,
- imp_dep_mods = dmods1, imp_direct_dep_mods = ddmods1, imp_dep_pkgs = dpkgs1,
+ imp_direct_dep_mods = ddmods1,
imp_dep_direct_pkgs = ddpkgs1,
imp_trust_pkgs = tpkgs1, imp_trust_own_pkg = tself1,
imp_orphs = orphs1, imp_finsts = finsts1 })
(ImportAvails { imp_mods = mods2,
- imp_dep_mods = dmods2, imp_direct_dep_mods = ddmods2, imp_dep_pkgs = dpkgs2,
+ imp_direct_dep_mods = ddmods2,
imp_dep_direct_pkgs = ddpkgs2,
imp_trust_pkgs = tpkgs2, imp_trust_own_pkg = tself2,
imp_orphs = orphs2, imp_finsts = finsts2 })
= ImportAvails { imp_mods = plusModuleEnv_C (++) mods1 mods2,
- imp_dep_mods = plusUFM_C plus_mod_dep dmods1 dmods2,
imp_direct_dep_mods = plusUFM_C plus_mod_dep ddmods1 ddmods2,
- imp_dep_pkgs = dpkgs1 `S.union` dpkgs2,
imp_dep_direct_pkgs = ddpkgs1 `S.union` ddpkgs2,
imp_trust_pkgs = tpkgs1 `S.union` tpkgs2,
imp_trust_own_pkg = tself1 || tself2,
diff --git a/compiler/GHC/Unit/Module/Deps.hs b/compiler/GHC/Unit/Module/Deps.hs
index e8b13e35ae..af64e36d8d 100644
--- a/compiler/GHC/Unit/Module/Deps.hs
+++ b/compiler/GHC/Unit/Module/Deps.hs
@@ -23,20 +23,16 @@ import GHC.Utils.Binary
--
-- Invariant: none of the lists contain duplicates.
data Dependencies = Deps
- { dep_mods :: [ModuleNameWithIsBoot]
- -- ^ All home-package modules transitively below this one
- -- I.e. modules that this one imports, or that are in the
- -- dep_mods of those directly-imported modules
- , dep_direct_mods :: [ModuleNameWithIsBoot]
-
- , dep_pkgs :: [(UnitId, Bool)]
- -- ^ All packages transitively below this module
- -- I.e. packages to which this module's direct imports belong,
- -- or that are in the dep_pkgs of those modules
+ { dep_direct_mods :: [ModuleNameWithIsBoot]
+ -- ^ All home-package modules which are below this one
+ -- I.e. modules that this one imports.
+
+ , dep_direct_pkgs :: [(UnitId, Bool)]
+ -- ^ All packages directly imported by this module
+ -- I.e. packages to which this module's direct imports belong.
-- The bool indicates if the package is required to be
-- trusted when the module is imported as a safe import
-- (Safe Haskell). See Note [Tracking Trust Transitively] in GHC.Rename.Names
- , dep_direct_pkgs :: [(UnitId, Bool)]
, dep_orphs :: [Module]
-- ^ Transitive closure of orphan modules (whether
@@ -63,26 +59,22 @@ data Dependencies = Deps
-- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies.
instance Binary Dependencies where
- put_ bh deps = do put_ bh (dep_mods deps)
- put_ bh (dep_direct_mods deps)
- put_ bh (dep_pkgs deps)
+ put_ bh deps = do put_ bh (dep_direct_mods deps)
put_ bh (dep_direct_pkgs deps)
put_ bh (dep_orphs deps)
put_ bh (dep_finsts deps)
put_ bh (dep_plgins deps)
- get bh = do ms <- get bh
- dms <- get bh
- ps <- get bh
+ get bh = do dms <- get bh
dps <- get bh
os <- get bh
fis <- get bh
pl <- get bh
- return (Deps { dep_mods = ms, dep_direct_mods = dms, dep_pkgs = ps, dep_direct_pkgs = dps, dep_orphs = os,
+ return (Deps { dep_direct_mods = dms, dep_direct_pkgs = dps, dep_orphs = os,
dep_finsts = fis, dep_plgins = pl })
noDependencies :: Dependencies
-noDependencies = Deps [] [] [] [] [] [] []
+noDependencies = Deps [] [] [] [] []