Skip to content

Commit

Permalink
Remove GetDependencyInformation in favour of GetModuleGraph.
Browse files Browse the repository at this point in the history
Computing and storing GetDependencyInformation for each file essentially individually means
that we perform downsweep on each file individually, wasting a lot of work and using an excessive
amount of memory to store all these duplicated graphs individually.

However, we already have the `GetModuleGraph` rule, which we need to compute before compiling
files any way due to being depended on by `NeedsCompilation`, which needs to know if any reverse
dependencies of the module we are compiling requires TH, which meant that each file already depends on
the results of downsweep for the whole project.

Instead, we can compute the whole graph once when we execute the `GetModuleGraph` rule and even use this inside `HscEnv.hsc_mod_graph` to avoid reconstructing the `ModuleGraph` on each invocation of `GhcSessionDeps`.

There may be concerns about excessive build churn due to any change to the result of `GetModuleGraph`
invalidating the result of `GhcSessionDeps` too often, but note that this only happens when something
in the header of a module changes, and this could be solved easily be re-introducing
a version of `GetDependencyInformation` with early cutoff that essentially returns the result of `GetModuleGraph`
but includes the hash of only the `ModSummary`s in the downward dependency closure of the file.
  • Loading branch information
wz1000 committed Jul 12, 2023
1 parent 27f46d7 commit 0220797
Show file tree
Hide file tree
Showing 6 changed files with 145 additions and 106 deletions.
63 changes: 26 additions & 37 deletions ghcide/src/Development/IDE/Core/Compile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,7 @@ import GHC (Anchor (anchor),
import qualified GHC as G
import GHC.Hs (LEpaComment)
import qualified GHC.Types.Error as Error
import Development.IDE.Import.DependencyInformation
#endif

#if MIN_VERSION_ghc(9,5,0)
Expand Down Expand Up @@ -1045,25 +1046,19 @@ handleGenerationErrors' dflags source action =
-- Add the current ModSummary to the graph, along with the
-- HomeModInfo's of all direct dependencies (by induction hypothesis all
-- transitive dependencies will be contained in envs)
mergeEnvs :: HscEnv -> ModuleGraph -> ModSummary -> [HomeModInfo] -> [HscEnv] -> IO HscEnv
mergeEnvs env mg ms extraMods envs = do
#if MIN_VERSION_ghc(9,3,0)
mergeEnvs :: HscEnv -> (ModSummary, [NodeKey]) -> [HomeModInfo] -> [HscEnv] -> IO HscEnv
mergeEnvs env (ms, deps) extraMods envs = do
let im = Compat.installedModule (toUnitId $ moduleUnit $ ms_mod ms) (moduleName (ms_mod ms))
ifr = InstalledFound (ms_location ms) im
curFinderCache = Compat.extendInstalledModuleEnv Compat.emptyInstalledModuleEnv im ifr
-- Very important to force this as otherwise the hsc_mod_graph field is not
-- forced and ends up retaining a reference to all the old hsc_envs we have merged to get
-- this new one, which in turn leads to the EPS referencing the HPT.
module_graph_nodes =
nubOrdOn mkNodeKey (ModuleNode deps ms : concatMap (mgModSummaries' . hsc_mod_graph) envs)

newFinderCache <- concatFC curFinderCache (map hsc_FC envs)
liftRnf rwhnf module_graph_nodes `seq` (return $ loadModulesHome extraMods $
return $! loadModulesHome extraMods $
let newHug = foldl' mergeHUG (hsc_HUG env) (map hsc_HUG envs) in
(hscUpdateHUG (const newHug) env){
hsc_FC = newFinderCache,
hsc_mod_graph = mkModuleGraph module_graph_nodes
})
hsc_mod_graph = mg
}

where
mergeHUG (UnitEnvGraph a) (UnitEnvGraph b) = UnitEnvGraph $ Map.unionWith mergeHUE a b
Expand All @@ -1082,30 +1077,16 @@ mergeEnvs env (ms, deps) extraMods envs = do
pure $ FinderCache fcModules' fcFiles'

#else
mergeEnvs :: HscEnv -> ModSummary -> [HomeModInfo] -> [HscEnv] -> IO HscEnv
mergeEnvs env ms extraMods envs = do
prevFinderCache <- concatFC <$> mapM (readIORef . hsc_FC) envs
let im = Compat.installedModule (toUnitId $ moduleUnit $ ms_mod ms) (moduleName (ms_mod ms))
ifr = InstalledFound (ms_location ms) im
-- Very important to force this as otherwise the hsc_mod_graph field is not
-- forced and ends up retaining a reference to all the old hsc_envs we have merged to get
-- this new one, which in turn leads to the EPS referencing the HPT.
module_graph_nodes =
#if MIN_VERSION_ghc(9,2,0)
-- We don't do any instantiation for backpack at this point of time, so it is OK to use
-- 'extendModSummaryNoDeps'.
-- This may have to change in the future.
map extendModSummaryNoDeps $
#endif
nubOrdOn ms_mod (ms : concatMap (mgModSummaries . hsc_mod_graph) envs)

newFinderCache <- newIORef $! Compat.extendInstalledModuleEnv prevFinderCache im ifr
liftRnf rwhnf module_graph_nodes `seq` (return $ loadModulesHome extraMods $
return $! loadModulesHome extraMods $
env{
hsc_HPT = foldMapBy mergeUDFM emptyUDFM hsc_HPT envs,
hsc_FC = newFinderCache,
hsc_mod_graph = mkModuleGraph module_graph_nodes
})
hsc_mod_graph = mg
}

