Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
-
d47bf776
by Matthew Pickering at 2025-04-14T16:44:41+01:00
26 changed files:
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeAction.hs
- + compiler/GHC/Driver/Messager.hs
- compiler/GHC/Driver/Pipeline.hs-boot
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Unit/External.hs
- compiler/GHC/Unit/Finder.hs
- − compiler/GHC/Unit/Module/External/Graph.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/ModNodeKey.hs
- compiler/ghc.cabal.in
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.hs
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.stdout
- testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/plugins/defaulting-plugin/DefaultLifted.hs
Changes:
| ... | ... | @@ -10,9 +10,14 @@ |
| 10 | 10 | {-# LANGUAGE ViewPatterns #-}
|
| 11 | 11 | module GHC.Driver.Downsweep
|
| 12 | 12 | ( downsweep
|
| 13 | + , downsweepThunk
|
|
| 14 | + , downsweepInstalledModules
|
|
| 15 | + , downsweepFromRootNodes
|
|
| 16 | + , DownsweepMode(..)
|
|
| 13 | 17 | -- * Summary functions
|
| 14 | 18 | , summariseModule
|
| 15 | 19 | , summariseFile
|
| 20 | + , summariseModuleInterface
|
|
| 16 | 21 | , SummariseResult(..)
|
| 17 | 22 | -- * Helper functions
|
| 18 | 23 | , instantiationNodes
|
| ... | ... | @@ -21,33 +26,37 @@ module GHC.Driver.Downsweep |
| 21 | 26 | |
| 22 | 27 | import GHC.Prelude
|
| 23 | 28 | |
| 24 | -import GHC.Tc.Utils.Backpack
|
|
| 25 | - |
|
| 26 | - |
|
| 27 | 29 | import GHC.Platform.Ways
|
| 28 | 30 | |
| 29 | 31 | import GHC.Driver.Config.Finder (initFinderOpts)
|
| 30 | 32 | import GHC.Driver.Config.Parser (initParserOpts)
|
| 31 | 33 | import GHC.Driver.Phases
|
| 32 | -import GHC.Driver.Pipeline
|
|
| 34 | +import {-# SOURCE #-} GHC.Driver.Pipeline (preprocess)
|
|
| 33 | 35 | import GHC.Driver.Session
|
| 34 | 36 | import GHC.Driver.Backend
|
| 35 | 37 | import GHC.Driver.Monad
|
| 36 | 38 | import GHC.Driver.Env
|
| 37 | 39 | import GHC.Driver.Errors
|
| 38 | 40 | import GHC.Driver.Errors.Types
|
| 39 | -import GHC.Driver.Main
|
|
| 41 | +import GHC.Driver.Messager
|
|
| 40 | 42 | import GHC.Driver.MakeSem
|
| 41 | 43 | import GHC.Driver.MakeAction
|
| 44 | +import GHC.Driver.Config.Diagnostic
|
|
| 45 | +import GHC.Driver.Ppr
|
|
| 42 | 46 | |
| 43 | -import GHC.Parser.Header
|
|
| 47 | +import GHC.Iface.Load
|
|
| 44 | 48 | |
| 49 | +import GHC.Parser.Header
|
|
| 50 | +import GHC.Rename.Names
|
|
| 51 | +import GHC.Tc.Utils.Backpack
|
|
| 45 | 52 | |
| 46 | 53 | import GHC.Data.Graph.Directed
|
| 47 | 54 | import GHC.Data.FastString
|
| 48 | 55 | import GHC.Data.Maybe ( expectJust )
|
| 56 | +import qualified GHC.Data.Maybe as M
|
|
| 49 | 57 | import GHC.Data.OsPath ( unsafeEncodeUtf )
|
| 50 | 58 | import GHC.Data.StringBuffer
|
| 59 | +import GHC.Data.Graph.Directed.Reachability
|
|
| 51 | 60 | import qualified GHC.LanguageExtensions as LangExt
|
| 52 | 61 | |
| 53 | 62 | import GHC.Utils.Exception ( throwIO, SomeAsyncException )
|
| ... | ... | @@ -58,6 +67,7 @@ import GHC.Utils.Error |
| 58 | 67 | import GHC.Utils.Logger
|
| 59 | 68 | import GHC.Utils.Fingerprint
|
| 60 | 69 | import GHC.Utils.TmpFs
|
| 70 | +import GHC.Utils.Constants
|
|
| 61 | 71 | |
| 62 | 72 | import GHC.Types.Error
|
| 63 | 73 | import GHC.Types.Target
|
| ... | ... | @@ -71,7 +81,10 @@ import GHC.Unit |
| 71 | 81 | import GHC.Unit.Env
|
| 72 | 82 | import GHC.Unit.Finder
|
| 73 | 83 | import GHC.Unit.Module.ModSummary
|
| 84 | +import GHC.Unit.Module.ModIface
|
|
| 74 | 85 | import GHC.Unit.Module.Graph
|
| 86 | +import GHC.Unit.Module.Deps
|
|
| 87 | +import qualified GHC.Unit.Home.Graph as HUG
|
|
| 75 | 88 | |
| 76 | 89 | import Data.Either ( rights, partitionEithers, lefts )
|
| 77 | 90 | import qualified Data.Map as Map
|
| ... | ... | @@ -82,6 +95,7 @@ import Control.Monad |
| 82 | 95 | import Control.Monad.Trans.Except ( ExceptT(..), runExceptT, throwE )
|
| 83 | 96 | import qualified Control.Monad.Catch as MC
|
| 84 | 97 | import Data.Maybe
|
| 98 | +import Data.List (partition)
|
|
| 85 | 99 | import Data.Time
|
| 86 | 100 | import Data.List (unfoldr)
|
| 87 | 101 | import Data.Bifunctor (first)
|
| ... | ... | @@ -91,19 +105,45 @@ import System.FilePath |
| 91 | 105 | import Control.Monad.Trans.Reader
|
| 92 | 106 | import qualified Data.Map.Strict as M
|
| 93 | 107 | import Control.Monad.Trans.Class
|
| 94 | -import GHC.Rename.Names
|
|
| 95 | -import GHC.Utils.Constants
|
|
| 108 | +import System.IO.Unsafe (unsafeInterleaveIO)
|
|
| 96 | 109 | |
| 97 | -import GHC.Data.Graph.Directed.Reachability
|
|
| 98 | -import qualified GHC.Unit.Home.Graph as HUG
|
|
| 110 | +{-
|
|
| 111 | +Note [Downsweep and the ModuleGraph]
|
|
| 112 | +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 113 | + |
|
| 114 | +The ModuleGraph stores the relationship between all the modules, units, and
|
|
| 115 | +instantiations in the current session.
|
|
| 116 | + |
|
| 117 | +When we do downsweep, we build up a new ModuleGraph, starting from the root
|
|
| 118 | +modules. By following all the dependencies we construct a graph which allows
|
|
| 119 | +us to answer questions about the transitive closure of the imports.
|
|
| 120 | + |
|
| 121 | +The module graph is accessible in the HscEnv.
|
|
| 122 | + |
|
| 123 | +When is this graph constructed?
|
|
| 124 | + |
|
| 125 | +1. In `--make` mode, we construct the graph before starting to do any compilation.
|
|
| 126 | + |
|
| 127 | +2. In `-c` (oneshot) mode, we construct the graph when we have calculated the
|
|
| 128 | + ModSummary for the module we are compiling. The `ModuleGraph` is stored in a
|
|
| 129 | + thunk, so it is only constructed when it is needed. This avoids reading
|
|
| 130 | + the interface files of the whole transitive closure unless they are needed.
|
|
| 131 | + |
|
| 132 | +3. In some situations (such as loading plugins) we may need to construct the
|
|
| 133 | + graph without having a ModSummary. In this case we use the `downsweepInstalledModules`
|
|
| 134 | + function.
|
|
| 135 | + |
|
| 136 | +The result is having a uniform graph available for the whole compilation pipeline.
|
|
| 137 | + |
|
| 138 | +-}
|
|
| 99 | 139 | |
| 100 | 140 | -- This caches the answer to the question, if we are in this unit, what does
|
| 101 | 141 | -- an import of this module mean.
|
| 102 | -type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either DriverMessages ModSummary]
|
|
| 142 | +type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either DriverMessages ModuleNodeInfo]
|
|
| 103 | 143 | |
| 104 | 144 | -----------------------------------------------------------------------------
|
| 105 | 145 | --
|
| 106 | --- | Downsweep (dependency analysis)
|
|
| 146 | +-- | Downsweep (dependency analysis) for --make mode
|
|
| 107 | 147 | --
|
| 108 | 148 | -- Chase downwards from the specified root set, returning summaries
|
| 109 | 149 | -- for all home modules encountered. Only follow source-import
|
| ... | ... | @@ -113,9 +153,15 @@ type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either Driv |
| 113 | 153 | -- cache to avoid recalculating a module summary if the source is
|
| 114 | 154 | -- unchanged.
|
| 115 | 155 | --
|
| 116 | --- The returned list of [ModSummary] nodes has one node for each home-package
|
|
| 156 | +-- The returned ModuleGraph has one node for each home-package
|
|
| 117 | 157 | -- module, plus one for any hs-boot files. The imports of these nodes
|
| 118 | 158 | -- are all there, including the imports of non-home-package modules.
|
| 159 | +--
|
|
| 160 | +-- This function is intendned for use by --make mode and will also insert
|
|
| 161 | +-- LinkNodes and InstantiationNodes for any home units.
|
|
| 162 | +--
|
|
| 163 | +-- It will also turn on code generation for any modules that need it by calling
|
|
| 164 | +-- 'enableCodeGenForTH'.
|
|
| 119 | 165 | downsweep :: HscEnv
|
| 120 | 166 | -> (GhcMessage -> AnyGhcDiagnostic)
|
| 121 | 167 | -> Maybe Messager
|
| ... | ... | @@ -132,8 +178,31 @@ downsweep :: HscEnv |
| 132 | 178 | -- which case there can be repeats
|
| 133 | 179 | downsweep hsc_env diag_wrapper msg old_summaries excl_mods allow_dup_roots = do
|
| 134 | 180 | n_jobs <- mkWorkerLimit (hsc_dflags hsc_env)
|
| 135 | - new <- rootSummariesParallel n_jobs hsc_env diag_wrapper msg summary
|
|
| 136 | - downsweep_imports hsc_env old_summary_map excl_mods allow_dup_roots new
|
|
| 181 | + (root_errs, root_summaries) <- rootSummariesParallel n_jobs hsc_env diag_wrapper msg summary
|
|
| 182 | + let closure_errs = checkHomeUnitsClosed unit_env
|
|
| 183 | + unit_env = hsc_unit_env hsc_env
|
|
| 184 | + |
|
| 185 | + all_errs = closure_errs ++ root_errs
|
|
| 186 | + |
|
| 187 | + case all_errs of
|
|
| 188 | + [] -> do
|
|
| 189 | + (downsweep_errs, downsweep_nodes) <- downsweepFromRootNodes hsc_env old_summary_map excl_mods allow_dup_roots DownsweepUseCompile (map ModuleNodeCompile root_summaries) []
|
|
| 190 | + |
|
| 191 | + let (other_errs, unit_nodes) = partitionEithers $ HUG.unitEnv_foldWithKey (\nodes uid hue -> nodes ++ unitModuleNodes downsweep_nodes uid hue) [] (hsc_HUG hsc_env)
|
|
| 192 | + |
|
| 193 | + let all_nodes = downsweep_nodes ++ unit_nodes
|
|
| 194 | + let all_errs = downsweep_errs ++ other_errs
|
|
| 195 | + |
|
| 196 | + let logger = hsc_logger hsc_env
|
|
| 197 | + tmpfs = hsc_tmpfs hsc_env
|
|
| 198 | + -- if we have been passed -fno-code, we enable code generation
|
|
| 199 | + -- for dependencies of modules that have -XTemplateHaskell,
|
|
| 200 | + -- otherwise those modules will fail to compile.
|
|
| 201 | + -- See Note [-fno-code mode] #8025
|
|
| 202 | + th_configured_nodes <- enableCodeGenForTH logger tmpfs unit_env all_nodes
|
|
| 203 | + |
|
| 204 | + return (all_errs, th_configured_nodes)
|
|
| 205 | + _ -> return (all_errs, emptyMG)
|
|
| 137 | 206 | where
|
| 138 | 207 | summary = getRootSummary excl_mods old_summary_map
|
| 139 | 208 | |
| ... | ... | @@ -146,47 +215,102 @@ downsweep hsc_env diag_wrapper msg old_summaries excl_mods allow_dup_roots = do |
| 146 | 215 | old_summary_map =
|
| 147 | 216 | M.fromList [((ms_unitid ms, msHsFilePath ms), ms) | ms <- old_summaries]
|
| 148 | 217 | |
| 149 | -downsweep_imports :: HscEnv
|
|
| 218 | + -- Dependencies arising on a unit (backpack and module linking deps)
|
|
| 219 | + unitModuleNodes :: [ModuleGraphNode] -> UnitId -> HomeUnitEnv -> [Either (Messages DriverMessage) ModuleGraphNode]
|
|
| 220 | + unitModuleNodes summaries uid hue =
|
|
| 221 | + maybeToList (linkNodes summaries uid hue)
|
|
| 222 | + |
|
| 223 | +-- | Calculate the module graph starting from a single ModSummary. The result is a
|
|
| 224 | +-- thunk, which when forced will perform the downsweep. This is useful in oneshot
|
|
| 225 | +-- mode where the module graph may never be needed.
|
|
| 226 | +-- If downsweep fails, then the resulting errors are just thrown.
|
|
| 227 | +downsweepThunk :: HscEnv -> ModSummary -> IO ModuleGraph
|
|
| 228 | +downsweepThunk hsc_env mod_summary = unsafeInterleaveIO $ do
|
|
| 229 | + debugTraceMsg (hsc_logger hsc_env) 3 $ text "Computing Module Graph thunk..."
|
|
| 230 | + ~(errs, mg) <- downsweepFromRootNodes hsc_env mempty [] True DownsweepUseFixed [ModuleNodeCompile mod_summary] []
|
|
| 231 | + let dflags = hsc_dflags hsc_env
|
|
| 232 | + liftIO $ printOrThrowDiagnostics (hsc_logger hsc_env)
|
|
| 233 | + (initPrintConfig dflags)
|
|
| 234 | + (initDiagOpts dflags)
|
|
| 235 | + (GhcDriverMessage <$> unionManyMessages errs)
|
|
| 236 | + return (mkModuleGraph mg)
|
|
| 237 | + |
|
| 238 | +-- | Create a module graph from a list of installed modules.
|
|
| 239 | +-- This is used by the loader when we need to load modules but there
|
|
| 240 | +-- isn't already an existing module graph. For example, when loading plugins
|
|
| 241 | +-- during initialisation.
|
|
| 242 | +--
|
|
| 243 | +-- If you call this function, then if the `Module` you request to downsweep can't
|
|
| 244 | +-- be found then this function will throw errors.
|
|
| 245 | +-- If you need to use this function elsewhere, then it would make sense to make it
|
|
| 246 | +-- return [DriverMessages] and [ModuleGraph] so that the caller can handle the errors as it sees fit.
|
|
| 247 | +-- At the moment, it is overfitted for what `get_reachable_nodes` needs.
|
|
| 248 | +downsweepInstalledModules :: HscEnv -> [Module] -> IO ModuleGraph
|
|
| 249 | +downsweepInstalledModules hsc_env mods = do
|
|
| 250 | + let
|
|
| 251 | + (home_mods, external_mods) = partition (\u -> moduleUnitId u `elem` hsc_all_home_unit_ids hsc_env) mods
|
|
| 252 | + installed_mods = map (fst . getModuleInstantiation) home_mods
|
|
| 253 | + external_uids = map moduleUnitId external_mods
|
|
| 254 | + |
|
| 255 | + process :: InstalledModule -> IO ModuleNodeInfo
|
|
| 256 | + process i = do
|
|
| 257 | + res <- findExactModule hsc_env i NotBoot
|
|
| 258 | + case res of
|
|
| 259 | + InstalledFound loc -> return $ ModuleNodeFixed (installedModuleToMnk i) loc
|
|
| 260 | + -- It is an internal-ish error if this happens, since we any call to this function should
|
|
| 261 | + -- already know that we can find the modules we need to load.
|
|
| 262 | + _ -> throwGhcException $ ProgramError $ showSDoc (hsc_dflags hsc_env) $ text "downsweepInstalledModules: Could not find installed module" <+> ppr i
|
|
| 263 | + |
|
| 264 | + nodes <- mapM process installed_mods
|
|
| 265 | + (errs, mg) <- downsweepFromRootNodes hsc_env mempty [] True DownsweepUseFixed nodes external_uids
|
|
| 266 | + |
|
| 267 | + -- Similarly here, we should really not get any errors, but print them out if we do.
|
|
| 268 | + let dflags = hsc_dflags hsc_env
|
|
| 269 | + liftIO $ printOrThrowDiagnostics (hsc_logger hsc_env)
|
|
| 270 | + (initPrintConfig dflags)
|
|
| 271 | + (initDiagOpts dflags)
|
|
| 272 | + (GhcDriverMessage <$> unionManyMessages errs)
|
|
| 273 | + |
|
| 274 | + return (mkModuleGraph mg)
|
|
| 275 | + |
|
| 276 | + |
|
| 277 | + |
|
| 278 | +-- | Whether downsweep should use compiler or fixed nodes. Compile nodes are used
|
|
| 279 | +-- by --make mode, and fixed nodes by oneshot mode.
|
|
| 280 | +--
|
|
| 281 | +-- See Note [Module Types in the ModuleGraph] for the difference between the two.
|
|
| 282 | +data DownsweepMode = DownsweepUseCompile | DownsweepUseFixed
|
|
| 283 | + |
|
| 284 | +-- | Perform downsweep, starting from the given root 'ModuleNodeInfo's and root
|
|
| 285 | +-- 'UnitId's.
|
|
| 286 | +-- This function will start at the given roots, and traverse downwards to find
|
|
| 287 | +-- all the dependencies, all the way to the leaf units.
|
|
| 288 | +downsweepFromRootNodes :: HscEnv
|
|
| 150 | 289 | -> M.Map (UnitId, FilePath) ModSummary
|
| 151 | 290 | -> [ModuleName]
|
| 152 | 291 | -> Bool
|
| 153 | - -> ([(UnitId, DriverMessages)], [ModSummary])
|
|
| 154 | - -> IO ([DriverMessages], ModuleGraph)
|
|
| 155 | -downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, rootSummariesOk)
|
|
| 292 | + -> DownsweepMode -- ^ Whether to create fixed or compile nodes for dependencies
|
|
| 293 | + -> [ModuleNodeInfo] -- ^ The starting ModuleNodeInfo
|
|
| 294 | + -> [UnitId] -- ^ The starting units
|
|
| 295 | + -> IO ([DriverMessages], [ModuleGraphNode])
|
|
| 296 | +downsweepFromRootNodes hsc_env old_summaries excl_mods allow_dup_roots mode root_nodes root_uids
|
|
| 156 | 297 | = do
|
| 157 | - let root_map = mkRootMap rootSummariesOk
|
|
| 298 | + let root_map = mkRootMap root_nodes
|
|
| 158 | 299 | checkDuplicates root_map
|
| 159 | - (deps, map0) <- loopSummaries rootSummariesOk (M.empty, root_map)
|
|
| 300 | + (module_deps, map0) <- loopModuleNodeInfos root_nodes (M.empty, root_map)
|
|
| 301 | + let all_deps = loopUnit hsc_env module_deps root_uids
|
|
| 302 | + |
|
| 160 | 303 | let all_instantiations = getHomeUnitInstantiations hsc_env
|
| 161 | - let deps' = loopInstantiations all_instantiations deps
|
|
| 162 | - let closure_errs = checkHomeUnitsClosed unit_env
|
|
| 163 | - unit_env = hsc_unit_env hsc_env
|
|
| 164 | - tmpfs = hsc_tmpfs hsc_env
|
|
| 304 | + let deps' = loopInstantiations all_instantiations all_deps
|
|
| 165 | 305 | |
| 166 | 306 | downsweep_errs = lefts $ concat $ M.elems map0
|
| 167 | 307 | downsweep_nodes = M.elems deps'
|
| 168 | 308 | |
| 169 | - (other_errs, unit_nodes) = partitionEithers $ HUG.unitEnv_foldWithKey (\nodes uid hue -> nodes ++ unitModuleNodes downsweep_nodes uid hue) [] (hsc_HUG hsc_env)
|
|
| 170 | - all_nodes = downsweep_nodes ++ unit_nodes
|
|
| 171 | - all_errs = all_root_errs ++ downsweep_errs ++ other_errs
|
|
| 172 | - all_root_errs = closure_errs ++ map snd root_errs
|
|
| 173 | - |
|
| 174 | - -- if we have been passed -fno-code, we enable code generation
|
|
| 175 | - -- for dependencies of modules that have -XTemplateHaskell,
|
|
| 176 | - -- otherwise those modules will fail to compile.
|
|
| 177 | - -- See Note [-fno-code mode] #8025
|
|
| 178 | - th_enabled_nodes <- enableCodeGenForTH logger tmpfs unit_env all_nodes
|
|
| 179 | - if null all_root_errs
|
|
| 180 | - then return (all_errs, th_enabled_nodes)
|
|
| 181 | - else pure $ (all_root_errs, emptyMG)
|
|
| 309 | + return (downsweep_errs, downsweep_nodes)
|
|
| 182 | 310 | where
|
| 183 | 311 | getHomeUnitInstantiations :: HscEnv -> [(UnitId, InstantiatedUnit)]
|
| 184 | 312 | getHomeUnitInstantiations hsc_env = HUG.unitEnv_foldWithKey (\nodes uid hue -> nodes ++ instantiationNodes uid (homeUnitEnv_units hue)) [] (hsc_HUG hsc_env)
|
| 185 | 313 | |
| 186 | - -- Dependencies arising on a unit (backpack and module linking deps)
|
|
| 187 | - unitModuleNodes :: [ModuleGraphNode] -> UnitId -> HomeUnitEnv -> [Either (Messages DriverMessage) ModuleGraphNode]
|
|
| 188 | - unitModuleNodes summaries uid hue =
|
|
| 189 | - maybeToList (linkNodes summaries uid hue)
|
|
| 190 | 314 | |
| 191 | 315 | calcDeps ms =
|
| 192 | 316 | -- Add a dependency on the HsBoot file if it exists
|
| ... | ... | @@ -195,8 +319,6 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro |
| 195 | 319 | [(ms_unitid ms, NoPkgQual, GWIB (noLoc $ ms_mod_name ms) IsBoot) | NotBoot <- [isBootSummary ms] ] ++
|
| 196 | 320 | [(ms_unitid ms, b, c) | (b, c) <- msDeps ms ]
|
| 197 | 321 | |
| 198 | - logger = hsc_logger hsc_env
|
|
| 199 | - |
|
| 200 | 322 | -- In a root module, the filename is allowed to diverge from the module
|
| 201 | 323 | -- name, so we have to check that there aren't multiple root files
|
| 202 | 324 | -- defining the same module (otherwise the duplicates will be silently
|
| ... | ... | @@ -209,7 +331,7 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro |
| 209 | 331 | , dup_root:_ <- dup_roots = liftIO $ multiRootsErr dup_root
|
| 210 | 332 | | otherwise = pure ()
|
| 211 | 333 | where
|
| 212 | - dup_roots :: [[ModSummary]] -- Each at least of length 2
|
|
| 334 | + dup_roots :: [[ModuleNodeInfo]] -- Each at least of length 2
|
|
| 213 | 335 | dup_roots = filterOut isSingleton $ map rights (M.elems root_map)
|
| 214 | 336 | |
| 215 | 337 | loopInstantiations :: [(UnitId, InstantiatedUnit)]
|
| ... | ... | @@ -250,6 +372,102 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro |
| 250 | 372 | | otherwise
|
| 251 | 373 | = Nothing
|
| 252 | 374 | |
| 375 | + loopModuleNodeInfos :: [ModuleNodeInfo] -> (M.Map NodeKey ModuleGraphNode, DownsweepCache) -> IO (M.Map NodeKey ModuleGraphNode, DownsweepCache)
|
|
| 376 | + loopModuleNodeInfos is cache = foldM (flip loopModuleNodeInfo) cache is
|
|
| 377 | + |
|
| 378 | + loopModuleNodeInfo :: ModuleNodeInfo -> (M.Map NodeKey ModuleGraphNode, DownsweepCache) -> IO (M.Map NodeKey ModuleGraphNode, DownsweepCache)
|
|
| 379 | + loopModuleNodeInfo mod_node_info (done, summarised) = do
|
|
| 380 | + case mod_node_info of
|
|
| 381 | + ModuleNodeCompile ms -> do
|
|
| 382 | + loopSummaries [ms] (done, summarised)
|
|
| 383 | + ModuleNodeFixed mod ml -> do
|
|
| 384 | + done' <- loopFixedModule mod ml done
|
|
| 385 | + return (done', summarised)
|
|
| 386 | + |
|
| 387 | + -- NB: loopFixedModule does not take a downsweep cache, because if you
|
|
| 388 | + -- ever reach a Fixed node, everything under that also must be fixed.
|
|
| 389 | + loopFixedModule :: ModNodeKeyWithUid -> ModLocation
|
|
| 390 | + -> M.Map NodeKey ModuleGraphNode
|
|
| 391 | + -> IO (M.Map NodeKey ModuleGraphNode)
|
|
| 392 | + loopFixedModule key loc done = do
|
|
| 393 | + let nk = NodeKey_Module key
|
|
| 394 | + case M.lookup nk done of
|
|
| 395 | + Just {} -> return done
|
|
| 396 | + Nothing -> do
|
|
| 397 | + -- MP: TODO, we should just read the dependency info from the interface rather than either
|
|
| 398 | + -- a. Loading the whole thing into the EPS (this might never nececssary and causes lots of things to be permanently loaded into memory)
|
|
| 399 | + -- b. Loading the whole interface into a buffer before discarding it. (wasted allocation and deserialisation)
|
|
| 400 | + read_result <-
|
|
| 401 | + -- 1. Check if the interface is already loaded into the EPS by some other
|
|
| 402 | + -- part of the compiler.
|
|
| 403 | + lookupIfaceByModuleHsc hsc_env (mnkToModule key) >>= \case
|
|
| 404 | + Just iface -> return (M.Succeeded iface)
|
|
| 405 | + Nothing -> readIface (hsc_logger hsc_env) (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule key) (ml_hi_file loc)
|
|
| 406 | + case read_result of
|
|
| 407 | + M.Succeeded iface -> do
|
|
| 408 | + -- Computer information about this node
|
|
| 409 | + let node_deps = ifaceDeps (mi_deps iface)
|
|
| 410 | + edges = map (either NodeKey_Module NodeKey_ExternalUnit) node_deps
|
|
| 411 | + node = ModuleNode edges (ModuleNodeFixed key loc)
|
|
| 412 | + foldM (loopFixedNodeKey (mnkUnitId key)) (M.insert nk node done) node_deps
|
|
| 413 | + -- Ignore any failure, we might try to read a .hi-boot file for
|
|
| 414 | + -- example, even if there is not one.
|
|
| 415 | + M.Failed {} ->
|
|
| 416 | + return done
|
|
| 417 | + |
|
| 418 | + loopFixedNodeKey :: UnitId -> M.Map NodeKey ModuleGraphNode -> Either ModNodeKeyWithUid UnitId -> IO (M.Map NodeKey ModuleGraphNode)
|
|
| 419 | + loopFixedNodeKey _ done (Left key) = do
|
|
| 420 | + loopFixedImports [key] done
|
|
| 421 | + loopFixedNodeKey home_uid done (Right uid) = do
|
|
| 422 | + -- Set active unit so that looking loopUnit finds the correct
|
|
| 423 | + -- -package flags in the unit state.
|
|
| 424 | + let hsc_env' = hscSetActiveUnitId home_uid hsc_env
|
|
| 425 | + return $ loopUnit hsc_env' done [uid]
|
|
| 426 | + |
|
| 427 | + |
|
| 428 | + ifaceDeps :: Dependencies -> [Either ModNodeKeyWithUid UnitId]
|
|
| 429 | + ifaceDeps deps =
|
|
| 430 | + [ Left (ModNodeKeyWithUid dep uid)
|
|
| 431 | + | (uid, dep) <- Set.toList (dep_direct_mods deps)
|
|
| 432 | + ] ++
|
|
| 433 | + [ Right uid
|
|
| 434 | + | uid <- Set.toList (dep_direct_pkgs deps)
|
|
| 435 | + ]
|
|
| 436 | + |
|
| 437 | + -- Like loopImports, but we already know exactly which module we are looking for.
|
|
| 438 | + loopFixedImports :: [ModNodeKeyWithUid]
|
|
| 439 | + -> M.Map NodeKey ModuleGraphNode
|
|
| 440 | + -> IO (M.Map NodeKey ModuleGraphNode)
|
|
| 441 | + loopFixedImports [] done = pure done
|
|
| 442 | + loopFixedImports (key:keys) done = do
|
|
| 443 | + let nk = NodeKey_Module key
|
|
| 444 | + case M.lookup nk done of
|
|
| 445 | + Just {} -> loopFixedImports keys done
|
|
| 446 | + Nothing -> do
|
|
| 447 | + read_result <- findExactModule hsc_env (mnkToInstalledModule key) (mnkIsBoot key)
|
|
| 448 | + case read_result of
|
|
| 449 | + InstalledFound loc -> do
|
|
| 450 | + done' <- loopFixedModule key loc done
|
|
| 451 | + loopFixedImports keys done'
|
|
| 452 | + _otherwise ->
|
|
| 453 | + -- If the finder fails, just keep going, there will be another
|
|
| 454 | + -- error later.
|
|
| 455 | + loopFixedImports keys done
|
|
| 456 | + |
|
| 457 | + downsweepSummarise :: HscEnv
|
|
| 458 | + -> HomeUnit
|
|
| 459 | + -> M.Map (UnitId, FilePath) ModSummary
|
|
| 460 | + -> IsBootInterface
|
|
| 461 | + -> Located ModuleName
|
|
| 462 | + -> PkgQual
|
|
| 463 | + -> Maybe (StringBuffer, UTCTime)
|
|
| 464 | + -> [ModuleName]
|
|
| 465 | + -> IO SummariseResult
|
|
| 466 | + downsweepSummarise hsc_env home_unit old_summaries is_boot wanted_mod mb_pkg maybe_buf excl_mods =
|
|
| 467 | + case mode of
|
|
| 468 | + DownsweepUseCompile -> summariseModule hsc_env home_unit old_summaries is_boot wanted_mod mb_pkg maybe_buf excl_mods
|
|
| 469 | + DownsweepUseFixed -> summariseModuleInterface hsc_env home_unit is_boot wanted_mod mb_pkg excl_mods
|
|
| 470 | + |
|
| 253 | 471 | |
| 254 | 472 | -- This loops over each import in each summary. It is mutually recursive with loopSummaries if we discover
|
| 255 | 473 | -- a new module by doing this.
|
| ... | ... | @@ -268,7 +486,7 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro |
| 268 | 486 | | Just summs <- M.lookup cache_key summarised
|
| 269 | 487 | = case summs of
|
| 270 | 488 | [Right ms] -> do
|
| 271 | - let nk = NodeKey_Module (msKey ms)
|
|
| 489 | + let nk = NodeKey_Module (mnKey ms)
|
|
| 272 | 490 | (rest, summarised', done') <- loopImports ss done summarised
|
| 273 | 491 | return (nk: rest, summarised', done')
|
| 274 | 492 | [Left _err] ->
|
| ... | ... | @@ -277,7 +495,7 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro |
| 277 | 495 | loopImports ss done summarised
|
| 278 | 496 | | otherwise
|
| 279 | 497 | = do
|
| 280 | - mb_s <- summariseModule hsc_env home_unit old_summaries
|
|
| 498 | + mb_s <- downsweepSummarise hsc_env home_unit old_summaries
|
|
| 281 | 499 | is_boot wanted_mod mb_pkg
|
| 282 | 500 | Nothing excl_mods
|
| 283 | 501 | case mb_s of
|
| ... | ... | @@ -295,11 +513,11 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro |
| 295 | 513 | FoundHomeWithError (_uid, e) -> loopImports ss done (Map.insert cache_key [(Left e)] summarised)
|
| 296 | 514 | FoundHome s -> do
|
| 297 | 515 | (done', summarised') <-
|
| 298 | - loopSummaries [s] (done, Map.insert cache_key [Right s] summarised)
|
|
| 516 | + loopModuleNodeInfo s (done, Map.insert cache_key [Right s] summarised)
|
|
| 299 | 517 | (other_deps, final_done, final_summarised) <- loopImports ss done' summarised'
|
| 300 | 518 | |
| 301 | 519 | -- MP: This assumes that we can only instantiate non home units, which is probably fair enough for now.
|
| 302 | - return (NodeKey_Module (msKey s) : other_deps, final_done, final_summarised)
|
|
| 520 | + return (NodeKey_Module (mnKey s) : other_deps, final_done, final_summarised)
|
|
| 303 | 521 | where
|
| 304 | 522 | cache_key = (home_uid, mb_pkg, unLoc <$> gwib)
|
| 305 | 523 | home_unit = ue_unitHomeUnit home_uid (hsc_unit_env hsc_env)
|
| ... | ... | @@ -316,17 +534,17 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro |
| 316 | 534 | Just us -> loopUnit lcl_hsc_env (loopUnit lcl_hsc_env (Map.insert nk (UnitNode us u) cache) us) uxs
|
| 317 | 535 | Nothing -> pprPanic "loopUnit" (text "Malformed package database, missing " <+> ppr u)
|
| 318 | 536 | |
| 319 | -multiRootsErr :: [ModSummary] -> IO ()
|
|
| 537 | +multiRootsErr :: [ModuleNodeInfo] -> IO ()
|
|
| 320 | 538 | multiRootsErr [] = panic "multiRootsErr"
|
| 321 | 539 | multiRootsErr summs@(summ1:_)
|
| 322 | 540 | = throwOneError $ fmap GhcDriverMessage $
|
| 323 | 541 | mkPlainErrorMsgEnvelope noSrcSpan $ DriverDuplicatedModuleDeclaration mod files
|
| 324 | 542 | where
|
| 325 | - mod = ms_mod summ1
|
|
| 326 | - files = map (expectJust . ml_hs_file . ms_location) summs
|
|
| 543 | + mod = moduleNodeInfoModule summ1
|
|
| 544 | + files = mapMaybe (ml_hs_file . moduleNodeInfoLocation) summs
|
|
| 327 | 545 | |
| 328 | -moduleNotFoundErr :: ModuleName -> DriverMessages
|
|
| 329 | -moduleNotFoundErr mod = singleMessage $ mkPlainErrorMsgEnvelope noSrcSpan (DriverModuleNotFound mod)
|
|
| 546 | +moduleNotFoundErr :: UnitId -> ModuleName -> DriverMessages
|
|
| 547 | +moduleNotFoundErr uid mod = singleMessage $ mkPlainErrorMsgEnvelope noSrcSpan (DriverModuleNotFound uid mod)
|
|
| 330 | 548 | |
| 331 | 549 | -- | Collect the instantiations of dependencies to create 'InstantiationNode' work graph nodes.
|
| 332 | 550 | -- These are used to represent the type checking that is done after
|
| ... | ... | @@ -380,18 +598,17 @@ getRootSummary :: |
| 380 | 598 | M.Map (UnitId, FilePath) ModSummary ->
|
| 381 | 599 | HscEnv ->
|
| 382 | 600 | Target ->
|
| 383 | - IO (Either (UnitId, DriverMessages) ModSummary)
|
|
| 601 | + IO (Either DriverMessages ModSummary)
|
|
| 384 | 602 | getRootSummary excl_mods old_summary_map hsc_env target
|
| 385 | 603 | | TargetFile file mb_phase <- targetId
|
| 386 | 604 | = do
|
| 387 | 605 | let offset_file = augmentByWorkingDirectory dflags file
|
| 388 | 606 | exists <- liftIO $ doesFileExist offset_file
|
| 389 | 607 | if exists || isJust maybe_buf
|
| 390 | - then first (uid,) <$>
|
|
| 391 | - summariseFile hsc_env home_unit old_summary_map offset_file mb_phase
|
|
| 608 | + then summariseFile hsc_env home_unit old_summary_map offset_file mb_phase
|
|
| 392 | 609 | maybe_buf
|
| 393 | 610 | else
|
| 394 | - return $ Left $ (uid,) $ singleMessage $
|
|
| 611 | + return $ Left $ singleMessage $
|
|
| 395 | 612 | mkPlainErrorMsgEnvelope noSrcSpan (DriverFileNotFound offset_file)
|
| 396 | 613 | | TargetModule modl <- targetId
|
| 397 | 614 | = do
|
| ... | ... | @@ -399,9 +616,9 @@ getRootSummary excl_mods old_summary_map hsc_env target |
| 399 | 616 | (L rootLoc modl) (ThisPkg (homeUnitId home_unit))
|
| 400 | 617 | maybe_buf excl_mods
|
| 401 | 618 | pure case maybe_summary of
|
| 402 | - FoundHome s -> Right s
|
|
| 403 | - FoundHomeWithError err -> Left err
|
|
| 404 | - _ -> Left (uid, moduleNotFoundErr modl)
|
|
| 619 | + FoundHome (ModuleNodeCompile s) -> Right s
|
|
| 620 | + FoundHomeWithError err -> Left (snd err)
|
|
| 621 | + _ -> Left (moduleNotFoundErr uid modl)
|
|
| 405 | 622 | where
|
| 406 | 623 | Target {targetId, targetContents = maybe_buf, targetUnitId = uid} = target
|
| 407 | 624 | home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env)
|
| ... | ... | @@ -426,8 +643,8 @@ rootSummariesParallel :: |
| 426 | 643 | HscEnv ->
|
| 427 | 644 | (GhcMessage -> AnyGhcDiagnostic) ->
|
| 428 | 645 | Maybe Messager ->
|
| 429 | - (HscEnv -> Target -> IO (Either (UnitId, DriverMessages) ModSummary)) ->
|
|
| 430 | - IO ([(UnitId, DriverMessages)], [ModSummary])
|
|
| 646 | + (HscEnv -> Target -> IO (Either DriverMessages ModSummary)) ->
|
|
| 647 | + IO ([DriverMessages], [ModSummary])
|
|
| 431 | 648 | rootSummariesParallel n_jobs hsc_env diag_wrapper msg get_summary = do
|
| 432 | 649 | (actions, get_results) <- unzip <$> mapM action_and_result (zip [1..] bundles)
|
| 433 | 650 | runPipelines n_jobs hsc_env diag_wrapper msg actions
|
| ... | ... | @@ -732,10 +949,10 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do |
| 732 | 949 | |
| 733 | 950 | -- | Populate the Downsweep cache with the root modules.
|
| 734 | 951 | mkRootMap
|
| 735 | - :: [ModSummary]
|
|
| 952 | + :: [ModuleNodeInfo]
|
|
| 736 | 953 | -> DownsweepCache
|
| 737 | 954 | mkRootMap summaries = Map.fromListWith (flip (++))
|
| 738 | - [ ((ms_unitid s, NoPkgQual, ms_mnwib s), [Right s]) | s <- summaries ]
|
|
| 955 | + [ ((moduleNodeInfoUnitId s, NoPkgQual, moduleNodeInfoMnwib s), [Right s]) | s <- summaries ]
|
|
| 739 | 956 | |
| 740 | 957 | -----------------------------------------------------------------------------
|
| 741 | 958 | -- Summarising modules
|
| ... | ... | @@ -863,26 +1080,64 @@ checkSummaryHash |
| 863 | 1080 | data SummariseResult =
|
| 864 | 1081 | FoundInstantiation InstantiatedUnit
|
| 865 | 1082 | | FoundHomeWithError (UnitId, DriverMessages)
|
| 866 | - | FoundHome ModSummary
|
|
| 1083 | + | FoundHome ModuleNodeInfo
|
|
| 867 | 1084 | | External UnitId
|
| 868 | 1085 | | NotThere
|
| 869 | 1086 | |
| 1087 | +-- | summariseModule finds the location of the source file for the given module.
|
|
| 1088 | +-- This version always returns a ModuleNodeCompile node, it is useful for
|
|
| 1089 | +-- --make mode.
|
|
| 1090 | +summariseModule :: HscEnv
|
|
| 1091 | + -> HomeUnit
|
|
| 1092 | + -> M.Map (UnitId, FilePath) ModSummary
|
|
| 1093 | + -> IsBootInterface
|
|
| 1094 | + -> Located ModuleName
|
|
| 1095 | + -> PkgQual
|
|
| 1096 | + -> Maybe (StringBuffer, UTCTime)
|
|
| 1097 | + -> [ModuleName]
|
|
| 1098 | + -> IO SummariseResult
|
|
| 1099 | +summariseModule hsc_env home_unit old_summaries is_boot wanted_mod mb_pkg maybe_buf excl_mods =
|
|
| 1100 | + summariseModuleDispatch k hsc_env home_unit is_boot wanted_mod mb_pkg excl_mods
|
|
| 1101 | + where
|
|
| 1102 | + k = summariseModuleWithSource home_unit old_summaries is_boot maybe_buf
|
|
| 1103 | + |
|
| 1104 | + |
|
| 1105 | +-- | Like summariseModule but for interface files that we don't want to compile.
|
|
| 1106 | +-- This version always returns a ModuleNodeFixed node.
|
|
| 1107 | +summariseModuleInterface :: HscEnv
|
|
| 1108 | + -> HomeUnit
|
|
| 1109 | + -> IsBootInterface
|
|
| 1110 | + -> Located ModuleName
|
|
| 1111 | + -> PkgQual
|
|
| 1112 | + -> [ModuleName]
|
|
| 1113 | + -> IO SummariseResult
|
|
| 1114 | +summariseModuleInterface hsc_env home_unit is_boot wanted_mod mb_pkg excl_mods =
|
|
| 1115 | + summariseModuleDispatch k hsc_env home_unit is_boot wanted_mod mb_pkg excl_mods
|
|
| 1116 | + where
|
|
| 1117 | + k _hsc_env loc mod = do
|
|
| 1118 | + -- The finder will return a path to the .hi-boot even if it doesn't actually
|
|
| 1119 | + -- exist. So check if it exists first before concluding it's there.
|
|
| 1120 | + does_exist <- doesFileExist (ml_hi_file loc)
|
|
| 1121 | + if does_exist
|
|
| 1122 | + then let key = moduleToMnk mod is_boot
|
|
| 1123 | + in return $ FoundHome (ModuleNodeFixed key loc)
|
|
| 1124 | + else return NotThere
|
|
| 1125 | + |
|
| 1126 | + |
|
| 1127 | + |
|
| 870 | 1128 | -- Summarise a module, and pick up source and timestamp.
|
| 871 | -summariseModule
|
|
| 872 | - :: HscEnv
|
|
| 1129 | +summariseModuleDispatch
|
|
| 1130 | + :: (HscEnv -> ModLocation -> Module -> IO SummariseResult) -- ^ Continuation about how to summarise a home module.
|
|
| 1131 | + -> HscEnv
|
|
| 873 | 1132 | -> HomeUnit
|
| 874 | - -> M.Map (UnitId, FilePath) ModSummary
|
|
| 875 | - -- ^ Map of old summaries
|
|
| 876 | 1133 | -> IsBootInterface -- True <=> a {-# SOURCE #-} import
|
| 877 | 1134 | -> Located ModuleName -- Imported module to be summarised
|
| 878 | 1135 | -> PkgQual
|
| 879 | - -> Maybe (StringBuffer, UTCTime)
|
|
| 880 | 1136 | -> [ModuleName] -- Modules to exclude
|
| 881 | 1137 | -> IO SummariseResult
|
| 882 | 1138 | |
| 883 | 1139 | |
| 884 | -summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_pkg
|
|
| 885 | - maybe_buf excl_mods
|
|
| 1140 | +summariseModuleDispatch k hsc_env' home_unit is_boot (L _ wanted_mod) mb_pkg excl_mods
|
|
| 886 | 1141 | | wanted_mod `elem` excl_mods
|
| 887 | 1142 | = return NotThere
|
| 888 | 1143 | | otherwise = find_it
|
| ... | ... | @@ -890,7 +1145,6 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p |
| 890 | 1145 | -- Temporarily change the currently active home unit so all operations
|
| 891 | 1146 | -- happen relative to it
|
| 892 | 1147 | hsc_env = hscSetActiveHomeUnit home_unit hsc_env'
|
| 893 | - dflags = hsc_dflags hsc_env
|
|
| 894 | 1148 | |
| 895 | 1149 | find_it :: IO SummariseResult
|
| 896 | 1150 | |
| ... | ... | @@ -898,9 +1152,9 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p |
| 898 | 1152 | found <- findImportedModuleWithIsBoot hsc_env wanted_mod is_boot mb_pkg
|
| 899 | 1153 | case found of
|
| 900 | 1154 | Found location mod
|
| 901 | - | isJust (ml_hs_file location) ->
|
|
| 1155 | + | moduleUnitId mod `Set.member` hsc_all_home_unit_ids hsc_env ->
|
|
| 902 | 1156 | -- Home package
|
| 903 | - just_found location mod
|
|
| 1157 | + k hsc_env location mod
|
|
| 904 | 1158 | | VirtUnit iud <- moduleUnit mod
|
| 905 | 1159 | , not (isHomeModule home_unit mod)
|
| 906 | 1160 | -> return $ FoundInstantiation iud
|
| ... | ... | @@ -910,9 +1164,22 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p |
| 910 | 1164 | -- (If it is TRULY not found at all, we'll
|
| 911 | 1165 | -- error when we actually try to compile)
|
| 912 | 1166 | |
| 913 | - just_found location mod = do
|
|
| 914 | - -- Adjust location to point to the hs-boot source file,
|
|
| 915 | - -- hi file, object file, when is_boot says so
|
|
| 1167 | + |
|
| 1168 | +-- | The continuation to summarise a home module if we want to find the source file
|
|
| 1169 | +-- for it and potentially compile it.
|
|
| 1170 | +summariseModuleWithSource
|
|
| 1171 | + :: HomeUnit
|
|
| 1172 | + -> M.Map (UnitId, FilePath) ModSummary
|
|
| 1173 | + -- ^ Map of old summaries
|
|
| 1174 | + -> IsBootInterface -- True <=> a {-# SOURCE #-} import
|
|
| 1175 | + -> Maybe (StringBuffer, UTCTime)
|
|
| 1176 | + -> HscEnv
|
|
| 1177 | + -> ModLocation
|
|
| 1178 | + -> Module
|
|
| 1179 | + -> IO SummariseResult
|
|
| 1180 | +summariseModuleWithSource home_unit old_summary_map is_boot maybe_buf hsc_env location mod = do
|
|
| 1181 | + -- Adjust location to point to the hs-boot source file,
|
|
| 1182 | + -- hi file, object file, when is_boot says so
|
|
| 916 | 1183 | let src_fn = expectJust (ml_hs_file location)
|
| 917 | 1184 | |
| 918 | 1185 | -- Check that it exists
|
| ... | ... | @@ -926,8 +1193,10 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p |
| 926 | 1193 | fresult <- new_summary_cache_check location mod src_fn h
|
| 927 | 1194 | return $ case fresult of
|
| 928 | 1195 | Left err -> FoundHomeWithError (moduleUnitId mod, err)
|
| 929 | - Right ms -> FoundHome ms
|
|
| 1196 | + Right ms -> FoundHome (ModuleNodeCompile ms)
|
|
| 930 | 1197 | |
| 1198 | + where
|
|
| 1199 | + dflags = hsc_dflags hsc_env
|
|
| 931 | 1200 | new_summary_cache_check loc mod src_fn h
|
| 932 | 1201 | | Just old_summary <- Map.lookup ((toUnitId (moduleUnit mod), src_fn)) old_summary_map =
|
| 933 | 1202 | |
| ... | ... | @@ -1061,4 +1330,4 @@ getPreprocessedImports hsc_env src_fn mb_phase maybe_buf = do |
| 1061 | 1330 | let rn_imps = fmap (\(pk, lmn@(L _ mn)) -> (rn_pkg_qual mn pk, lmn))
|
| 1062 | 1331 | let pi_srcimps = rn_imps pi_srcimps'
|
| 1063 | 1332 | let pi_theimps = rn_imps pi_theimps'
|
| 1064 | - return PreprocessedImports {..} |
|
| \ No newline at end of file | ||
| 1333 | + return PreprocessedImports {..} |
| ... | ... | @@ -27,6 +27,7 @@ module GHC.Driver.Env |
| 27 | 27 | , discardIC
|
| 28 | 28 | , lookupType
|
| 29 | 29 | , lookupIfaceByModule
|
| 30 | + , lookupIfaceByModuleHsc
|
|
| 30 | 31 | , mainModIs
|
| 31 | 32 | |
| 32 | 33 | , hugRulesBelow
|
| ... | ... | @@ -249,6 +250,11 @@ hugInstancesBelow hsc_env uid mnwib = do |
| 249 | 250 | --
|
| 250 | 251 | -- Note: Don't expose this function. This is a footgun if exposed!
|
| 251 | 252 | hugSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO [[a]]
|
| 253 | +-- An explicit check to see if we are in one-shot mode to avoid poking the ModuleGraph thunk
|
|
| 254 | +-- These things are currently stored in the EPS for home packages. (See #25795 for
|
|
| 255 | +-- progress in removing these kind of checks)
|
|
| 256 | +-- See Note [Downsweep and the ModuleGraph]
|
|
| 257 | +hugSomeThingsBelowUs _ _ hsc_env _ _ | isOneShot (ghcMode (hsc_dflags hsc_env)) = return []
|
|
| 252 | 258 | hugSomeThingsBelowUs extract include_hi_boot hsc_env uid mn
|
| 253 | 259 | = let hug = hsc_HUG hsc_env
|
| 254 | 260 | mg = hsc_mod_graph hsc_env
|
| ... | ... | @@ -345,6 +351,11 @@ lookupIfaceByModule hug pit mod |
| 345 | 351 | -- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
|
| 346 | 352 | -- of its own, but it doesn't seem worth the bother.
|
| 347 | 353 | |
| 354 | +lookupIfaceByModuleHsc :: HscEnv -> Module -> IO (Maybe ModIface)
|
|
| 355 | +lookupIfaceByModuleHsc hsc_env mod = do
|
|
| 356 | + eps <- hscEPS hsc_env
|
|
| 357 | + lookupIfaceByModule (hsc_HUG hsc_env) (eps_PIT eps) mod
|
|
| 358 | + |
|
| 348 | 359 | mainModIs :: HomeUnitEnv -> Module
|
| 349 | 360 | mainModIs hue = mkHomeModule (expectJust $ homeUnitEnv_home_unit hue) (mainModuleNameIs (homeUnitEnv_dflags hue))
|
| 350 | 361 |
| ... | ... | @@ -67,6 +67,7 @@ data HscEnv |
| 67 | 67 | |
| 68 | 68 | hsc_mod_graph :: ModuleGraph,
|
| 69 | 69 | -- ^ The module graph of the current session
|
| 70 | + -- See Note [Downsweep and the ModuleGraph] for when this is constructed.
|
|
| 70 | 71 | |
| 71 | 72 | hsc_IC :: InteractiveContext,
|
| 72 | 73 | -- ^ The context for evaluating interactive statements
|
| ... | ... | @@ -155,7 +155,7 @@ instance Diagnostic DriverMessage where |
| 155 | 155 | text "module" <+> quotes (ppr mod) <+>
|
| 156 | 156 | text "is defined in multiple files:" <+>
|
| 157 | 157 | sep (map text files)
|
| 158 | - DriverModuleNotFound mod
|
|
| 158 | + DriverModuleNotFound _uid mod
|
|
| 159 | 159 | -> mkSimpleDecorated (text "module" <+> quotes (ppr mod) <+> text "cannot be found locally")
|
| 160 | 160 | DriverFileModuleNameMismatch actual expected
|
| 161 | 161 | -> mkSimpleDecorated $
|
| ... | ... | @@ -187,7 +187,7 @@ data DriverMessage where |
| 187 | 187 | |
| 188 | 188 | Test cases: None.
|
| 189 | 189 | -}
|
| 190 | - DriverModuleNotFound :: !ModuleName -> DriverMessage
|
|
| 190 | + DriverModuleNotFound :: !UnitId -> !ModuleName -> DriverMessage
|
|
| 191 | 191 | |
| 192 | 192 | {-| DriverFileModuleNameMismatch occurs if a module 'A' is defined in a file with a different name.
|
| 193 | 193 | The first field is the name written in the source code; the second argument is the name extracted
|
| ... | ... | @@ -118,6 +118,7 @@ import GHC.Driver.Backend |
| 118 | 118 | import GHC.Driver.Env
|
| 119 | 119 | import GHC.Driver.Env.KnotVars
|
| 120 | 120 | import GHC.Driver.Errors
|
| 121 | +import GHC.Driver.Messager
|
|
| 121 | 122 | import GHC.Driver.Errors.Types
|
| 122 | 123 | import GHC.Driver.CodeOutput
|
| 123 | 124 | import GHC.Driver.Config.Cmm.Parser (initCmmParserConfig)
|
| ... | ... | @@ -220,7 +221,6 @@ import GHC.Cmm.UniqueRenamer |
| 220 | 221 | import GHC.Unit
|
| 221 | 222 | import GHC.Unit.Env
|
| 222 | 223 | import GHC.Unit.Finder
|
| 223 | -import GHC.Unit.External
|
|
| 224 | 224 | import GHC.Unit.Module.ModDetails
|
| 225 | 225 | import GHC.Unit.Module.ModGuts
|
| 226 | 226 | import GHC.Unit.Module.ModIface
|
| ... | ... | @@ -814,7 +814,6 @@ This is the only thing that isn't caught by the type-system. |
| 814 | 814 | -}
|
| 815 | 815 | |
| 816 | 816 | |
| 817 | -type Messager = HscEnv -> (Int,Int) -> RecompileRequired -> ModuleGraphNode -> IO ()
|
|
| 818 | 817 | |
| 819 | 818 | -- | Do the recompilation avoidance checks for both one-shot and --make modes
|
| 820 | 819 | -- This function is the *only* place in the compiler where we decide whether to
|
| ... | ... | @@ -1476,46 +1475,6 @@ genModDetails hsc_env old_iface |
| 1476 | 1475 | dumpIfaceStats hsc_env
|
| 1477 | 1476 | return new_details
|
| 1478 | 1477 | |
| 1479 | ---------------------------------------------------------------
|
|
| 1480 | --- Progress displayers.
|
|
| 1481 | ---------------------------------------------------------------
|
|
| 1482 | - |
|
| 1483 | -oneShotMsg :: Logger -> RecompileRequired -> IO ()
|
|
| 1484 | -oneShotMsg logger recomp =
|
|
| 1485 | - case recomp of
|
|
| 1486 | - UpToDate -> compilationProgressMsg logger $ text "compilation IS NOT required"
|
|
| 1487 | - NeedsRecompile _ -> return ()
|
|
| 1488 | - |
|
| 1489 | -batchMsg :: Messager
|
|
| 1490 | -batchMsg = batchMsgWith (\_ _ _ _ -> empty)
|
|
| 1491 | -batchMultiMsg :: Messager
|
|
| 1492 | -batchMultiMsg = batchMsgWith (\_ _ _ node -> brackets (ppr (mgNodeUnitId node)))
|
|
| 1493 | - |
|
| 1494 | -batchMsgWith :: (HscEnv -> (Int, Int) -> RecompileRequired -> ModuleGraphNode -> SDoc) -> Messager
|
|
| 1495 | -batchMsgWith extra hsc_env_start mod_index recomp node =
|
|
| 1496 | - case recomp of
|
|
| 1497 | - UpToDate
|
|
| 1498 | - | logVerbAtLeast logger 2 -> showMsg (text "Skipping") empty
|
|
| 1499 | - | otherwise -> return ()
|
|
| 1500 | - NeedsRecompile reason0 -> showMsg (text herald) $ case reason0 of
|
|
| 1501 | - MustCompile -> empty
|
|
| 1502 | - (RecompBecause reason) -> text " [" <> pprWithUnitState state (ppr reason) <> text "]"
|
|
| 1503 | - where
|
|
| 1504 | - herald = case node of
|
|
| 1505 | - LinkNode {} -> "Linking"
|
|
| 1506 | - InstantiationNode {} -> "Instantiating"
|
|
| 1507 | - ModuleNode {} -> "Compiling"
|
|
| 1508 | - UnitNode {} -> "Loading"
|
|
| 1509 | - hsc_env = hscSetActiveUnitId (mgNodeUnitId node) hsc_env_start
|
|
| 1510 | - dflags = hsc_dflags hsc_env
|
|
| 1511 | - logger = hsc_logger hsc_env
|
|
| 1512 | - state = hsc_units hsc_env
|
|
| 1513 | - showMsg msg reason =
|
|
| 1514 | - compilationProgressMsg logger $
|
|
| 1515 | - (showModuleIndex mod_index <>
|
|
| 1516 | - msg <+> showModMsg dflags (recompileRequired recomp) node)
|
|
| 1517 | - <> extra hsc_env mod_index recomp node
|
|
| 1518 | - <> reason
|
|
| 1519 | 1478 | |
| 1520 | 1479 | --------------------------------------------------------------
|
| 1521 | 1480 | -- Safe Haskell
|
| ... | ... | @@ -1803,10 +1762,7 @@ hscCheckSafe' m l = do |
| 1803 | 1762 | lookup' :: Module -> Hsc (Maybe ModIface)
|
| 1804 | 1763 | lookup' m = do
|
| 1805 | 1764 | hsc_env <- getHscEnv
|
| 1806 | - hsc_eps <- liftIO $ hscEPS hsc_env
|
|
| 1807 | - let pkgIfaceT = eps_PIT hsc_eps
|
|
| 1808 | - hug = hsc_HUG hsc_env
|
|
| 1809 | - iface <- liftIO $ lookupIfaceByModule hug pkgIfaceT m
|
|
| 1765 | + iface <- liftIO $ lookupIfaceByModuleHsc hsc_env m
|
|
| 1810 | 1766 | -- the 'lookupIfaceByModule' method will always fail when calling from GHCi
|
| 1811 | 1767 | -- as the compiler hasn't filled in the various module tables
|
| 1812 | 1768 | -- so we need to call 'getModuleInterface' to load from disk
|
| ... | ... | @@ -2954,18 +2910,6 @@ dumpIfaceStats hsc_env = do |
| 2954 | 2910 | logDumpMsg logger "Interface statistics" (ifaceStats eps)
|
| 2955 | 2911 | |
| 2956 | 2912 | |
| 2957 | -{- **********************************************************************
|
|
| 2958 | -%* *
|
|
| 2959 | - Progress Messages: Module i of n
|
|
| 2960 | -%* *
|
|
| 2961 | -%********************************************************************* -}
|
|
| 2962 | - |
|
| 2963 | -showModuleIndex :: (Int, Int) -> SDoc
|
|
| 2964 | -showModuleIndex (i,n) = text "[" <> pad <> int i <> text " of " <> int n <> text "] "
|
|
| 2965 | - where
|
|
| 2966 | - -- compute the length of x > 0 in base 10
|
|
| 2967 | - len x = ceiling (logBase 10 (fromIntegral x+1) :: Float)
|
|
| 2968 | - pad = text (replicate (len n - len i) ' ') -- TODO: use GHC.Utils.Ppr.RStr
|
|
| 2969 | 2913 | |
| 2970 | 2914 | writeInterfaceOnlyMode :: DynFlags -> Bool
|
| 2971 | 2915 | writeInterfaceOnlyMode dflags =
|
| ... | ... | @@ -41,6 +41,7 @@ module GHC.Driver.Make ( |
| 41 | 41 | -- * Re-exports from Downsweep
|
| 42 | 42 | checkHomeUnitsClosed,
|
| 43 | 43 | summariseModule,
|
| 44 | + summariseModuleInterface,
|
|
| 44 | 45 | SummariseResult(..),
|
| 45 | 46 | summariseFile,
|
| 46 | 47 | |
| ... | ... | @@ -648,7 +649,7 @@ load' mhmi_cache how_much diag_wrapper mHscMessage mod_graph = do |
| 648 | 649 | | otherwise = do
|
| 649 | 650 | throwOneError $ mkPlainErrorMsgEnvelope noSrcSpan
|
| 650 | 651 | $ GhcDriverMessage
|
| 651 | - $ DriverModuleNotFound (moduleName m)
|
|
| 652 | + $ DriverModuleNotFound (moduleUnit m) (moduleName m)
|
|
| 652 | 653 | |
| 653 | 654 | checkHowMuch how_much $ do
|
| 654 | 655 | |
| ... | ... | @@ -1667,7 +1668,7 @@ executeCompileNode k n !old_hmi hug mrehydrate_mods mni = do |
| 1667 | 1668 | executeCompileNodeFixed hsc_env MakeEnv{diag_wrapper, env_messager} mod loc =
|
| 1668 | 1669 | wrapAction diag_wrapper hsc_env $ do
|
| 1669 | 1670 | forM_ env_messager $ \hscMessage -> hscMessage hsc_env (k, n) UpToDate (ModuleNode [] (ModuleNodeFixed mod loc))
|
| 1670 | - read_result <- readIface (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule mod) (ml_hi_file loc)
|
|
| 1671 | + read_result <- readIface (hsc_logger hsc_env) (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule mod) (ml_hi_file loc)
|
|
| 1671 | 1672 | case read_result of
|
| 1672 | 1673 | M.Failed interface_err ->
|
| 1673 | 1674 | let mn = mnkModuleName mod
|
| ... | ... | @@ -25,7 +25,7 @@ import GHC.Driver.DynFlags |
| 25 | 25 | import GHC.Driver.Monad
|
| 26 | 26 | import GHC.Driver.Env
|
| 27 | 27 | import GHC.Driver.Errors.Types
|
| 28 | -import GHC.Driver.Main
|
|
| 28 | +import GHC.Driver.Messager
|
|
| 29 | 29 | import GHC.Driver.MakeSem
|
| 30 | 30 | |
| 31 | 31 | import GHC.Utils.Logger
|
| 1 | +module GHC.Driver.Messager (Messager, oneShotMsg, batchMsg, batchMultiMsg, showModuleIndex) where
|
|
| 2 | + |
|
| 3 | +import GHC.Prelude
|
|
| 4 | +import GHC.Driver.Env
|
|
| 5 | +import GHC.Unit.Module.Graph
|
|
| 6 | +import GHC.Iface.Recomp
|
|
| 7 | +import GHC.Utils.Logger
|
|
| 8 | +import GHC.Utils.Outputable
|
|
| 9 | +import GHC.Utils.Error
|
|
| 10 | +import GHC.Unit.State
|
|
| 11 | + |
|
| 12 | +type Messager = HscEnv -> (Int,Int) -> RecompileRequired -> ModuleGraphNode -> IO ()
|
|
| 13 | + |
|
| 14 | +--------------------------------------------------------------
|
|
| 15 | +-- Progress displayers.
|
|
| 16 | +--------------------------------------------------------------
|
|
| 17 | + |
|
| 18 | +oneShotMsg :: Logger -> RecompileRequired -> IO ()
|
|
| 19 | +oneShotMsg logger recomp =
|
|
| 20 | + case recomp of
|
|
| 21 | + UpToDate -> compilationProgressMsg logger $ text "compilation IS NOT required"
|
|
| 22 | + NeedsRecompile _ -> return ()
|
|
| 23 | + |
|
| 24 | +batchMsg :: Messager
|
|
| 25 | +batchMsg = batchMsgWith (\_ _ _ _ -> empty)
|
|
| 26 | +batchMultiMsg :: Messager
|
|
| 27 | +batchMultiMsg = batchMsgWith (\_ _ _ node -> brackets (ppr (mgNodeUnitId node)))
|
|
| 28 | + |
|
| 29 | +batchMsgWith :: (HscEnv -> (Int, Int) -> RecompileRequired -> ModuleGraphNode -> SDoc) -> Messager
|
|
| 30 | +batchMsgWith extra hsc_env_start mod_index recomp node =
|
|
| 31 | + case recomp of
|
|
| 32 | + UpToDate
|
|
| 33 | + | logVerbAtLeast logger 2 -> showMsg (text "Skipping") empty
|
|
| 34 | + | otherwise -> return ()
|
|
| 35 | + NeedsRecompile reason0 -> showMsg (text herald) $ case reason0 of
|
|
| 36 | + MustCompile -> empty
|
|
| 37 | + (RecompBecause reason) -> text " [" <> pprWithUnitState state (ppr reason) <> text "]"
|
|
| 38 | + where
|
|
| 39 | + herald = case node of
|
|
| 40 | + LinkNode {} -> "Linking"
|
|
| 41 | + InstantiationNode {} -> "Instantiating"
|
|
| 42 | + ModuleNode {} -> "Compiling"
|
|
| 43 | + UnitNode {} -> "Loading"
|
|
| 44 | + hsc_env = hscSetActiveUnitId (mgNodeUnitId node) hsc_env_start
|
|
| 45 | + dflags = hsc_dflags hsc_env
|
|
| 46 | + logger = hsc_logger hsc_env
|
|
| 47 | + state = hsc_units hsc_env
|
|
| 48 | + showMsg msg reason =
|
|
| 49 | + compilationProgressMsg logger $
|
|
| 50 | + (showModuleIndex mod_index <>
|
|
| 51 | + msg <+> showModMsg dflags (recompileRequired recomp) node)
|
|
| 52 | + <> extra hsc_env mod_index recomp node
|
|
| 53 | + <> reason
|
|
| 54 | + |
|
| 55 | +{- **********************************************************************
|
|
| 56 | +%* *
|
|
| 57 | + Progress Messages: Module i of n
|
|
| 58 | +%* *
|
|
| 59 | +%********************************************************************* -}
|
|
| 60 | + |
|
| 61 | +showModuleIndex :: (Int, Int) -> SDoc
|
|
| 62 | +showModuleIndex (i,n) = text "[" <> pad <> int i <> text " of " <> int n <> text "] "
|
|
| 63 | + where
|
|
| 64 | + -- compute the length of x > 0 in base 10
|
|
| 65 | + len x = ceiling (logBase 10 (fromIntegral x+1) :: Float)
|
|
| 66 | + pad = text (replicate (len n - len i) ' ') -- TODO: use GHC.Utils.Ppr.RStr |
|
| \ No newline at end of file |
| ... | ... | @@ -3,12 +3,22 @@ module GHC.Driver.Pipeline where |
| 3 | 3 | |
| 4 | 4 | import GHC.Driver.Env.Types ( HscEnv )
|
| 5 | 5 | import GHC.ForeignSrcLang ( ForeignSrcLang )
|
| 6 | -import GHC.Prelude (FilePath, IO)
|
|
| 6 | +import GHC.Prelude (FilePath, IO, Maybe, Either)
|
|
| 7 | 7 | import GHC.Unit.Module.Location (ModLocation)
|
| 8 | 8 | import GHC.Driver.Session (DynFlags)
|
| 9 | +import GHC.Driver.Phases (Phase)
|
|
| 10 | +import GHC.Driver.Errors.Types (DriverMessages)
|
|
| 11 | +import GHC.Types.Target (InputFileBuffer)
|
|
| 9 | 12 | |
| 10 | 13 | import Language.Haskell.Syntax.Module.Name
|
| 11 | 14 | |
| 12 | 15 | -- These are used in GHC.Driver.Pipeline.Execute, but defined in terms of runPipeline
|
| 13 | 16 | compileForeign :: HscEnv -> ForeignSrcLang -> FilePath -> IO FilePath
|
| 14 | 17 | compileEmptyStub :: DynFlags -> HscEnv -> FilePath -> ModLocation -> ModuleName -> IO ()
|
| 18 | + |
|
| 19 | +preprocess :: HscEnv
|
|
| 20 | + -> FilePath
|
|
| 21 | + -> Maybe InputFileBuffer
|
|
| 22 | + -> Maybe Phase
|
|
| 23 | + -> IO (Either DriverMessages (DynFlags, FilePath))
|
|
| 24 | + |
| ... | ... | @@ -33,6 +33,7 @@ import GHC.Unit.Module.ModSummary |
| 33 | 33 | import qualified GHC.LanguageExtensions as LangExt
|
| 34 | 34 | import GHC.Types.SrcLoc
|
| 35 | 35 | import GHC.Driver.Main
|
| 36 | +import GHC.Driver.Downsweep
|
|
| 36 | 37 | import GHC.Tc.Types
|
| 37 | 38 | import GHC.Types.Error
|
| 38 | 39 | import GHC.Driver.Errors.Types
|
| ... | ... | @@ -760,11 +761,17 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do |
| 760 | 761 | let msg :: Messager
|
| 761 | 762 | msg hsc_env _ what _ = oneShotMsg (hsc_logger hsc_env) what
|
| 762 | 763 | |
| 764 | + -- A lazy module graph thunk, don't force it unless you need it!
|
|
| 765 | + mg <- downsweepThunk hsc_env mod_summary
|
|
| 766 | + |
|
| 763 | 767 | -- Need to set the knot-tying mutable variable for interface
|
| 764 | 768 | -- files. See GHC.Tc.Utils.TcGblEnv.tcg_type_env_var.
|
| 765 | 769 | -- See also Note [hsc_type_env_var hack]
|
| 766 | 770 | type_env_var <- newIORef emptyNameEnv
|
| 767 | - let hsc_env' = hsc_env { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)]) }
|
|
| 771 | + let hsc_env' = hsc_env { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)])
|
|
| 772 | + , hsc_mod_graph = mg }
|
|
| 773 | + |
|
| 774 | + |
|
| 768 | 775 | |
| 769 | 776 | status <- hscRecompStatus (Just msg) hsc_env' mod_summary
|
| 770 | 777 | Nothing emptyHomeModInfoLinkable (1, 1)
|
| ... | ... | @@ -25,7 +25,6 @@ module GHC.Iface.Load ( |
| 25 | 25 | -- IfM functions
|
| 26 | 26 | loadInterface,
|
| 27 | 27 | loadSysInterface, loadUserInterface, loadPluginInterface,
|
| 28 | - loadExternalGraphBelow,
|
|
| 29 | 28 | findAndReadIface, readIface, writeIface,
|
| 30 | 29 | flagsToIfCompression,
|
| 31 | 30 | moduleFreeHolesPrecise,
|
| ... | ... | @@ -49,7 +48,6 @@ import {-# SOURCE #-} GHC.IfaceToCore |
| 49 | 48 | ( tcIfaceDecls, tcIfaceRules, tcIfaceInst, tcIfaceFamInst
|
| 50 | 49 | , tcIfaceAnnotations, tcIfaceCompleteMatches, tcIfaceDefaults)
|
| 51 | 50 | |
| 52 | -import GHC.Driver.Config.Finder
|
|
| 53 | 51 | import GHC.Driver.Env
|
| 54 | 52 | import GHC.Driver.Errors.Types
|
| 55 | 53 | import GHC.Driver.DynFlags
|
| ... | ... | @@ -110,7 +108,6 @@ import GHC.Unit.Home |
| 110 | 108 | import GHC.Unit.Home.PackageTable
|
| 111 | 109 | import GHC.Unit.Finder
|
| 112 | 110 | import GHC.Unit.Env
|
| 113 | -import GHC.Unit.Module.External.Graph
|
|
| 114 | 111 | |
| 115 | 112 | import GHC.Data.Maybe
|
| 116 | 113 | |
| ... | ... | @@ -122,7 +119,6 @@ import GHC.Driver.Env.KnotVars |
| 122 | 119 | import {-# source #-} GHC.Driver.Main (loadIfaceByteCode)
|
| 123 | 120 | import GHC.Iface.Errors.Types
|
| 124 | 121 | import Data.Function ((&))
|
| 125 | -import qualified Data.Set as Set
|
|
| 126 | 122 | import GHC.Unit.Module.Graph
|
| 127 | 123 | import qualified GHC.Unit.Home.Graph as HUG
|
| 128 | 124 | |
| ... | ... | @@ -413,112 +409,6 @@ loadInterfaceWithException doc mod_name where_from |
| 413 | 409 | let ctx = initSDocContext dflags defaultUserStyle
|
| 414 | 410 | withIfaceErr ctx (loadInterface doc mod_name where_from)
|
| 415 | 411 | |
| 416 | --- | Load the part of the external module graph which is transitively reachable
|
|
| 417 | --- from the given modules.
|
|
| 418 | ---
|
|
| 419 | --- This operation is used just before TH splices are run (in 'getLinkDeps').
|
|
| 420 | ---
|
|
| 421 | --- A field in the EPS tracks which home modules are already fully loaded, which we use
|
|
| 422 | --- here to avoid trying to load them a second time.
|
|
| 423 | ---
|
|
| 424 | --- The function takes a set of keys which are currently in the process of being loaded.
|
|
| 425 | --- This is used to avoid duplicating work by loading keys twice if they appear along multiple
|
|
| 426 | --- paths in the transitive closure. Once the interface and all its dependencies are
|
|
| 427 | --- loaded, the key is added to the "fully loaded" set, so we know that it and it's
|
|
| 428 | --- transitive closure are present in the graph.
|
|
| 429 | ---
|
|
| 430 | --- Note that being "in progress" is different from being "fully loaded", consider if there
|
|
| 431 | --- is an exception during `loadExternalGraphBelow`, then an "in progress" item may fail
|
|
| 432 | --- to become fully loaded.
|
|
| 433 | -loadExternalGraphBelow :: (Module -> SDoc) -> Maybe HomeUnit {-^ The current home unit -}
|
|
| 434 | - -> Set.Set ExternalKey -> [Module] -> IfM lcl (Set.Set ExternalKey)
|
|
| 435 | -loadExternalGraphBelow _ Nothing _ _ = panic "loadExternalGraphBelow: No home unit"
|
|
| 436 | -loadExternalGraphBelow msg (Just home_unit) in_progress mods =
|
|
| 437 | - foldM (loadExternalGraphModule msg home_unit) in_progress mods
|
|
| 438 | - |
|
| 439 | --- | Load the interface for a module, and all its transitive dependencies but
|
|
| 440 | --- only if we haven't fully loaded the module already or are in the process of fully loading it.
|
|
| 441 | -loadExternalGraphModule :: (Module -> SDoc) -> HomeUnit
|
|
| 442 | - -> Set.Set ExternalKey
|
|
| 443 | - -> Module
|
|
| 444 | - -> IfM lcl (Set.Set ExternalKey)
|
|
| 445 | -loadExternalGraphModule msg home_unit in_progress mod
|
|
| 446 | - | homeUnitId home_unit /= moduleUnitId mod = do
|
|
| 447 | - loadExternalPackageBelow in_progress (moduleUnitId mod)
|
|
| 448 | - | otherwise = do
|
|
| 449 | - |
|
| 450 | - let key = ExternalModuleKey $ ModNodeKeyWithUid (GWIB (moduleName mod) NotBoot) (moduleUnitId mod)
|
|
| 451 | - graph <- eps_module_graph <$> getEps
|
|
| 452 | - |
|
| 453 | - if (not (isFullyLoadedModule key graph || Set.member key in_progress))
|
|
| 454 | - then actuallyLoadExternalGraphModule msg home_unit in_progress key mod
|
|
| 455 | - else return in_progress
|
|
| 456 | - |
|
| 457 | --- | Load the interface for a module, and all its transitive dependenices.
|
|
| 458 | -actuallyLoadExternalGraphModule
|
|
| 459 | - :: (Module -> SDoc)
|
|
| 460 | - -> HomeUnit
|
|
| 461 | - -> Set.Set ExternalKey
|
|
| 462 | - -> ExternalKey
|
|
| 463 | - -> Module
|
|
| 464 | - -> IOEnv (Env IfGblEnv lcl) (Set.Set ExternalKey)
|
|
| 465 | -actuallyLoadExternalGraphModule msg home_unit in_progress key mod = do
|
|
| 466 | - dflags <- getDynFlags
|
|
| 467 | - let ctx = initSDocContext dflags defaultUserStyle
|
|
| 468 | - iface <- withIfaceErr ctx $
|
|
| 469 | - loadInterface (msg mod) mod (ImportByUser NotBoot)
|
|
| 470 | - |
|
| 471 | - let deps = mi_deps iface
|
|
| 472 | - mod_deps = dep_direct_mods deps
|
|
| 473 | - pkg_deps = dep_direct_pkgs deps
|
|
| 474 | - |
|
| 475 | - -- Do not attempt to load the same key again when traversing
|
|
| 476 | - let in_progress' = Set.insert key in_progress
|
|
| 477 | - |
|
| 478 | - -- Load all direct dependencies that are in the home package
|
|
| 479 | - cache_mods <- loadExternalGraphBelow msg (Just home_unit) in_progress'
|
|
| 480 | - $ map (\(uid, GWIB mn _) -> mkModule (RealUnit (Definite uid)) mn)
|
|
| 481 | - $ Set.toList mod_deps
|
|
| 482 | - |
|
| 483 | - -- Load all the package nodes, and packages beneath them.
|
|
| 484 | - cache_pkgs <- foldM loadExternalPackageBelow cache_mods (Set.toList pkg_deps)
|
|
| 485 | - |
|
| 486 | - registerFullyLoaded key
|
|
| 487 | - return cache_pkgs
|
|
| 488 | - |
|
| 489 | -registerFullyLoaded :: ExternalKey -> IfM lcl ()
|
|
| 490 | -registerFullyLoaded key = do
|
|
| 491 | - -- Update the external graph with this module being fully loaded.
|
|
| 492 | - logger <- getLogger
|
|
| 493 | - liftIO $ trace_if logger (text "Fully loaded:" <+> ppr key)
|
|
| 494 | - updateEps_ $ \eps ->
|
|
| 495 | - eps{eps_module_graph = setFullyLoadedModule key (eps_module_graph eps)}
|
|
| 496 | - |
|
| 497 | -loadExternalPackageBelow :: Set.Set ExternalKey -> UnitId -> IfM lcl (Set.Set ExternalKey)
|
|
| 498 | -loadExternalPackageBelow in_progress uid = do
|
|
| 499 | - graph <- eps_module_graph <$> getEps
|
|
| 500 | - us <- hsc_units <$> getTopEnv
|
|
| 501 | - let key = ExternalPackageKey uid
|
|
| 502 | - if not (isFullyLoadedModule key graph || Set.member key in_progress)
|
|
| 503 | - then do
|
|
| 504 | - let in_progress' = Set.insert key in_progress
|
|
| 505 | - case unitDepends <$> lookupUnitId us uid of
|
|
| 506 | - Just dep_uids -> do
|
|
| 507 | - loadPackageIntoEPSGraph uid dep_uids
|
|
| 508 | - final_cache <- foldM loadExternalPackageBelow in_progress' dep_uids
|
|
| 509 | - registerFullyLoaded key
|
|
| 510 | - return final_cache
|
|
| 511 | - Nothing -> pprPanic "loadExternalPackagesBelow: missing" (ppr uid)
|
|
| 512 | - else
|
|
| 513 | - return in_progress
|
|
| 514 | - |
|
| 515 | -loadPackageIntoEPSGraph :: UnitId -> [UnitId] -> IfM lcl ()
|
|
| 516 | -loadPackageIntoEPSGraph uid dep_uids =
|
|
| 517 | - updateEps_ $ \eps ->
|
|
| 518 | - eps { eps_module_graph =
|
|
| 519 | - extendExternalModuleGraph (NodeExternalPackage uid
|
|
| 520 | - (Set.fromList dep_uids)) (eps_module_graph eps) }
|
|
| 521 | - |
|
| 522 | 412 | ------------------
|
| 523 | 413 | loadInterface :: SDoc -> Module -> WhereFrom
|
| 524 | 414 | -> IfM lcl (MaybeErr MissingInterfaceError ModIface)
|
| ... | ... | @@ -628,15 +518,6 @@ loadInterface doc_str mod from |
| 628 | 518 | ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface)
|
| 629 | 519 | ; purged_hsc_env <- getTopEnv
|
| 630 | 520 | |
| 631 | - ; let direct_deps = map (uncurry (flip ModNodeKeyWithUid)) $ (Set.toList (dep_direct_mods $ mi_deps iface))
|
|
| 632 | - ; let direct_pkg_deps = Set.toList $ dep_direct_pkgs $ mi_deps iface
|
|
| 633 | - ; let !module_graph_key =
|
|
| 634 | - if moduleUnitId mod `elem` hsc_all_home_unit_ids hsc_env
|
|
| 635 | - --- ^ home unit mods in eps can only happen in oneshot mode
|
|
| 636 | - then Just $ NodeHomePackage (miKey iface) (map ExternalModuleKey direct_deps
|
|
| 637 | - ++ map ExternalPackageKey direct_pkg_deps)
|
|
| 638 | - else Nothing
|
|
| 639 | - |
|
| 640 | 521 | ; let final_iface = iface
|
| 641 | 522 | & set_mi_decls (panic "No mi_decls in PIT")
|
| 642 | 523 | & set_mi_insts (panic "No mi_insts in PIT")
|
| ... | ... | @@ -678,11 +559,6 @@ loadInterface doc_str mod from |
| 678 | 559 | eps_iface_bytecode = add_bytecode (eps_iface_bytecode eps),
|
| 679 | 560 | eps_rule_base = extendRuleBaseList (eps_rule_base eps)
|
| 680 | 561 | new_eps_rules,
|
| 681 | - eps_module_graph =
|
|
| 682 | - let eps_graph' = case module_graph_key of
|
|
| 683 | - Just k -> extendExternalModuleGraph k (eps_module_graph eps)
|
|
| 684 | - Nothing -> eps_module_graph eps
|
|
| 685 | - in eps_graph',
|
|
| 686 | 562 | eps_complete_matches
|
| 687 | 563 | = eps_complete_matches eps ++ new_eps_complete_matches,
|
| 688 | 564 | eps_inst_env = extendInstEnvList (eps_inst_env eps)
|
| ... | ... | @@ -792,6 +668,9 @@ dontLeakTheHUG thing_inside = do |
| 792 | 668 | -- tweak.
|
| 793 | 669 | old_unit_env = hsc_unit_env hsc_env
|
| 794 | 670 | keepFor20509
|
| 671 | + -- oneshot mode does not support backpack
|
|
| 672 | + -- and we want to avoid prodding the hsc_mod_graph thunk
|
|
| 673 | + | isOneShot (ghcMode (hsc_dflags hsc_env)) = False
|
|
| 795 | 674 | | mgHasHoles (hsc_mod_graph hsc_env) = True
|
| 796 | 675 | | otherwise = False
|
| 797 | 676 | pruneHomeUnitEnv hme = do
|
| ... | ... | @@ -1012,12 +891,10 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do |
| 1012 | 891 | |
| 1013 | 892 | let profile = targetProfile dflags
|
| 1014 | 893 | unit_state = hsc_units hsc_env
|
| 1015 | - fc = hsc_FC hsc_env
|
|
| 1016 | 894 | name_cache = hsc_NC hsc_env
|
| 1017 | 895 | mhome_unit = hsc_home_unit_maybe hsc_env
|
| 1018 | 896 | dflags = hsc_dflags hsc_env
|
| 1019 | 897 | logger = hsc_logger hsc_env
|
| 1020 | - other_fopts = initFinderOpts . homeUnitEnv_dflags <$> (hsc_HUG hsc_env)
|
|
| 1021 | 898 | |
| 1022 | 899 | |
| 1023 | 900 | trace_if logger (sep [hsep [text "Reading",
|
| ... | ... | @@ -1036,9 +913,8 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do |
| 1036 | 913 | let iface = getGhcPrimIface hsc_env
|
| 1037 | 914 | return (Succeeded (iface, panic "GHC.Prim ModLocation (findAndReadIface)"))
|
| 1038 | 915 | else do
|
| 1039 | - let fopts = initFinderOpts dflags
|
|
| 1040 | 916 | -- Look for the file
|
| 1041 | - mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod hi_boot_file)
|
|
| 917 | + mb_found <- liftIO (findExactModule hsc_env mod hi_boot_file)
|
|
| 1042 | 918 | case mb_found of
|
| 1043 | 919 | InstalledFound loc -> do
|
| 1044 | 920 | -- See Note [Home module load error]
|
| ... | ... | @@ -1101,7 +977,6 @@ read_file :: Logger -> NameCache -> UnitState -> DynFlags |
| 1101 | 977 | -> Module -> FilePath
|
| 1102 | 978 | -> IO (MaybeErr ReadInterfaceError (ModIface, FilePath))
|
| 1103 | 979 | read_file logger name_cache unit_state dflags wanted_mod file_path = do
|
| 1104 | - trace_if logger (text "readIFace" <+> text file_path)
|
|
| 1105 | 980 | |
| 1106 | 981 | -- Figure out what is recorded in mi_module. If this is
|
| 1107 | 982 | -- a fully definite interface, it'll match exactly, but
|
| ... | ... | @@ -1112,7 +987,7 @@ read_file logger name_cache unit_state dflags wanted_mod file_path = do |
| 1112 | 987 | (_, Just indef_mod) ->
|
| 1113 | 988 | instModuleToModule unit_state
|
| 1114 | 989 | (uninstantiateInstantiatedModule indef_mod)
|
| 1115 | - read_result <- readIface dflags name_cache wanted_mod' file_path
|
|
| 990 | + read_result <- readIface logger dflags name_cache wanted_mod' file_path
|
|
| 1116 | 991 | case read_result of
|
| 1117 | 992 | Failed err -> return (Failed err)
|
| 1118 | 993 | Succeeded iface -> return (Succeeded (iface, file_path))
|
| ... | ... | @@ -1139,12 +1014,14 @@ flagsToIfCompression dflags |
| 1139 | 1014 | -- Failed err <=> file not found, or unreadable, or illegible
|
| 1140 | 1015 | -- Succeeded iface <=> successfully found and parsed
|
| 1141 | 1016 | readIface
|
| 1142 | - :: DynFlags
|
|
| 1017 | + :: Logger
|
|
| 1018 | + -> DynFlags
|
|
| 1143 | 1019 | -> NameCache
|
| 1144 | 1020 | -> Module
|
| 1145 | 1021 | -> FilePath
|
| 1146 | 1022 | -> IO (MaybeErr ReadInterfaceError ModIface)
|
| 1147 | -readIface dflags name_cache wanted_mod file_path = do
|
|
| 1023 | +readIface logger dflags name_cache wanted_mod file_path = do
|
|
| 1024 | + trace_if logger (text "readIFace" <+> text file_path)
|
|
| 1148 | 1025 | let profile = targetProfile dflags
|
| 1149 | 1026 | res <- tryMost $ readBinIface profile name_cache CheckHiWay QuietBinIFace file_path
|
| 1150 | 1027 | case res of
|
| ... | ... | @@ -23,7 +23,6 @@ import GHC.Prelude |
| 23 | 23 | import GHC.Data.FastString
|
| 24 | 24 | |
| 25 | 25 | import GHC.Driver.Backend
|
| 26 | -import GHC.Driver.Config.Finder
|
|
| 27 | 26 | import GHC.Driver.Env
|
| 28 | 27 | import GHC.Driver.DynFlags
|
| 29 | 28 | import GHC.Driver.Ppr
|
| ... | ... | @@ -303,7 +302,7 @@ check_old_iface hsc_env mod_summary maybe_iface |
| 303 | 302 | |
| 304 | 303 | loadIface read_dflags iface_path = do
|
| 305 | 304 | let ncu = hsc_NC hsc_env
|
| 306 | - read_result <- readIface read_dflags ncu (ms_mod mod_summary) iface_path
|
|
| 305 | + read_result <- readIface logger read_dflags ncu (ms_mod mod_summary) iface_path
|
|
| 307 | 306 | case read_result of
|
| 308 | 307 | Failed err -> do
|
| 309 | 308 | let msg = readInterfaceErrorDiagnostic err
|
| ... | ... | @@ -635,7 +634,7 @@ checkDependencies :: HscEnv -> ModSummary -> ModIface -> IfG RecompileRequired |
| 635 | 634 | checkDependencies hsc_env summary iface
|
| 636 | 635 | = do
|
| 637 | 636 | res_normal <- classify_import (findImportedModule hsc_env) (ms_textual_imps summary ++ ms_srcimps summary)
|
| 638 | - res_plugin <- classify_import (\mod _ -> findPluginModule fc fopts units mhome_unit mod) (ms_plugin_imps summary)
|
|
| 637 | + res_plugin <- classify_import (\mod _ -> findPluginModule hsc_env mod) (ms_plugin_imps summary)
|
|
| 639 | 638 | case sequence (res_normal ++ res_plugin) of
|
| 640 | 639 | Left recomp -> return $ NeedsRecompile recomp
|
| 641 | 640 | Right es -> do
|
| ... | ... | @@ -657,13 +656,8 @@ checkDependencies hsc_env summary iface |
| 657 | 656 | let reason = ModuleChanged mod
|
| 658 | 657 | in classify reason <$> find_import mod mb_pkg)
|
| 659 | 658 | imports
|
| 660 | - dflags = hsc_dflags hsc_env
|
|
| 661 | - fopts = initFinderOpts dflags
|
|
| 662 | 659 | logger = hsc_logger hsc_env
|
| 663 | - fc = hsc_FC hsc_env
|
|
| 664 | - mhome_unit = hsc_home_unit_maybe hsc_env
|
|
| 665 | 660 | all_home_units = hsc_all_home_unit_ids hsc_env
|
| 666 | - units = hsc_units hsc_env
|
|
| 667 | 661 | prev_dep_mods = map (second gwib_mod) $ Set.toAscList $ dep_direct_mods (mi_deps iface)
|
| 668 | 662 | prev_dep_pkgs = Set.toAscList (Set.union (dep_direct_pkgs (mi_deps iface))
|
| 669 | 663 | (dep_plugin_pkgs (mi_deps iface)))
|
| ... | ... | @@ -228,31 +228,6 @@ See Note [Home module build products] for some more information about that. |
| 228 | 228 | The only other place where the flag is consulted is when enabling code generation
|
| 229 | 229 | with `-fno-code`, which does so to anticipate what decision we will make at the
|
| 230 | 230 | splice point about what we would prefer.
|
| 231 | - |
|
| 232 | -Note [Reachability in One-shot mode vs Make mode]
|
|
| 233 | -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
|
| 234 | -Why are there two code paths in `get_reachable_nodes`? (ldOneShotMode vs otherwise)
|
|
| 235 | - |
|
| 236 | -In one-shot mode, the home package modules are loaded into the EPS,
|
|
| 237 | -whereas for --make mode, the home package modules are in the HUG/HPT.
|
|
| 238 | - |
|
| 239 | -For both of these cases, we cache the calculation of transitive
|
|
| 240 | -dependencies in a 'ModuleGraph'. For the --make case, the relevant
|
|
| 241 | -'ModuleGraph' is in the EPS, the other case uses the 'ModuleGraph'
|
|
| 242 | -for the home modules.
|
|
| 243 | - |
|
| 244 | -The home modules graph is known statically after downsweep.
|
|
| 245 | -On the contrary, the EPS module graph is only extended when a
|
|
| 246 | -module is loaded into the EPS -- which is done lazily as needed.
|
|
| 247 | -Therefore, for get_link_deps, we need to force the transitive
|
|
| 248 | -closure to be loaded before querying the graph for the reachable
|
|
| 249 | -link dependencies -- done in the call to 'loadExternalGraphBelow'.
|
|
| 250 | -Because we cache the transitive closure, this work is only done once.
|
|
| 251 | - |
|
| 252 | -After forcing the modules with the call to 'loadExternalGraphBelow' in
|
|
| 253 | -'get_reachable_nodes', the external module graph has all edges needed to
|
|
| 254 | -compute the full transitive closure so we can proceed just like we do in the
|
|
| 255 | -second path with a normal module graph.
|
|
| 256 | 231 | -}
|
| 257 | 232 | |
| 258 | 233 | dieWith :: LinkDepsOpts -> SrcSpan -> SDoc -> IO a
|
| ... | ... | @@ -76,12 +76,10 @@ import GHC.Utils.Logger |
| 76 | 76 | import GHC.Utils.TmpFs
|
| 77 | 77 | |
| 78 | 78 | import GHC.Unit.Env
|
| 79 | -import GHC.Unit.Home
|
|
| 80 | 79 | import GHC.Unit.Home.ModInfo
|
| 81 | 80 | import GHC.Unit.External (ExternalPackageState (..))
|
| 82 | 81 | import GHC.Unit.Module
|
| 83 | 82 | import GHC.Unit.Module.ModNodeKey
|
| 84 | -import GHC.Unit.Module.External.Graph
|
|
| 85 | 83 | import GHC.Unit.Module.Graph
|
| 86 | 84 | import GHC.Unit.Module.ModIface
|
| 87 | 85 | import GHC.Unit.State as Packages
|
| ... | ... | @@ -119,6 +117,9 @@ import System.Win32.Info (getSystemDirectory) |
| 119 | 117 | |
| 120 | 118 | import GHC.Utils.Exception
|
| 121 | 119 | import GHC.Unit.Home.Graph (lookupHug, unitEnv_foldWithKey)
|
| 120 | +import GHC.Driver.Downsweep
|
|
| 121 | + |
|
| 122 | + |
|
| 122 | 123 | |
| 123 | 124 | -- Note [Linkers and loaders]
|
| 124 | 125 | -- ~~~~~~~~~~~~~~~~~~~~~~~~~~
|
| ... | ... | @@ -615,89 +616,53 @@ initLinkDepsOpts hsc_env = opts |
| 615 | 616 | dflags = hsc_dflags hsc_env
|
| 616 | 617 | |
| 617 | 618 | ldLoadByteCode mod = do
|
| 619 | + _ <- initIfaceLoad hsc_env $
|
|
| 620 | + loadInterface (text "get_reachable_nodes" <+> parens (ppr mod))
|
|
| 621 | + mod ImportBySystem
|
|
| 618 | 622 | EPS {eps_iface_bytecode} <- hscEPS hsc_env
|
| 619 | 623 | sequence (lookupModuleEnv eps_iface_bytecode mod)
|
| 620 | 624 | |
| 621 | 625 | |
| 622 | --- See Note [Reachability in One-shot mode vs Make mode]
|
|
| 623 | 626 | get_reachable_nodes :: HscEnv -> [Module] -> IO ([Module], UniqDSet UnitId)
|
| 624 | 627 | get_reachable_nodes hsc_env mods
|
| 625 | 628 | |
| 626 | - -- Reachability on 'ExternalModuleGraph' (for one shot mode)
|
|
| 627 | - | isOneShot (ghcMode dflags)
|
|
| 629 | + -- Fallback case if the ModuleGraph has not been initialised by the user.
|
|
| 630 | + -- This can happen if is the user is loading plugins or doing something else very
|
|
| 631 | + -- early in the compiler pipeline.
|
|
| 632 | + | isEmptyMG (hsc_mod_graph hsc_env)
|
|
| 628 | 633 | = do
|
| 629 | - initIfaceCheck (text "loader") hsc_env
|
|
| 630 | - $ void $ loadExternalGraphBelow msg (hsc_home_unit_maybe hsc_env) Set.empty mods
|
|
| 631 | - -- Read the EPS only after `loadExternalGraphBelow`
|
|
| 632 | - eps <- hscEPS hsc_env
|
|
| 633 | - let
|
|
| 634 | - emg = eps_module_graph eps
|
|
| 635 | - get_mod_info_eps (ModNodeKeyWithUid gwib uid)
|
|
| 636 | - | uid == homeUnitId (ue_unsafeHomeUnit unit_env)
|
|
| 637 | - = case lookupModuleEnv (eps_PIT eps) (Module (RealUnit $ Definite uid) (gwib_mod gwib)) of
|
|
| 638 | - Just iface -> return $ Just iface
|
|
| 639 | - Nothing -> moduleNotLoaded "(in EPS)" gwib uid
|
|
| 640 | - | otherwise
|
|
| 641 | - = return Nothing
|
|
| 642 | - |
|
| 643 | - get_mod_key m
|
|
| 644 | - | moduleUnitId m == homeUnitId (ue_unsafeHomeUnit unit_env)
|
|
| 645 | - = ExternalModuleKey (mkModuleNk m)
|
|
| 646 | - | otherwise = ExternalPackageKey (moduleUnitId m)
|
|
| 647 | - |
|
| 648 | - go get_mod_key emgNodeKey (emgReachableLoopMany emg) (map emgProject) get_mod_info_eps
|
|
| 634 | + mg <- downsweepInstalledModules hsc_env mods
|
|
| 635 | + go mg
|
|
| 649 | 636 | |
| 650 | - -- Reachability on 'ModuleGraph' (for --make mode)
|
|
| 651 | 637 | | otherwise
|
| 652 | - = go hmgModKey mkNodeKey (mgReachableLoop hmGraph) (catMaybes . map hmgProject) get_mod_info_hug
|
|
| 638 | + = go (hsc_mod_graph hsc_env)
|
|
| 653 | 639 | |
| 654 | 640 | where
|
| 655 | - dflags = hsc_dflags hsc_env
|
|
| 656 | 641 | unit_env = hsc_unit_env hsc_env
|
| 657 | 642 | mkModuleNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m)
|
| 658 | - msg mod =
|
|
| 659 | - text "need to link module" <+> ppr mod <+>
|
|
| 660 | - text "and the modules below it, due to use of Template Haskell"
|
|
| 661 | - |
|
| 662 | - hmGraph = hsc_mod_graph hsc_env
|
|
| 663 | 643 | |
| 664 | - hmgModKey m
|
|
| 644 | + hmgModKey mg m
|
|
| 665 | 645 | | let k = NodeKey_Module (mkModuleNk m)
|
| 666 | - , mgMember hmGraph k = k
|
|
| 646 | + , mgMember mg k = k
|
|
| 667 | 647 | | otherwise = NodeKey_ExternalUnit (moduleUnitId m)
|
| 668 | 648 | |
| 669 | - hmgProject = \case
|
|
| 670 | - NodeKey_Module with_uid -> Just $ Left with_uid
|
|
| 671 | - NodeKey_ExternalUnit uid -> Just $ Right uid
|
|
| 672 | - _ -> Nothing
|
|
| 673 | - |
|
| 674 | - emgProject = \case
|
|
| 675 | - ExternalModuleKey with_uid -> Left with_uid
|
|
| 676 | - ExternalPackageKey uid -> Right uid
|
|
| 677 | - |
|
| 678 | 649 | -- The main driver for getting dependencies, which calls the given
|
| 679 | 650 | -- functions to compute the reachable nodes.
|
| 680 | - go :: (Module -> key)
|
|
| 681 | - -> (node -> key)
|
|
| 682 | - -> ([key] -> [node])
|
|
| 683 | - -> ([key] -> [Either ModNodeKeyWithUid UnitId])
|
|
| 684 | - -> (ModNodeKeyWithUid -> IO (Maybe ModIface))
|
|
| 685 | - -> IO ([Module], UniqDSet UnitId)
|
|
| 686 | - go modKey nodeKey manyReachable project get_mod_info
|
|
| 687 | - | let mod_keys = map modKey mods
|
|
| 688 | - = do
|
|
| 689 | - let (all_home_mods, pkgs_s) = partitionEithers $ project $ mod_keys ++ map nodeKey (manyReachable mod_keys)
|
|
| 690 | - ifaces <- mapMaybeM get_mod_info all_home_mods
|
|
| 691 | - let mods_s = map mi_module ifaces
|
|
| 651 | + go :: ModuleGraph -> IO ([Module], UniqDSet UnitId)
|
|
| 652 | + go mg = do
|
|
| 653 | + let mod_keys = map (hmgModKey mg) mods
|
|
| 654 | + all_reachable = mod_keys ++ map mkNodeKey (mgReachableLoop mg mod_keys)
|
|
| 655 | + (mods_s, pkgs_s) <- partitionEithers <$> mapMaybeM get_mod_info all_reachable
|
|
| 692 | 656 | return (mods_s, mkUniqDSet pkgs_s)
|
| 693 | 657 | |
| 694 | - get_mod_info_hug (ModNodeKeyWithUid gwib uid) =
|
|
| 658 | + get_mod_info :: NodeKey -> IO (Maybe (Either Module UnitId))
|
|
| 659 | + get_mod_info (NodeKey_Module m@(ModNodeKeyWithUid gwib uid)) =
|
|
| 695 | 660 | lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) >>= \case
|
| 696 | - Just hmi -> return $ Just (hm_iface hmi)
|
|
| 697 | - Nothing -> moduleNotLoaded "(in HUG)" gwib uid
|
|
| 661 | + Just hmi -> return $ Just (Left (mi_module (hm_iface hmi)))
|
|
| 662 | + Nothing -> return (Just (Left (mnkToModule m)))
|
|
| 663 | + get_mod_info (NodeKey_ExternalUnit uid) = return (Just (Right uid))
|
|
| 664 | + get_mod_info _ = return Nothing
|
|
| 698 | 665 | |
| 699 | - moduleNotLoaded m gwib uid = throwGhcExceptionIO $ ProgramError $ showSDoc dflags $
|
|
| 700 | - text "getLinkDeps: Home module not loaded" <+> text m <+> ppr (gwib_mod gwib) <+> ppr uid
|
|
| 701 | 666 | |
| 702 | 667 | {- **********************************************************************
|
| 703 | 668 |
| ... | ... | @@ -56,7 +56,6 @@ import GHC.Types.Name.Reader |
| 56 | 56 | import GHC.Types.Unique.DFM
|
| 57 | 57 | |
| 58 | 58 | import GHC.Unit.Finder ( findPluginModule, FindResult(..) )
|
| 59 | -import GHC.Driver.Config.Finder ( initFinderOpts )
|
|
| 60 | 59 | import GHC.Driver.Config.Diagnostic ( initIfaceMessageOpts )
|
| 61 | 60 | import GHC.Unit.Module ( Module, ModuleName, thisGhcUnit, GenModule(moduleUnit), IsBootInterface(NotBoot) )
|
| 62 | 61 | import GHC.Unit.Module.ModIface
|
| ... | ... | @@ -343,13 +342,8 @@ lookupRdrNameInModuleForPlugins :: HasDebugCallStack |
| 343 | 342 | -> IO (Maybe (Name, ModIface))
|
| 344 | 343 | lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do
|
| 345 | 344 | let dflags = hsc_dflags hsc_env
|
| 346 | - let fopts = initFinderOpts dflags
|
|
| 347 | - let fc = hsc_FC hsc_env
|
|
| 348 | - let unit_env = hsc_unit_env hsc_env
|
|
| 349 | - let unit_state = ue_homeUnitState unit_env
|
|
| 350 | - let mhome_unit = hsc_home_unit_maybe hsc_env
|
|
| 351 | 345 | -- First find the unit the module resides in by searching exposed units and home modules
|
| 352 | - found_module <- findPluginModule fc fopts unit_state mhome_unit mod_name
|
|
| 346 | + found_module <- findPluginModule hsc_env mod_name
|
|
| 353 | 347 | case found_module of
|
| 354 | 348 | Found _ mod -> do
|
| 355 | 349 | -- Find the exports of the module
|
| ... | ... | @@ -33,7 +33,6 @@ import GHC.Types.TypeEnv |
| 33 | 33 | import GHC.Types.Unique.DSet
|
| 34 | 34 | |
| 35 | 35 | import GHC.Linker.Types (Linkable)
|
| 36 | -import GHC.Unit.Module.External.Graph
|
|
| 37 | 36 | |
| 38 | 37 | import Data.IORef
|
| 39 | 38 | |
| ... | ... | @@ -72,7 +71,6 @@ initExternalPackageState = EPS |
| 72 | 71 | , eps_PIT = emptyPackageIfaceTable
|
| 73 | 72 | , eps_free_holes = emptyInstalledModuleEnv
|
| 74 | 73 | , eps_PTE = emptyTypeEnv
|
| 75 | - , eps_module_graph = emptyExternalModuleGraph
|
|
| 76 | 74 | , eps_iface_bytecode = emptyModuleEnv
|
| 77 | 75 | , eps_inst_env = emptyInstEnv
|
| 78 | 76 | , eps_fam_inst_env = emptyFamInstEnv
|
| ... | ... | @@ -141,8 +139,6 @@ data ExternalPackageState |
| 141 | 139 | -- for every import, so cache it here. When the PIT
|
| 142 | 140 | -- gets filled in we can drop these entries.
|
| 143 | 141 | |
| 144 | - eps_module_graph :: ExternalModuleGraph,
|
|
| 145 | - |
|
| 146 | 142 | eps_PTE :: !PackageTypeEnv,
|
| 147 | 143 | -- ^ Result of typechecking all the external package
|
| 148 | 144 | -- interface files we have sucked in. The domain of
|
| ... | ... | @@ -66,7 +66,6 @@ import Control.Monad |
| 66 | 66 | import Data.Time
|
| 67 | 67 | import qualified Data.Map as M
|
| 68 | 68 | import GHC.Driver.Env
|
| 69 | - ( hsc_home_unit_maybe, HscEnv(hsc_FC, hsc_dflags, hsc_unit_env) )
|
|
| 70 | 69 | import GHC.Driver.Config.Finder
|
| 71 | 70 | import qualified Data.Set as Set
|
| 72 | 71 | import Data.List.NonEmpty ( NonEmpty (..) )
|
| ... | ... | @@ -224,21 +223,26 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg = |
| 224 | 223 | -- plugin. This consults the same set of exposed packages as
|
| 225 | 224 | -- 'findImportedModule', unless @-hide-all-plugin-packages@ or
|
| 226 | 225 | -- @-plugin-package@ are specified.
|
| 227 | -findPluginModule :: FinderCache -> FinderOpts -> UnitState -> Maybe HomeUnit -> ModuleName -> IO FindResult
|
|
| 228 | -findPluginModule fc fopts units (Just home_unit) mod_name =
|
|
| 226 | +findPluginModuleNoHsc :: FinderCache -> FinderOpts -> UnitState -> Maybe HomeUnit -> ModuleName -> IO FindResult
|
|
| 227 | +findPluginModuleNoHsc fc fopts units (Just home_unit) mod_name =
|
|
| 229 | 228 | findHomeModule fc fopts home_unit mod_name
|
| 230 | 229 | `orIfNotFound`
|
| 231 | 230 | findExposedPluginPackageModule fc fopts units mod_name
|
| 232 | -findPluginModule fc fopts units Nothing mod_name =
|
|
| 231 | +findPluginModuleNoHsc fc fopts units Nothing mod_name =
|
|
| 233 | 232 | findExposedPluginPackageModule fc fopts units mod_name
|
| 234 | 233 | |
| 235 | --- | Locate a specific 'Module'. The purpose of this function is to
|
|
| 236 | --- create a 'ModLocation' for a given 'Module', that is to find out
|
|
| 237 | --- where the files associated with this module live. It is used when
|
|
| 238 | --- reading the interface for a module mentioned by another interface,
|
|
| 239 | --- for example (a "system import").
|
|
| 240 | -findExactModule :: FinderCache -> FinderOpts -> UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
|
|
| 241 | -findExactModule fc fopts other_fopts unit_state mhome_unit mod is_boot = do
|
|
| 234 | +findPluginModule :: HscEnv -> ModuleName -> IO FindResult
|
|
| 235 | +findPluginModule hsc_env mod_name = do
|
|
| 236 | + let fc = hsc_FC hsc_env
|
|
| 237 | + let units = hsc_units hsc_env
|
|
| 238 | + let mhome_unit = hsc_home_unit_maybe hsc_env
|
|
| 239 | + findPluginModuleNoHsc fc (initFinderOpts (hsc_dflags hsc_env)) units mhome_unit mod_name
|
|
| 240 | + |
|
| 241 | + |
|
| 242 | +-- | A version of findExactModule which takes the exact parts of the HscEnv it needs
|
|
| 243 | +-- directly.
|
|
| 244 | +findExactModuleNoHsc :: FinderCache -> FinderOpts -> UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
|
|
| 245 | +findExactModuleNoHsc fc fopts other_fopts unit_state mhome_unit mod is_boot = do
|
|
| 242 | 246 | res <- case mhome_unit of
|
| 243 | 247 | Just home_unit
|
| 244 | 248 | | isHomeInstalledModule home_unit mod
|
| ... | ... | @@ -251,6 +255,21 @@ findExactModule fc fopts other_fopts unit_state mhome_unit mod is_boot = do |
| 251 | 255 | _ -> return res
|
| 252 | 256 | |
| 253 | 257 | |
| 258 | +-- | Locate a specific 'Module'. The purpose of this function is to
|
|
| 259 | +-- create a 'ModLocation' for a given 'Module', that is to find out
|
|
| 260 | +-- where the files associated with this module live. It is used when
|
|
| 261 | +-- reading the interface for a module mentioned by another interface,
|
|
| 262 | +-- for example (a "system import").
|
|
| 263 | +findExactModule :: HscEnv -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
|
|
| 264 | +findExactModule hsc_env mod is_boot = do
|
|
| 265 | + let dflags = hsc_dflags hsc_env
|
|
| 266 | + let fc = hsc_FC hsc_env
|
|
| 267 | + let unit_state = hsc_units hsc_env
|
|
| 268 | + let home_unit = hsc_home_unit_maybe hsc_env
|
|
| 269 | + let other_fopts = initFinderOpts . homeUnitEnv_dflags <$> (hsc_HUG hsc_env)
|
|
| 270 | + findExactModuleNoHsc fc (initFinderOpts dflags) other_fopts unit_state home_unit mod is_boot
|
|
| 271 | + |
|
| 272 | + |
|
| 254 | 273 | -- -----------------------------------------------------------------------------
|
| 255 | 274 | -- Helpers
|
| 256 | 275 |
| 1 | -{-# LANGUAGE LambdaCase #-}
|
|
| 2 | -{-# LANGUAGE RecordWildCards #-}
|
|
| 3 | - |
|
| 4 | --- | Like @'GHC.Unit.Module.Graph'@ but for the @'ExternalModuleGraph'@ which is
|
|
| 5 | --- stored in the EPS.
|
|
| 6 | -module GHC.Unit.Module.External.Graph
|
|
| 7 | - ( -- * External Module Graph
|
|
| 8 | - --
|
|
| 9 | - -- | A module graph for the EPS.
|
|
| 10 | - ExternalModuleGraph, ExternalGraphNode(..)
|
|
| 11 | - , ExternalKey(..), emptyExternalModuleGraph
|
|
| 12 | - , emgNodeKey, emgNodeDeps, emgLookupKey
|
|
| 13 | - |
|
| 14 | - -- * Extending
|
|
| 15 | - --
|
|
| 16 | - -- | The @'ExternalModuleGraph'@ is a structure which is incrementally
|
|
| 17 | - -- updated as the 'ExternalPackageState' (EPS) is updated (when an iface is
|
|
| 18 | - -- loaded, in 'loadInterface').
|
|
| 19 | - --
|
|
| 20 | - -- Therefore, there is an operation for extending the 'ExternalModuleGraph',
|
|
| 21 | - -- unlike @'GHC.Unit.Module.Graph.ModuleGraph'@, which is constructed once
|
|
| 22 | - -- during downsweep and never altered (since all of the home units
|
|
| 23 | - -- dependencies are fully known then).
|
|
| 24 | - , extendExternalModuleGraph
|
|
| 25 | - |
|
| 26 | - -- * Loading
|
|
| 27 | - --
|
|
| 28 | - -- | As mentioned in the top-level haddocks for the
|
|
| 29 | - -- 'extendExternalModuleGraph', the external module graph is incrementally
|
|
| 30 | - -- updated as interfaces are loaded. This module graph keeps an additional
|
|
| 31 | - -- cache registering which modules have already been fully loaded.
|
|
| 32 | - --
|
|
| 33 | - -- This cache is necessary to quickly check when a full-transitive-closure
|
|
| 34 | - -- reachability query would be valid for some module.
|
|
| 35 | - --
|
|
| 36 | - -- Such a query may be invalid if ran on a module in the
|
|
| 37 | - -- 'ExternalModuleGraph' whose dependencies have /not yet/ been fully loaded
|
|
| 38 | - -- into the EPS.
|
|
| 39 | - -- (Recall that interfaces are lazily loaded, and the 'ExternalModuleGraph'
|
|
| 40 | - -- is only incrementally updated).
|
|
| 41 | - --
|
|
| 42 | - -- To guarantee the full transitive closure of a given module is completely
|
|
| 43 | - -- loaded into the EPS (i.e. all interfaces of the modules below this one
|
|
| 44 | - -- are also loaded), see @'loadExternalGraphBelow'@ in
|
|
| 45 | - -- 'GHC.Iface.Load'.
|
|
| 46 | - , isFullyLoadedModule
|
|
| 47 | - , setFullyLoadedModule
|
|
| 48 | - |
|
| 49 | - -- * Reachability
|
|
| 50 | - --
|
|
| 51 | - -- | Fast reachability queries on the external module graph. Similar to
|
|
| 52 | - -- reachability queries on 'GHC.Unit.Module.Graph'.
|
|
| 53 | - , emgReachableLoop
|
|
| 54 | - , emgReachableLoopMany
|
|
| 55 | - ) where
|
|
| 56 | - |
|
| 57 | -import GHC.Prelude
|
|
| 58 | -import GHC.Unit.Module.Graph
|
|
| 59 | -import GHC.Data.Graph.Directed.Reachability
|
|
| 60 | -import GHC.Data.Graph.Directed
|
|
| 61 | -import qualified Data.Map as M
|
|
| 62 | -import qualified Data.Set as S
|
|
| 63 | -import Data.Bifunctor (first, bimap)
|
|
| 64 | -import Data.Maybe
|
|
| 65 | -import GHC.Utils.Outputable
|
|
| 66 | -import GHC.Unit.Types (UnitId, GenWithIsBoot(..), IsBootInterface(..), mkModule)
|
|
| 67 | -import GHC.Utils.Misc
|
|
| 68 | - |
|
| 69 | - |
|
| 70 | ---------------------------------------------------------------------------------
|
|
| 71 | --- * Main
|
|
| 72 | ---------------------------------------------------------------------------------
|
|
| 73 | - |
|
| 74 | -data ExternalModuleGraph = ExternalModuleGraph
|
|
| 75 | - { external_nodes :: [ExternalGraphNode]
|
|
| 76 | - -- This transitive dependency query does not contain hs-boot nodes.
|
|
| 77 | - , external_trans :: (ReachabilityIndex ExternalNode, ExternalKey -> Maybe ExternalNode)
|
|
| 78 | - , external_fully_loaded :: !(S.Set ExternalKey) }
|
|
| 79 | - |
|
| 80 | -type ExternalNode = Node Int ExternalGraphNode
|
|
| 81 | - |
|
| 82 | -data ExternalGraphNode
|
|
| 83 | - -- | A node for a home package module that is inserted in the EPS.
|
|
| 84 | - --
|
|
| 85 | - -- INVARIANT: This type of node can only ever exist if compiling in one-shot
|
|
| 86 | - -- mode. In --make mode, it is imperative that the EPS doesn't have any home
|
|
| 87 | - -- package modules ever.
|
|
| 88 | - = NodeHomePackage
|
|
| 89 | - { externalNodeKey :: ModNodeKeyWithUid
|
|
| 90 | - , externalNodeDeps :: [ExternalKey] }
|
|
| 91 | - -- | A node for packages with at least one module loaded in the EPS.
|
|
| 92 | - --
|
|
| 93 | - -- Edge from A to NodeExternalPackage p when A has p as a direct package
|
|
| 94 | - -- dependency.
|
|
| 95 | - | NodeExternalPackage
|
|
| 96 | - { externalPkgKey :: UnitId
|
|
| 97 | - , externalPkgDeps :: S.Set UnitId
|
|
| 98 | - }
|
|
| 99 | - |
|
| 100 | -data ExternalKey
|
|
| 101 | - = ExternalModuleKey ModNodeKeyWithUid
|
|
| 102 | - | ExternalPackageKey UnitId
|
|
| 103 | - deriving (Eq, Ord)
|
|
| 104 | - |
|
| 105 | -emptyExternalModuleGraph :: ExternalModuleGraph
|
|
| 106 | -emptyExternalModuleGraph = ExternalModuleGraph [] (graphReachability emptyGraph, const Nothing) S.empty
|
|
| 107 | - |
|
| 108 | --- | Get the dependencies of an 'ExternalNode'
|
|
| 109 | -emgNodeDeps :: Bool -> ExternalGraphNode -> [ExternalKey]
|
|
| 110 | -emgNodeDeps drop_hs_boot_nodes = \case
|
|
| 111 | - NodeHomePackage _ dps -> map drop_hs_boot dps
|
|
| 112 | - NodeExternalPackage _ dps -> map ExternalPackageKey $ S.toList dps
|
|
| 113 | - where
|
|
| 114 | - -- Drop hs-boot nodes by using HsSrcFile as the key
|
|
| 115 | - hs_boot_key | drop_hs_boot_nodes = NotBoot -- is regular mod or signature
|
|
| 116 | - | otherwise = IsBoot
|
|
| 117 | - |
|
| 118 | - drop_hs_boot (ExternalModuleKey (ModNodeKeyWithUid (GWIB mn IsBoot) uid)) = (ExternalModuleKey (ModNodeKeyWithUid (GWIB mn hs_boot_key) uid))
|
|
| 119 | - drop_hs_boot x = x
|
|
| 120 | - |
|
| 121 | --- | The graph key for a given node
|
|
| 122 | -emgNodeKey :: ExternalGraphNode -> ExternalKey
|
|
| 123 | -emgNodeKey (NodeHomePackage k _) = ExternalModuleKey k
|
|
| 124 | -emgNodeKey (NodeExternalPackage k _) = ExternalPackageKey k
|
|
| 125 | - |
|
| 126 | --- | Lookup a key in the EMG.
|
|
| 127 | -emgLookupKey :: ExternalKey -> ExternalModuleGraph -> Maybe ExternalGraphNode
|
|
| 128 | -emgLookupKey k emg = node_payload <$> (snd (external_trans emg)) k
|
|
| 129 | - |
|
| 130 | ---------------------------------------------------------------------------------
|
|
| 131 | --- * Extending
|
|
| 132 | ---------------------------------------------------------------------------------
|
|
| 133 | - |
|
| 134 | -extendExternalModuleGraph :: ExternalGraphNode -> ExternalModuleGraph -> ExternalModuleGraph
|
|
| 135 | -extendExternalModuleGraph node ExternalModuleGraph{..} =
|
|
| 136 | - ExternalModuleGraph
|
|
| 137 | - { external_fully_loaded = external_fully_loaded
|
|
| 138 | - , external_nodes = node : external_nodes
|
|
| 139 | - , external_trans = first cyclicGraphReachability $
|
|
| 140 | - externalGraphNodes True (node : external_nodes)
|
|
| 141 | - }
|
|
| 142 | - |
|
| 143 | ---------------------------------------------------------------------------------
|
|
| 144 | --- * Loading
|
|
| 145 | ---------------------------------------------------------------------------------
|
|
| 146 | - |
|
| 147 | -isFullyLoadedModule :: ExternalKey -> ExternalModuleGraph -> Bool
|
|
| 148 | -isFullyLoadedModule key graph = S.member key (external_fully_loaded graph)
|
|
| 149 | - |
|
| 150 | -setFullyLoadedModule :: ExternalKey -> ExternalModuleGraph -> ExternalModuleGraph
|
|
| 151 | -setFullyLoadedModule key graph = graph { external_fully_loaded = S.insert key (external_fully_loaded graph)}
|
|
| 152 | - |
|
| 153 | ---------------------------------------------------------------------------------
|
|
| 154 | --- * Reachability
|
|
| 155 | ---------------------------------------------------------------------------------
|
|
| 156 | - |
|
| 157 | --- | Return all nodes reachable from the given key, also known as its full
|
|
| 158 | --- transitive closure.
|
|
| 159 | ---
|
|
| 160 | --- @Nothing@ if the key couldn't be found in the graph.
|
|
| 161 | -emgReachableLoop :: ExternalModuleGraph -> ExternalKey -> Maybe [ExternalGraphNode]
|
|
| 162 | -emgReachableLoop mg nk = map node_payload <$> modules_below where
|
|
| 163 | - (td_map, lookup_node) = external_trans mg
|
|
| 164 | - modules_below =
|
|
| 165 | - allReachable td_map <$> lookup_node nk
|
|
| 166 | - |
|
| 167 | --- | Return all nodes reachable from all of the given keys.
|
|
| 168 | -emgReachableLoopMany :: ExternalModuleGraph -> [ExternalKey] -> [ExternalGraphNode]
|
|
| 169 | -emgReachableLoopMany mg nk = map node_payload modules_below where
|
|
| 170 | - (td_map, lookup_node) = external_trans mg
|
|
| 171 | - modules_below =
|
|
| 172 | - allReachableMany td_map (mapMaybe lookup_node nk)
|
|
| 173 | - |
|
| 174 | ---------------------------------------------------------------------------------
|
|
| 175 | --- * Internals
|
|
| 176 | ---------------------------------------------------------------------------------
|
|
| 177 | - |
|
| 178 | --- | Turn a list of graph nodes into an efficient queriable graph.
|
|
| 179 | --- The first boolean parameter indicates whether nodes corresponding to hs-boot files
|
|
| 180 | --- should be collapsed into their relevant hs nodes.
|
|
| 181 | -externalGraphNodes :: Bool
|
|
| 182 | - -> [ExternalGraphNode]
|
|
| 183 | - -> (Graph ExternalNode, ExternalKey -> Maybe ExternalNode)
|
|
| 184 | -externalGraphNodes drop_hs_boot_nodes summaries =
|
|
| 185 | - (graphFromEdgedVerticesUniq nodes, lookup_node)
|
|
| 186 | - where
|
|
| 187 | - -- Map from module to extra boot summary dependencies which need to be merged in
|
|
| 188 | - (boot_summaries, nodes) = bimap M.fromList id $ partitionWith go numbered_summaries
|
|
| 189 | - |
|
| 190 | - where
|
|
| 191 | - go (s, key) =
|
|
| 192 | - case s of
|
|
| 193 | - NodeHomePackage (ModNodeKeyWithUid (GWIB mn IsBoot) uid) _deps | drop_hs_boot_nodes
|
|
| 194 | - -- Using emgNodeDeps here converts dependencies on other
|
|
| 195 | - -- boot files to dependencies on dependencies on non-boot files.
|
|
| 196 | - -> Left (mkModule uid mn, emgNodeDeps drop_hs_boot_nodes s)
|
|
| 197 | - _ -> normal_case
|
|
| 198 | - where
|
|
| 199 | - normal_case =
|
|
| 200 | - let lkup_key =
|
|
| 201 | - case s of
|
|
| 202 | - NodeHomePackage (ModNodeKeyWithUid (GWIB mn IsBoot) uid) _deps
|
|
| 203 | - -> Just $ mkModule uid mn
|
|
| 204 | - _ -> Nothing
|
|
| 205 | - |
|
| 206 | - extra = (lkup_key >>= \key -> M.lookup key boot_summaries)
|
|
| 207 | - |
|
| 208 | - in Right $ DigraphNode s key $ out_edge_keys $
|
|
| 209 | - (fromMaybe [] extra
|
|
| 210 | - ++ emgNodeDeps drop_hs_boot_nodes s)
|
|
| 211 | - |
|
| 212 | - numbered_summaries = zip summaries [1..]
|
|
| 213 | - |
|
| 214 | - lookup_node :: ExternalKey -> Maybe ExternalNode
|
|
| 215 | - lookup_node key = M.lookup key node_map
|
|
| 216 | - |
|
| 217 | - lookup_key :: ExternalKey -> Maybe Int
|
|
| 218 | - lookup_key = fmap node_key . lookup_node
|
|
| 219 | - |
|
| 220 | - node_map :: M.Map ExternalKey ExternalNode
|
|
| 221 | - node_map =
|
|
| 222 | - M.fromList [ (emgNodeKey s, node)
|
|
| 223 | - | node <- nodes
|
|
| 224 | - , let s = node_payload node
|
|
| 225 | - ]
|
|
| 226 | - |
|
| 227 | - out_edge_keys :: [ExternalKey] -> [Int]
|
|
| 228 | - out_edge_keys = mapMaybe lookup_key
|
|
| 229 | - -- If we want keep_hi_boot_nodes, then we do lookup_key with
|
|
| 230 | - -- IsBoot; else False
|
|
| 231 | - |
|
| 232 | -instance Outputable ExternalGraphNode where
|
|
| 233 | - ppr = \case
|
|
| 234 | - NodeHomePackage mk ds -> text "NodeHomePackage" <+> ppr mk <+> ppr ds
|
|
| 235 | - NodeExternalPackage mk ds -> text "NodeExternalPackage" <+> ppr mk <+> ppr ds
|
|
| 236 | - |
|
| 237 | -instance Outputable ExternalKey where
|
|
| 238 | - ppr = \case
|
|
| 239 | - ExternalModuleKey mk -> text "ExternalModuleKey" <+> ppr mk
|
|
| 240 | - ExternalPackageKey uid -> text "ExternalPackageKey" <+> ppr uid
|
|
| 241 | - |
|
| 242 | -instance Outputable ExternalModuleGraph where
|
|
| 243 | - ppr ExternalModuleGraph{external_nodes, external_fully_loaded}
|
|
| 244 | - = text "ExternalModuleGraph" <+> ppr external_nodes <+> ppr external_fully_loaded |
| ... | ... | @@ -41,6 +41,8 @@ module GHC.Unit.Module.Graph |
| 41 | 41 | |
| 42 | 42 | , ModuleNodeInfo(..)
|
| 43 | 43 | , moduleNodeInfoModule
|
| 44 | + , moduleNodeInfoUnitId
|
|
| 45 | + , moduleNodeInfoMnwib
|
|
| 44 | 46 | , moduleNodeInfoModuleName
|
| 45 | 47 | , moduleNodeInfoModNodeKeyWithUid
|
| 46 | 48 | , moduleNodeInfoHscSource
|
| ... | ... | @@ -48,7 +50,7 @@ module GHC.Unit.Module.Graph |
| 48 | 50 | , isBootModuleNodeInfo
|
| 49 | 51 | -- * Module graph operations
|
| 50 | 52 | , lengthMG
|
| 51 | - |
|
| 53 | + , isEmptyMG
|
|
| 52 | 54 | -- ** 'ModSummary' operations
|
| 53 | 55 | --
|
| 54 | 56 | -- | A couple of operations on the module graph allow access to the
|
| ... | ... | @@ -100,6 +102,10 @@ module GHC.Unit.Module.Graph |
| 100 | 102 | , ModNodeKey
|
| 101 | 103 | , ModNodeKeyWithUid(..)
|
| 102 | 104 | , mnkToModule
|
| 105 | + , moduleToMnk
|
|
| 106 | + , mnkToInstalledModule
|
|
| 107 | + , installedModuleToMnk
|
|
| 108 | + , mnkIsBoot
|
|
| 103 | 109 | , msKey
|
| 104 | 110 | , mnKey
|
| 105 | 111 | , miKey
|
| ... | ... | @@ -310,7 +316,7 @@ checkFixedModuleInvariant node_types node = case node of |
| 310 | 316 | _ -> Nothing
|
| 311 | 317 | |
| 312 | 318 | |
| 313 | -{- Note [Modules Types in the ModuleGraph]
|
|
| 319 | +{- Note [Module Types in the ModuleGraph]
|
|
| 314 | 320 | ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
| 315 | 321 | |
| 316 | 322 | Modules can be one of two different types in the module graph.
|
| ... | ... | @@ -365,6 +371,14 @@ isBootModuleNodeInfo (ModuleNodeCompile ms) = isBootSummary ms |
| 365 | 371 | moduleNodeInfoModuleName :: ModuleNodeInfo -> ModuleName
|
| 366 | 372 | moduleNodeInfoModuleName m = moduleName (moduleNodeInfoModule m)
|
| 367 | 373 | |
| 374 | +moduleNodeInfoUnitId :: ModuleNodeInfo -> UnitId
|
|
| 375 | +moduleNodeInfoUnitId (ModuleNodeFixed key _) = mnkUnitId key
|
|
| 376 | +moduleNodeInfoUnitId (ModuleNodeCompile ms) = ms_unitid ms
|
|
| 377 | + |
|
| 378 | +moduleNodeInfoMnwib :: ModuleNodeInfo -> ModuleNameWithIsBoot
|
|
| 379 | +moduleNodeInfoMnwib (ModuleNodeFixed key _) = mnkModuleName key
|
|
| 380 | +moduleNodeInfoMnwib (ModuleNodeCompile ms) = ms_mnwib ms
|
|
| 381 | + |
|
| 368 | 382 | -- | Collect the immediate dependencies of a ModuleGraphNode,
|
| 369 | 383 | -- optionally avoiding hs-boot dependencies.
|
| 370 | 384 | -- If the drop_hs_boot_nodes flag is False, and if this is a .hs and there is
|
| ... | ... | @@ -425,6 +439,9 @@ instance Ord ModuleGraphNode where |
| 425 | 439 | lengthMG :: ModuleGraph -> Int
|
| 426 | 440 | lengthMG = length . mg_mss
|
| 427 | 441 | |
| 442 | +isEmptyMG :: ModuleGraph -> Bool
|
|
| 443 | +isEmptyMG = null . mg_mss
|
|
| 444 | + |
|
| 428 | 445 | --------------------------------------------------------------------------------
|
| 429 | 446 | -- ** ModSummaries
|
| 430 | 447 | --------------------------------------------------------------------------------
|
| 1 | -module GHC.Unit.Module.ModNodeKey ( ModNodeKeyWithUid(..), mnkToModule, mnkIsBoot ) where
|
|
| 1 | +module GHC.Unit.Module.ModNodeKey
|
|
| 2 | + ( ModNodeKeyWithUid(..)
|
|
| 3 | + , mnkToModule
|
|
| 4 | + , moduleToMnk
|
|
| 5 | + , mnkIsBoot
|
|
| 6 | + , mnkToInstalledModule
|
|
| 7 | + , installedModuleToMnk
|
|
| 8 | + ) where
|
|
| 2 | 9 | |
| 3 | 10 | import GHC.Prelude
|
| 4 | 11 | import GHC.Utils.Outputable
|
| ... | ... | @@ -7,12 +14,22 @@ import GHC.Unit.Types |
| 7 | 14 | data ModNodeKeyWithUid = ModNodeKeyWithUid { mnkModuleName :: !ModuleNameWithIsBoot
|
| 8 | 15 | , mnkUnitId :: !UnitId } deriving (Eq, Ord)
|
| 9 | 16 | |
| 10 | -mnkIsBoot :: ModNodeKeyWithUid -> IsBootInterface
|
|
| 11 | -mnkIsBoot (ModNodeKeyWithUid mnwib _) = gwib_isBoot mnwib
|
|
| 12 | - |
|
| 13 | 17 | mnkToModule :: ModNodeKeyWithUid -> Module
|
| 14 | 18 | mnkToModule (ModNodeKeyWithUid mnwib uid) = Module (RealUnit (Definite uid)) (gwib_mod mnwib)
|
| 15 | 19 | |
| 20 | +mnkToInstalledModule :: ModNodeKeyWithUid -> InstalledModule
|
|
| 21 | +mnkToInstalledModule (ModNodeKeyWithUid mnwib uid) = Module uid (gwib_mod mnwib)
|
|
| 22 | + |
|
| 23 | +-- | Already InstalledModules are always NotBoot
|
|
| 24 | +installedModuleToMnk :: InstalledModule -> ModNodeKeyWithUid
|
|
| 25 | +installedModuleToMnk mod = ModNodeKeyWithUid (GWIB (moduleName mod) NotBoot) (moduleUnit mod)
|
|
| 26 | + |
|
| 27 | +moduleToMnk :: Module -> IsBootInterface -> ModNodeKeyWithUid
|
|
| 28 | +moduleToMnk mod is_boot = ModNodeKeyWithUid (GWIB (moduleName mod) is_boot) (moduleUnitId mod)
|
|
| 29 | + |
|
| 30 | +mnkIsBoot :: ModNodeKeyWithUid -> IsBootInterface
|
|
| 31 | +mnkIsBoot (ModNodeKeyWithUid mnwib _) = gwib_isBoot mnwib
|
|
| 32 | + |
|
| 16 | 33 | instance Outputable ModNodeKeyWithUid where
|
| 17 | 34 | ppr (ModNodeKeyWithUid mnwib uid) = ppr uid <> colon <> ppr mnwib
|
| 18 | 35 |
| ... | ... | @@ -526,6 +526,7 @@ Library |
| 526 | 526 | GHC.Driver.MakeSem
|
| 527 | 527 | GHC.Driver.Main
|
| 528 | 528 | GHC.Driver.Make
|
| 529 | + GHC.Driver.Messager
|
|
| 529 | 530 | GHC.Driver.MakeAction
|
| 530 | 531 | GHC.Driver.MakeFile
|
| 531 | 532 | GHC.Driver.Monad
|
| ... | ... | @@ -956,7 +957,6 @@ Library |
| 956 | 957 | GHC.Unit.Module.Env
|
| 957 | 958 | GHC.Unit.Module.Graph
|
| 958 | 959 | GHC.Unit.Module.ModNodeKey
|
| 959 | - GHC.Unit.Module.External.Graph
|
|
| 960 | 960 | GHC.Unit.Module.Imported
|
| 961 | 961 | GHC.Unit.Module.Location
|
| 962 | 962 | GHC.Unit.Module.ModDetails
|
| 1 | +{-# LANGUAGE RecordWildCards #-}
|
|
| 2 | +module Main where
|
|
| 3 | + |
|
| 4 | +import GHC
|
|
| 5 | +import GHC.Driver.Session
|
|
| 6 | +import GHC.Driver.Monad
|
|
| 7 | +import GHC.Driver.Env
|
|
| 8 | +import GHC.Driver.Make (summariseFile)
|
|
| 9 | +import GHC.Driver.Downsweep
|
|
| 10 | +import GHC.Unit.Module.Graph
|
|
| 11 | +import GHC.Unit.Module.ModSummary
|
|
| 12 | +import GHC.Unit.Types
|
|
| 13 | +import GHC.Unit.Module
|
|
| 14 | +import GHC.Unit.Module.ModNodeKey
|
|
| 15 | +import GHC.Types.SourceFile
|
|
| 16 | +import System.Environment
|
|
| 17 | +import Control.Monad (void, when)
|
|
| 18 | +import Data.Maybe (fromJust)
|
|
| 19 | +import Control.Exception (ExceptionWithContext(..), SomeException)
|
|
| 20 | +import Control.Monad.Catch (handle, throwM)
|
|
| 21 | +import Control.Exception.Context
|
|
| 22 | +import GHC.Utils.Outputable
|
|
| 23 | +import Data.List
|
|
| 24 | +import GHC.Unit.Env
|
|
| 25 | +import GHC.Unit.State
|
|
| 26 | +import GHC.Tc.Utils.Monad
|
|
| 27 | +import GHC.Iface.Env
|
|
| 28 | +import GHC.Driver.Ppr
|
|
| 29 | +import GHC.Unit.Home
|
|
| 30 | + |
|
| 31 | + |
|
| 32 | +main :: IO ()
|
|
| 33 | +main = do
|
|
| 34 | + [libdir] <- getArgs
|
|
| 35 | + runGhc (Just libdir) $ handle (\(ExceptionWithContext c e :: ExceptionWithContext SomeException) ->
|
|
| 36 | + liftIO $ putStrLn (displayExceptionContext c) >> print e >> throwM e) $ do
|
|
| 37 | + |
|
| 38 | + -- Set up session
|
|
| 39 | + dflags <- getSessionDynFlags
|
|
| 40 | + setSessionDynFlags (dflags { verbosity = 1 })
|
|
| 41 | + hsc_env <- getSession
|
|
| 42 | + setSession $ hscSetActiveUnitId mainUnitId hsc_env
|
|
| 43 | + |
|
| 44 | + -- Get ModSummaries for our test modules
|
|
| 45 | + msA <- getModSummaryFromTarget "T1A.hs"
|
|
| 46 | + msB <- getModSummaryFromTarget "T1B.hs"
|
|
| 47 | + msC <- getModSummaryFromTarget "T1C.hs"
|
|
| 48 | + |
|
| 49 | + let targets = [ Target (TargetModule (ms_mod_name msA)) True (moduleUnitId $ ms_mod msA) Nothing
|
|
| 50 | + , Target (TargetModule (ms_mod_name msB)) True (moduleUnitId $ ms_mod msB) Nothing
|
|
| 51 | + , Target (TargetModule (ms_mod_name msC)) True (moduleUnitId $ ms_mod msC) Nothing
|
|
| 52 | + ]
|
|
| 53 | + |
|
| 54 | + setTargets targets
|
|
| 55 | + |
|
| 56 | + -- Compile interfaces for our modules
|
|
| 57 | + load LoadAllTargets
|
|
| 58 | + |
|
| 59 | + hsc_env <- getSession
|
|
| 60 | + setSession $ hsc_env { hsc_dflags = (hsc_dflags hsc_env) { ghcMode = OneShot } }
|
|
| 61 | + hsc_env <- getSession
|
|
| 62 | + |
|
| 63 | + |
|
| 64 | + -- Create ModNodeKeys with unit IDs
|
|
| 65 | + let keyA = msKey msA
|
|
| 66 | + keyB = msKey msB
|
|
| 67 | + keyC = msKey msC
|
|
| 68 | + |
|
| 69 | + let mkGraph s = do
|
|
| 70 | + ([], nodes) <- downsweepFromRootNodes hsc_env mempty [] True DownsweepUseFixed s []
|
|
| 71 | + return $ mkModuleGraph nodes
|
|
| 72 | + |
|
| 73 | + graph <- liftIO $ mkGraph [ModuleNodeCompile msC]
|
|
| 74 | + |
|
| 75 | + liftIO $ putStrLn "loaded"
|
|
| 76 | + -- 1. Check that the module graph is valid
|
|
| 77 | + let invariantErrors = checkModuleGraph graph
|
|
| 78 | + |
|
| 79 | + case invariantErrors of
|
|
| 80 | + [] -> liftIO $ putStrLn "PASS Test passed"
|
|
| 81 | + errors -> do
|
|
| 82 | + liftIO $ putStrLn "FAIL Test failed - invariant violations"
|
|
| 83 | + liftIO $ putStrLn $ showSDoc dflags $ vcat (map ppr errors)
|
|
| 84 | + |
|
| 85 | + -- 2. Check that from the root, we can reach the "ghc-internal" package.
|
|
| 86 | + let ghcInternalPackage = NodeKey_ExternalUnit ghcInternalUnitId
|
|
| 87 | + let root = NodeKey_Module keyC
|
|
| 88 | + let reached = mgQuery graph root ghcInternalPackage
|
|
| 89 | + if not reached
|
|
| 90 | + then liftIO $ putStrLn "FAIL Test failed - cannot reach ghc-internal"
|
|
| 91 | + else liftIO $ putStrLn "PASS Test passed"
|
|
| 92 | + |
|
| 93 | + |
|
| 94 | + |
|
| 95 | + where
|
|
| 96 | + |
|
| 97 | + -- Helper to get ModSummary from a target file
|
|
| 98 | + getModSummaryFromTarget :: FilePath -> Ghc ModSummary
|
|
| 99 | + getModSummaryFromTarget file = do
|
|
| 100 | + hsc_env <- getSession
|
|
| 101 | + Right ms <- liftIO $ summariseFile hsc_env (DefiniteHomeUnit mainUnitId Nothing) mempty file Nothing Nothing
|
|
| 102 | + return ms |
| 1 | +[1 of 3] Compiling T1A ( T1A.hs, T1A.o )
|
|
| 2 | +[2 of 3] Compiling T1B ( T1B.hs, T1B.o )
|
|
| 3 | +[3 of 3] Compiling T1C ( T1C.hs, T1C.o )
|
|
| 4 | +loaded
|
|
| 5 | +PASS Test passed
|
|
| 6 | +PASS Test passed |
| ... | ... | @@ -13,3 +13,11 @@ test('ModuleGraphInvariants', |
| 13 | 13 | ],
|
| 14 | 14 | compile_and_run,
|
| 15 | 15 | ['-package ghc'])
|
| 16 | + |
|
| 17 | +test('InterfaceModuleGraph',
|
|
| 18 | + [extra_run_opts(f'"{config.libdir}"'),
|
|
| 19 | + extra_files(['T1A.hs', 'T1B.hs', 'T1C.hs']),
|
|
| 20 | + wasm_broken(25953)
|
|
| 21 | + ],
|
|
| 22 | + compile_and_run,
|
|
| 23 | + ['-package ghc']) |
| ... | ... | @@ -46,13 +46,8 @@ lookupModule :: ModuleName -- ^ Name of the module |
| 46 | 46 | -> TcPluginM Module
|
| 47 | 47 | lookupModule mod_nm = do
|
| 48 | 48 | hsc_env <- getTopEnv
|
| 49 | - let dflags = hsc_dflags hsc_env
|
|
| 50 | - let fopts = initFinderOpts dflags
|
|
| 51 | - let fc = hsc_FC hsc_env
|
|
| 52 | - let units = hsc_units hsc_env
|
|
| 53 | 49 | let home_unit = hsc_home_unit hsc_env
|
| 54 | - -- found_module <- findPluginModule fc fopts units home_unit mod_name
|
|
| 55 | - found_module <- tcPluginIO $ findPluginModule fc fopts units (Just home_unit) mod_nm
|
|
| 50 | + found_module <- tcPluginIO $ findPluginModule hsc_env mod_nm
|
|
| 56 | 51 | case found_module of
|
| 57 | 52 | FoundModule h -> return (fr_mod h)
|
| 58 | 53 | _ -> do
|