diff options
author | Sylvain Henry <sylvain@haskus.fr> | 2021-09-08 11:17:38 +0200 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2021-09-17 09:45:36 -0400 |
commit | c662ac7e39a0a2fb85d4ab17ae71d54752d24f39 (patch) | |
tree | 01ec2534a67671f010fb985f00fce1a4cd492f99 /compiler | |
parent | da60e6276e4b71217e2e75dfa49f2d460b526af3 (diff) | |
download | haskell-c662ac7e39a0a2fb85d4ab17ae71d54752d24f39.tar.gz |
Refactor module dependencies code
* moved deps related code into GHC.Unit.Module.Deps
* refactored Deps module to not export Dependencies constructor to help
maintaining invariants
Diffstat (limited to 'compiler')
-rw-r--r-- | compiler/GHC/Driver/Session.hs | 5 | ||||
-rw-r--r-- | compiler/GHC/HsToCore.hs | 1 | ||||
-rw-r--r-- | compiler/GHC/HsToCore/Usage.hs | 53 | ||||
-rw-r--r-- | compiler/GHC/Iface/Load.hs | 28 | ||||
-rw-r--r-- | compiler/GHC/Iface/Make.hs | 2 | ||||
-rw-r--r-- | compiler/GHC/Iface/Recomp.hs | 18 | ||||
-rw-r--r-- | compiler/GHC/Iface/Rename.hs | 13 | ||||
-rw-r--r-- | compiler/GHC/Rename/Names.hs | 15 | ||||
-rw-r--r-- | compiler/GHC/Tc/Types.hs | 74 | ||||
-rw-r--r-- | compiler/GHC/Unit/Module/Deps.hs | 183 | ||||
-rw-r--r-- | compiler/GHC/Unit/Module/ModSummary.hs | 12 |
11 files changed, 212 insertions, 192 deletions
diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs index a6f1a50382..3b28a0b17e 100644 --- a/compiler/GHC/Driver/Session.hs +++ b/compiler/GHC/Driver/Session.hs @@ -55,7 +55,6 @@ module GHC.Driver.Session ( DynLibLoader(..), fFlags, fLangFlags, xFlags, wWarningFlags, - dynFlagDependencies, makeDynFlagsConsistent, positionIndependent, optimisationFlags, @@ -1574,10 +1573,6 @@ lang_set dflags lang = setLanguage :: Language -> DynP () setLanguage l = upd (`lang_set` Just l) --- | Some modules have dependencies on others through the DynFlags rather than textual imports -dynFlagDependencies :: DynFlags -> [ModuleName] -dynFlagDependencies = pluginModNames - -- | Is the -fpackage-trust mode on packageTrustOn :: DynFlags -> Bool packageTrustOn = gopt Opt_PackageTrust diff --git a/compiler/GHC/HsToCore.hs b/compiler/GHC/HsToCore.hs index 88d1133963..2824b1fafe 100644 --- a/compiler/GHC/HsToCore.hs +++ b/compiler/GHC/HsToCore.hs @@ -86,6 +86,7 @@ import GHC.Types.HpcInfo import GHC.Unit import GHC.Unit.Module.ModGuts import GHC.Unit.Module.ModIface +import GHC.Unit.Module.Deps import Data.List (partition) import Data.IORef diff --git a/compiler/GHC/HsToCore/Usage.hs b/compiler/GHC/HsToCore/Usage.hs index c9c4214fd0..21bbc6eec1 100644 --- a/compiler/GHC/HsToCore/Usage.hs +++ b/compiler/GHC/HsToCore/Usage.hs @@ -4,7 +4,7 @@ module GHC.HsToCore.Usage ( -- * Dependency/fingerprinting code (used by GHC.Iface.Make) - mkUsageInfo, mkUsedNames, mkDependencies + mkUsageInfo, mkUsedNames, ) where import GHC.Prelude @@ -23,7 +23,6 @@ import GHC.Utils.Panic import GHC.Types.Name import GHC.Types.Name.Set ( NameSet, allUses ) import GHC.Types.Unique.Set -import GHC.Types.Unique.FM import GHC.Unit import GHC.Unit.External @@ -33,10 +32,9 @@ import GHC.Unit.Module.Deps import GHC.Data.Maybe -import Data.List (sortBy, sort, partition) +import Data.List (sortBy) import Data.Map (Map) import qualified Data.Map as Map -import qualified Data.Set as Set import GHC.Linker.Types import GHC.Linker.Loader ( getLoaderState ) @@ -61,53 +59,6 @@ its dep_orphs. This was the cause of #14128. -} --- | Extract information from the rename and typecheck phases to produce --- a dependencies information for the module being compiled. --- --- The fourth argument is a list of plugin modules. -mkDependencies :: HomeUnit -> Module -> ImportAvails -> [Module] -> Dependencies -mkDependencies home_unit mod imports plugin_mods = - let (home_plugins, external_plugins) = partition (isHomeUnit home_unit . moduleUnit) plugin_mods - plugin_units = map (toUnitId . moduleUnit) external_plugins - all_direct_mods = foldr (\mn m -> addToUFM m mn (GWIB mn NotBoot)) - (imp_direct_dep_mods imports) - (map moduleName home_plugins) - - direct_mods = modDepsElts (delFromUFM all_direct_mods (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 - -- loadHiBootInterface can see if M's direct imports depend - -- on M.hi-boot, and hence that we should do the hi-boot consistency - -- check.) - - dep_orphs = filter (/= mod) (imp_orphs imports) - -- We must also remove self-references from imp_orphs. See - -- Note [Module self-dependency] - - direct_pkgs = foldr Set.insert (imp_dep_direct_pkgs imports) plugin_units - - -- Set the packages required to be Safe according to Safe Haskell. - -- See Note [Tracking Trust Transitively] in GHC.Rename.Names - trust_pkgs = imp_trust_pkgs imports - - -- If there's a non-boot import, then it shadows the boot import - -- coming from the dependencies - source_mods = modDepsElts (imp_boot_mods imports) - - sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports - - in Deps { dep_direct_mods = direct_mods - , dep_direct_pkgs = direct_pkgs - , dep_sig_mods = sort sig_mods - , dep_trusted_pkgs = trust_pkgs - , dep_boot_mods = source_mods - , dep_orphs = dep_orphs - , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) - -- sort to get into canonical order - -- NB. remember to use lexicographic ordering - } - mkUsedNames :: TcGblEnv -> NameSet mkUsedNames TcGblEnv{ tcg_dus = dus } = allUses dus diff --git a/compiler/GHC/Iface/Load.hs b/compiler/GHC/Iface/Load.hs index dc993aa261..c271613b3d 100644 --- a/compiler/GHC/Iface/Load.hs +++ b/compiler/GHC/Iface/Load.hs @@ -115,8 +115,6 @@ import GHC.Data.FastString import Control.Monad import Data.Map ( toList ) -import qualified Data.Set as Set -import Data.Set (Set) import System.FilePath import System.Directory import GHC.Driver.Env.KnotVars @@ -1184,32 +1182,6 @@ pprUsageImport usage usg_mod' safe | usg_safe usage = text "safe" | otherwise = text " -/ " --- | Pretty-print unit dependencies -pprDeps :: UnitState -> Dependencies -> SDoc -pprDeps unit_state (Deps { dep_direct_mods = dmods - , dep_boot_mods = bmods - , dep_orphs = orphs - , dep_direct_pkgs = pkgs - , dep_trusted_pkgs = tps - , dep_finsts = finsts - }) - = pprWithUnitState unit_state $ - vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, - text "boot module dependencies:" <+> ppr_set ppr bmods, - text "direct package dependencies:" <+> ppr_set ppr pkgs, - if null tps - then empty - else text "trusted package dependencies:" <+> ppr_set ppr tps, - text "orphans:" <+> fsep (map ppr orphs), - text "family instance modules:" <+> fsep (map ppr finsts) - ] - where - ppr_mod (GWIB mod IsBoot) = ppr mod <+> text "[boot]" - ppr_mod (GWIB mod NotBoot) = ppr mod - - ppr_set :: Outputable a => (a -> SDoc) -> Set a -> SDoc - ppr_set w = fsep . fmap w . Set.toAscList - pprFixities :: [(OccName, Fixity)] -> SDoc pprFixities [] = Outputable.empty pprFixities fixes = text "fixities" <+> pprWithCommas pprFix fixes diff --git a/compiler/GHC/Iface/Make.hs b/compiler/GHC/Iface/Make.hs index ed113ef7fd..b28e777a88 100644 --- a/compiler/GHC/Iface/Make.hs +++ b/compiler/GHC/Iface/Make.hs @@ -82,7 +82,7 @@ import GHC.Data.FastString import GHC.Data.Maybe import GHC.HsToCore.Docs -import GHC.HsToCore.Usage ( mkUsageInfo, mkUsedNames, mkDependencies ) +import GHC.HsToCore.Usage ( mkUsageInfo, mkUsedNames ) import GHC.Unit import GHC.Unit.Module.Warnings diff --git a/compiler/GHC/Iface/Recomp.hs b/compiler/GHC/Iface/Recomp.hs index 0abee1a5c0..918460a236 100644 --- a/compiler/GHC/Iface/Recomp.hs +++ b/compiler/GHC/Iface/Recomp.hs @@ -973,11 +973,11 @@ addFingerprints hsc_env iface0 (local_env, decls_w_hashes) <- foldM fingerprint_group (emptyOccEnv, []) groups - -- when calculating fingerprints, we always need to use canonical - -- ordering for lists of things. In particular, the mi_deps has various - -- lists of modules and suchlike, so put these all in canonical order: + -- when calculating fingerprints, we always need to use canonical ordering + -- for lists of things. The mi_deps has various lists of modules and + -- suchlike, which are stored in canonical order: let sorted_deps :: Dependencies - sorted_deps = sortDependencies (mi_deps iface0) + sorted_deps = mi_deps iface0 -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way @@ -1193,16 +1193,6 @@ getOrphanHashes hsc_env mods = do mapM get_orph_hash mods -sortDependencies :: Dependencies -> Dependencies -sortDependencies d - = Deps { dep_direct_mods = dep_direct_mods d, - dep_direct_pkgs = dep_direct_pkgs d, - dep_sig_mods = sort (dep_sig_mods d), - dep_trusted_pkgs = dep_trusted_pkgs d, - dep_boot_mods = dep_boot_mods d, - dep_orphs = sortBy stableModuleCmp (dep_orphs d), - dep_finsts = sortBy stableModuleCmp (dep_finsts d) } - {- ************************************************************************ * * diff --git a/compiler/GHC/Iface/Rename.hs b/compiler/GHC/Iface/Rename.hs index e2a89570d3..fdbe0dd55a 100644 --- a/compiler/GHC/Iface/Rename.hs +++ b/compiler/GHC/Iface/Rename.hs @@ -128,19 +128,18 @@ rnModExports hsc_env insts iface $ mapM rnAvailInfo (mi_exports iface) rnDependencies :: Rename Dependencies -rnDependencies deps = do - orphs <- rnDepModules dep_orphs deps - finsts <- rnDepModules dep_finsts deps - return deps { dep_orphs = orphs, dep_finsts = finsts } +rnDependencies deps0 = do + deps1 <- dep_orphs_update deps0 (rnDepModules dep_orphs) + dep_finsts_update deps1 (rnDepModules dep_finsts) -rnDepModules :: (Dependencies -> [Module]) -> Dependencies -> ShIfM [Module] -rnDepModules sel deps = do +rnDepModules :: (Dependencies -> [Module]) -> [Module] -> ShIfM [Module] +rnDepModules sel mods = do hsc_env <- getTopEnv hmap <- getHoleSubst -- NB: It's not necessary to test if we're doing signature renaming, -- because ModIface will never contain module reference for itself -- in these dependencies. - fmap (nubSort . concat) . T.forM (sel deps) $ \mod -> do + fmap (nubSort . concat) . T.forM mods $ \mod -> do -- For holes, its necessary to "see through" the instantiation -- of the hole to get accurate family instance dependencies. -- For example, if B imports <A>, and <A> is instantiated with diff --git a/compiler/GHC/Rename/Names.hs b/compiler/GHC/Rename/Names.hs index b7dd191aa0..9c9781aa9d 100644 --- a/compiler/GHC/Rename/Names.hs +++ b/compiler/GHC/Rename/Names.hs @@ -477,13 +477,16 @@ calculateAvails home_unit iface mod_safe' want_boot imported_by = -- 'imp_finsts' if it defines an orphan or instance family; thus the -- orph_iface/has_iface tests. - orphans | orph_iface = assertPpr (not (imp_sem_mod `elem` dep_orphs deps)) (ppr imp_sem_mod <+> ppr (dep_orphs deps)) $ - imp_sem_mod : dep_orphs deps - | otherwise = dep_orphs deps + deporphs = dep_orphs deps + depfinsts = dep_finsts deps - finsts | has_finsts = assertPpr (not (imp_sem_mod `elem` dep_finsts deps)) (ppr imp_sem_mod <+> ppr (dep_orphs deps)) $ - imp_sem_mod : dep_finsts deps - | otherwise = dep_finsts deps + orphans | orph_iface = assertPpr (not (imp_sem_mod `elem` deporphs)) (ppr imp_sem_mod <+> ppr deporphs) $ + imp_sem_mod : deporphs + | otherwise = deporphs + + finsts | has_finsts = assertPpr (not (imp_sem_mod `elem` depfinsts)) (ppr imp_sem_mod <+> ppr depfinsts) $ + imp_sem_mod : depfinsts + | otherwise = depfinsts -- Trusted packages are a lot like orphans. trusted_pkgs | mod_safe' = dep_trusted_pkgs deps diff --git a/compiler/GHC/Tc/Types.hs b/compiler/GHC/Tc/Types.hs index 34d2c2e578..f89949d1f8 100644 --- a/compiler/GHC/Tc/Types.hs +++ b/compiler/GHC/Tc/Types.hs @@ -42,7 +42,7 @@ module GHC.Tc.Types( -- Renamer types ErrCtxt, RecFieldEnv, pushErrCtxt, pushErrCtxtSameOrigin, ImportAvails(..), emptyImportAvails, plusImportAvails, - WhereFrom(..), mkModDeps, modDepsElts, + WhereFrom(..), mkModDeps, -- Typechecker types TcTypeEnv, TcBinderStack, TcBinder(..), @@ -146,7 +146,7 @@ import GHC.Data.List.SetOps import GHC.Unit import GHC.Unit.Module.Warnings -import GHC.Unit.Module.Imported +import GHC.Unit.Module.Deps import GHC.Unit.Module.ModDetails import GHC.Utils.Error @@ -1365,69 +1365,6 @@ peCategory NoDataKindsDC = "data constructor" ************************************************************************ -} --- | 'ImportAvails' summarises what was imported from where, irrespective of --- whether the imported things are actually used or not. It is used: --- --- * when processing the export list, --- --- * when constructing usage info for the interface file, --- --- * to identify the list of directly imported modules for initialisation --- purposes and for optimised overlap checking of family instances, --- --- * when figuring out what things are really unused --- -data ImportAvails - = ImportAvails { - imp_mods :: ImportedMods, - -- = ModuleEnv [ImportedModsVal], - -- ^ Domain is all directly-imported modules - -- - -- See the documentation on ImportedModsVal in - -- "GHC.Unit.Module.Imported" for the meaning of the fields. - -- - -- We need a full ModuleEnv rather than a ModuleNameEnv here, - -- because we might be importing modules of the same name from - -- different packages. (currently not the case, but might be in the - -- future). - - imp_direct_dep_mods :: ModuleNameEnv ModuleNameWithIsBoot, - -- ^ Home-package modules directly imported by the module being compiled. - - imp_dep_direct_pkgs :: Set UnitId, - -- ^ Packages directly needed by the module being compiled - - imp_trust_own_pkg :: Bool, - -- ^ Do we require that our own package is trusted? - -- This is to handle efficiently the case where a Safe module imports - -- a Trustworthy module that resides in the same package as it. - -- See Note [Trust Own Package] in "GHC.Rename.Names" - - -- Transitive information below here - - imp_trust_pkgs :: Set UnitId, - -- ^ This records the - -- packages the current module needs to trust for Safe Haskell - -- compilation to succeed. A package is required to be trusted if - -- we are dependent on a trustworthy module in that package. - -- See Note [Tracking Trust Transitively] in "GHC.Rename.Names" - - imp_boot_mods :: ModuleNameEnv ModuleNameWithIsBoot, - -- ^ Domain is all modules which have hs-boot files, and whether - -- we should import the boot version of interface file. Only used - -- in one-shot mode to populate eps_is_boot. - - imp_sig_mods :: [ModuleName], - -- ^ Signature modules below this one - - imp_orphs :: [Module], - -- ^ Orphan modules below us in the import tree (and maybe including - -- us for imported modules) - - imp_finsts :: [Module] - -- ^ Family instance modules below us in the import tree (and maybe - -- including us for imported modules) - } mkModDeps :: Set ModuleNameWithIsBoot -> ModuleNameEnv ModuleNameWithIsBoot @@ -1449,13 +1386,6 @@ plusModDeps = plusUFM_C plus_mod_dep -- Reusing existing tuples saves 10% of allocations on test -- perf/compiler/MultiLayerModules -modDepsElts - :: ModuleNameEnv ModuleNameWithIsBoot - -> Set ModuleNameWithIsBoot -modDepsElts = S.fromList . nonDetEltsUFM - -- It's OK to use nonDetEltsUFM here because sorting by module names - -- restores determinism - emptyImportAvails :: ImportAvails emptyImportAvails = ImportAvails { imp_mods = emptyModuleEnv, imp_direct_dep_mods = emptyUFM, diff --git a/compiler/GHC/Unit/Module/Deps.hs b/compiler/GHC/Unit/Module/Deps.hs index ebdd4b351f..c3c3340f41 100644 --- a/compiler/GHC/Unit/Module/Deps.hs +++ b/compiler/GHC/Unit/Module/Deps.hs @@ -1,8 +1,20 @@ -- | Dependencies and Usage of a module module GHC.Unit.Module.Deps - ( Dependencies (..) - , Usage (..) + ( Dependencies + , mkDependencies , noDependencies + , dep_direct_mods + , dep_direct_pkgs + , dep_sig_mods + , dep_trusted_pkgs + , dep_orphs + , dep_finsts + , dep_boot_mods + , dep_orphs_update + , dep_finsts_update + , pprDeps + , Usage (..) + , ImportAvails (..) ) where @@ -10,12 +22,19 @@ import GHC.Prelude import GHC.Types.SafeHaskell import GHC.Types.Name +import GHC.Types.Unique.FM + import GHC.Unit.Module.Name +import GHC.Unit.Module.Imported import GHC.Unit.Module +import GHC.Unit.Home +import GHC.Unit.State import GHC.Utils.Fingerprint import GHC.Utils.Binary +import GHC.Utils.Outputable +import Data.List (sortBy, sort, partition) import Data.Set (Set) import qualified Data.Set as Set @@ -26,6 +45,8 @@ import qualified Data.Set as Set -- -- Invariant: none of the lists contain duplicates. -- +-- Invariant: lists are ordered canonically (e.g. using stableModuleCmp) +-- -- See Note [Transitive Information in Dependencies] data Dependencies = Deps { dep_direct_mods :: Set ModuleNameWithIsBoot @@ -34,9 +55,10 @@ data Dependencies = Deps , dep_direct_pkgs :: Set UnitId -- ^ All packages directly imported by this module -- I.e. packages to which this module's direct imports belong. - -- + ------------------------------------ -- Transitive information below here + , dep_sig_mods :: ![ModuleName] -- ^ Transitive closure of hsig files in the home package @@ -74,6 +96,71 @@ data Dependencies = Deps -- Equality used only for old/new comparison in GHC.Iface.Recomp.addFingerprints -- See 'GHC.Tc.Utils.ImportAvails' for details on dependencies. + +-- | Extract information from the rename and typecheck phases to produce +-- a dependencies information for the module being compiled. +-- +-- The fourth argument is a list of plugin modules. +mkDependencies :: HomeUnit -> Module -> ImportAvails -> [Module] -> Dependencies +mkDependencies home_unit mod imports plugin_mods = + let (home_plugins, external_plugins) = partition (isHomeUnit home_unit . moduleUnit) plugin_mods + plugin_units = Set.fromList (map (toUnitId . moduleUnit) external_plugins) + all_direct_mods = foldr (\mn m -> addToUFM m mn (GWIB mn NotBoot)) + (imp_direct_dep_mods imports) + (map moduleName home_plugins) + + modDepsElts = Set.fromList . nonDetEltsUFM + -- It's OK to use nonDetEltsUFM here because sorting by module names + -- restores determinism + + direct_mods = modDepsElts (delFromUFM all_direct_mods (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 + -- loadHiBootInterface can see if M's direct imports depend + -- on M.hi-boot, and hence that we should do the hi-boot consistency + -- check.) + + dep_orphs = filter (/= mod) (imp_orphs imports) + -- We must also remove self-references from imp_orphs. See + -- Note [Module self-dependency] + + direct_pkgs = foldr Set.insert (imp_dep_direct_pkgs imports) plugin_units + + -- Set the packages required to be Safe according to Safe Haskell. + -- See Note [Tracking Trust Transitively] in GHC.Rename.Names + trust_pkgs = imp_trust_pkgs imports + + -- If there's a non-boot import, then it shadows the boot import + -- coming from the dependencies + source_mods = modDepsElts (imp_boot_mods imports) + + sig_mods = filter (/= (moduleName mod)) $ imp_sig_mods imports + + in Deps { dep_direct_mods = direct_mods + , dep_direct_pkgs = direct_pkgs + , dep_sig_mods = sort sig_mods + , dep_trusted_pkgs = trust_pkgs + , dep_boot_mods = source_mods + , dep_orphs = sortBy stableModuleCmp dep_orphs + , dep_finsts = sortBy stableModuleCmp (imp_finsts imports) + -- sort to get into canonical order + -- NB. remember to use lexicographic ordering + } + +-- | Update module dependencies containing orphans (used by Backpack) +dep_orphs_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies +dep_orphs_update deps f = do + r <- f (dep_orphs deps) + pure (deps { dep_orphs = sortBy stableModuleCmp r }) + +-- | Update module dependencies containing family instances (used by Backpack) +dep_finsts_update :: Monad m => Dependencies -> ([Module] -> m [Module]) -> m Dependencies +dep_finsts_update deps f = do + r <- f (dep_finsts deps) + pure (deps { dep_finsts = sortBy stableModuleCmp r }) + + instance Binary Dependencies where put_ bh deps = do put_ bh (dep_direct_mods deps) put_ bh (dep_direct_pkgs deps) @@ -109,6 +196,32 @@ noDependencies = Deps , dep_finsts = [] } +-- | Pretty-print unit dependencies +pprDeps :: UnitState -> Dependencies -> SDoc +pprDeps unit_state (Deps { dep_direct_mods = dmods + , dep_boot_mods = bmods + , dep_orphs = orphs + , dep_direct_pkgs = pkgs + , dep_trusted_pkgs = tps + , dep_finsts = finsts + }) + = pprWithUnitState unit_state $ + vcat [text "direct module dependencies:" <+> ppr_set ppr_mod dmods, + text "boot module dependencies:" <+> ppr_set ppr bmods, + text "direct package dependencies:" <+> ppr_set ppr pkgs, + if null tps + then empty + else text "trusted package dependencies:" <+> ppr_set ppr tps, + text "orphans:" <+> fsep (map ppr orphs), + text "family instance modules:" <+> fsep (map ppr finsts) + ] + where + ppr_mod (GWIB mod IsBoot) = ppr mod <+> text "[boot]" + ppr_mod (GWIB mod NotBoot) = ppr mod + + ppr_set :: Outputable a => (a -> SDoc) -> Set a -> SDoc + ppr_set w = fsep . fmap w . Set.toAscList + -- | Records modules for which changes may force recompilation of this module -- See wiki: https://gitlab.haskell.org/ghc/ghc/wikis/commentary/compiler/recompilation-avoidance -- @@ -327,3 +440,67 @@ Question: does this happen even across packages? No: if I need to load the interface for module X from package P I always look for p:X.hi. -} + +-- | 'ImportAvails' summarises what was imported from where, irrespective of +-- whether the imported things are actually used or not. It is used: +-- +-- * when processing the export list, +-- +-- * when constructing usage info for the interface file, +-- +-- * to identify the list of directly imported modules for initialisation +-- purposes and for optimised overlap checking of family instances, +-- +-- * when figuring out what things are really unused +-- +data ImportAvails + = ImportAvails { + imp_mods :: ImportedMods, + -- = ModuleEnv [ImportedModsVal], + -- ^ Domain is all directly-imported modules + -- + -- See the documentation on ImportedModsVal in + -- "GHC.Unit.Module.Imported" for the meaning of the fields. + -- + -- We need a full ModuleEnv rather than a ModuleNameEnv here, + -- because we might be importing modules of the same name from + -- different packages. (currently not the case, but might be in the + -- future). + + imp_direct_dep_mods :: ModuleNameEnv ModuleNameWithIsBoot, + -- ^ Home-package modules directly imported by the module being compiled. + + imp_dep_direct_pkgs :: Set UnitId, + -- ^ Packages directly needed by the module being compiled + + imp_trust_own_pkg :: Bool, + -- ^ Do we require that our own package is trusted? + -- This is to handle efficiently the case where a Safe module imports + -- a Trustworthy module that resides in the same package as it. + -- See Note [Trust Own Package] in "GHC.Rename.Names" + + -- Transitive information below here + + imp_trust_pkgs :: Set UnitId, + -- ^ This records the + -- packages the current module needs to trust for Safe Haskell + -- compilation to succeed. A package is required to be trusted if + -- we are dependent on a trustworthy module in that package. + -- See Note [Tracking Trust Transitively] in "GHC.Rename.Names" + + imp_boot_mods :: ModuleNameEnv ModuleNameWithIsBoot, + -- ^ Domain is all modules which have hs-boot files, and whether + -- we should import the boot version of interface file. Only used + -- in one-shot mode to populate eps_is_boot. + + imp_sig_mods :: [ModuleName], + -- ^ Signature modules below this one + + imp_orphs :: [Module], + -- ^ Orphan modules below us in the import tree (and maybe including + -- us for imported modules) + + imp_finsts :: [Module] + -- ^ Family instance modules below us in the import tree (and maybe + -- including us for imported modules) + } diff --git a/compiler/GHC/Unit/Module/ModSummary.hs b/compiler/GHC/Unit/Module/ModSummary.hs index ba59655033..c584385aef 100644 --- a/compiler/GHC/Unit/Module/ModSummary.hs +++ b/compiler/GHC/Unit/Module/ModSummary.hs @@ -1,4 +1,5 @@ {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE TupleSections #-} -- | A ModSummary is a node in the compilation manager's dependency graph -- (ModuleGraph) @@ -10,6 +11,7 @@ module GHC.Unit.Module.ModSummary , ms_installed_mod , ms_mod_name , ms_imps + , ms_plugin_imps , ms_mnwib , ms_home_srcimps , ms_home_imps @@ -114,11 +116,11 @@ ms_mod_name = moduleName . ms_mod -- | Textual imports, plus plugin imports but not SOURCE imports. ms_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)] -ms_imps ms = - ms_textual_imps ms ++ - map mk_additional_import (dynFlagDependencies (ms_hspp_opts ms)) - where - mk_additional_import mod_nm = (Nothing, noLoc mod_nm) +ms_imps ms = ms_textual_imps ms ++ ms_plugin_imps ms + +-- | Plugin imports +ms_plugin_imps :: ModSummary -> [(Maybe FastString, Located ModuleName)] +ms_plugin_imps ms = map ((Nothing,) . noLoc) (pluginModNames (ms_hspp_opts ms)) home_imps :: [(Maybe FastString, Located ModuleName)] -> [Located ModuleName] home_imps imps = [ lmodname | (mb_pkg, lmodname) <- imps, |