where
mergeUDFM = plusUDFM_C combineModules
Expand Down Expand Up @@ -1504,8 +1485,8 @@ loadInterface session ms linkableNeeded RecompilationInfo{..} = do
let runtime_deps
| not (mi_used_th iface) = emptyModuleEnv
| otherwise = parseRuntimeDeps (md_anns details)
-- Perform the fine grained recompilation check for TH
maybe_recomp <- checkLinkableDependencies get_linkable_hashes (hsc_mod_graph sessionWithMsDynFlags) runtime_deps
-- Peform the fine grained recompilation check for TH
maybe_recomp <- checkLinkableDependencies session get_linkable_hashes runtime_deps
case maybe_recomp of
Just msg -> do_regenerate msg
Nothing
Expand Down Expand Up @@ -1542,13 +1523,21 @@ parseRuntimeDeps anns = mkModuleEnv $ mapMaybe go anns
-- the runtime dependencies of the module, to check if any of them are out of date
-- Hopefully 'runtime_deps' will be empty if the module didn't actually use TH
-- See Note [Recompilation avoidance in the presence of TH]
checkLinkableDependencies :: MonadIO m => ([NormalizedFilePath] -> m [BS.ByteString]) -> ModuleGraph -> ModuleEnv BS.ByteString -> m (Maybe RecompileRequired)
checkLinkableDependencies get_linkable_hashes graph runtime_deps = do
let hs_files = mapM go (moduleEnvToList runtime_deps)
go (mod, hash) = do
ms <- mgLookupModule graph mod
let hs = fromJust $ ml_hs_file $ ms_location ms
pure (toNormalizedFilePath' hs, hash)
checkLinkableDependencies :: MonadIO m => HscEnv -> ([NormalizedFilePath] -> m [BS.ByteString]) -> ModuleEnv BS.ByteString -> m (Maybe RecompileRequired)
checkLinkableDependencies hsc_env get_linkable_hashes runtime_deps = do
#if MIN_VERSION_ghc(9,3,0)
moduleLocs <- liftIO $ readIORef (fcModuleCache $ hsc_FC hsc_env)
#else
moduleLocs <- liftIO $ readIORef (hsc_FC hsc_env)
#endif
let go (mod, hash) = do
ifr <- lookupInstalledModuleEnv moduleLocs $ Compat.installedModule (toUnitId $ moduleUnit mod) (moduleName mod)
case ifr of
InstalledFound loc _ -> do
hs <- ml_hs_file loc
pure (toNormalizedFilePath' hs,hash)
_ -> Nothing
hs_files = mapM go (moduleEnvToList runtime_deps)
case hs_files of
Nothing -> error "invalid module graph"
Just fs -> do
Expand Down
14 changes: 2 additions & 12 deletions ghcide/src/Development/IDE/Core/RuleTypes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,11 +69,6 @@ type instance RuleResult GetParsedModule = ParsedModule
-- all comments included using Opt_KeepRawTokenStream
type instance RuleResult GetParsedModuleWithComments = ParsedModule

-- | The dependency information produced by following the imports recursively.
-- This rule will succeed even if there is an error, e.g., a module could not be located,
-- a module could not be parsed or an import cycle.
type instance RuleResult GetDependencyInformation = DependencyInformation

type instance RuleResult GetModuleGraph = DependencyInformation

data GetKnownTargets = GetKnownTargets
Expand Down Expand Up @@ -262,8 +257,8 @@ type instance RuleResult GhcSessionDeps = HscEnvEq
-- | Resolve the imports in a module to the file path of a module in the same package
type instance RuleResult GetLocatedImports = [(Located ModuleName, Maybe ArtifactsLocation)]

-- | This rule is used to report import cycles. It depends on GetDependencyInformation.
-- We cannot report the cycles directly from GetDependencyInformation since
-- | This rule is used to report import cycles. It depends on GetModuleGraph.
-- We cannot report the cycles directly from GetModuleGraph since
-- we can only report diagnostics for the current file.
type instance RuleResult ReportImportCycles = ()

Expand Down Expand Up @@ -401,11 +396,6 @@ data NeedsCompilation = NeedsCompilation
instance Hashable NeedsCompilation
instance NFData NeedsCompilation

data GetDependencyInformation = GetDependencyInformation
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetDependencyInformation
instance NFData GetDependencyInformation

data GetModuleGraph = GetModuleGraph
deriving (Eq, Show, Typeable, Generic)
instance Hashable GetModuleGraph
Expand Down
Loading

0 comments on commit 0220797

Please sign in to comment.