Skip to content

Commit 948c7dd

Browse files
committed
Replace checkForImportCycles option with fullModuleGraph option that restores the old behaviour
1 parent bca6e24 commit 948c7dd

File tree

2 files changed

+24
-16
lines changed

2 files changed

+24
-16
lines changed

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 23 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -14,10 +14,6 @@ module Development.IDE.Core.Rules(
1414
IdeState, GetParsedModule(..), TransitiveDependencies(..),
1515
Priority(..), GhcSessionIO(..), GetClientSettings(..),
1616
-- * Functions
17-
--
18-
--
19-
--
20-
--
2117
priorityTypeCheck,
2218
priorityGenerateCore,
2319
priorityFilesOfInterest,
@@ -665,7 +661,11 @@ knownFilesRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake recorde
665661
getModuleGraphRule :: Recorder (WithPriority Log) -> Rules ()
666662
getModuleGraphRule recorder = defineNoFile (cmapWithPrio LogShake recorder) $ \GetModuleGraph -> do
667663
fs <- toKnownFiles <$> useNoFile_ GetKnownTargets
668-
(rawDepInfo, bm) <- rawDependencyInformation (HashSet.toList fs)
664+
dependencyInfoForFiles (HashSet.toList fs)
665+
666+
dependencyInfoForFiles :: [NormalizedFilePath] -> Action DependencyInformation
667+
dependencyInfoForFiles fs = do
668+
(rawDepInfo, bm) <- rawDependencyInformation fs
669669
let (all_fs, _all_ids) = unzip $ HM.toList $ pathToIdMap $ rawPathIdMap rawDepInfo
670670
mss <- map (fmap msrModSummary) <$> uses GetModSummaryWithoutTimestamps all_fs
671671
#if MIN_VERSION_ghc(9,3,0)
@@ -758,11 +758,11 @@ loadGhcSession recorder ghcSessionDepsConfig = do
758758
ghcSessionDepsDefinition fullModSummary ghcSessionDepsConfig env file
759759

760760
newtype GhcSessionDepsConfig = GhcSessionDepsConfig
761-
{ checkForImportCycles :: Bool
761+
{ fullModuleGraph :: Bool
762762
}
763763
instance Default GhcSessionDepsConfig where
764764
def = GhcSessionDepsConfig
765-
{ checkForImportCycles = True
765+
{ fullModuleGraph = True
766766
}
767767

768768
-- | Note [GhcSessionDeps]
@@ -781,15 +781,18 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
781781
case mbdeps of
782782
Nothing -> return Nothing
783783
Just deps -> do
784-
when checkForImportCycles $ void $ uses_ ReportImportCycles deps
784+
when fullModuleGraph $ void $ uses_ ReportImportCycles deps
785785
ms <- msrModSummary <$> if fullModSummary
786786
then use_ GetModSummary file
787787
else use_ GetModSummaryWithoutTimestamps file
788788

789789
depSessions <- map hscEnv <$> uses_ (GhcSessionDeps_ fullModSummary) deps
790790
ifaces <- uses_ GetModIface deps
791791
let inLoadOrder = map (\HiFileResult{..} -> HomeModInfo hirModIface hirModDetails Nothing) ifaces
792-
mg <- depModuleGraph <$> useNoFile_ GetModuleGraph
792+
mg <- depModuleGraph <$>
793+
if fullModuleGraph
794+
then useNoFile_ GetModuleGraph
795+
else dependencyInfoForFiles [file]
793796
session' <- liftIO $ mergeEnvs hsc mg ms inLoadOrder depSessions
794797

795798
Just <$> liftIO (newHscEnvEqWithImportPaths (envImportPaths env) session' [])
@@ -1189,8 +1192,16 @@ newtype CompiledLinkables = CompiledLinkables { getCompiledLinkables :: Var (Mod
11891192
instance IsIdeGlobal CompiledLinkables
11901193

11911194
data RulesConfig = RulesConfig
1192-
{ -- | Disable import cycle checking for improved performance in large codebases
1193-
checkForImportCycles :: Bool
1195+
{ -- | Share the computation for the entire module graph
1196+
-- We usually compute the full module graph for the project
1197+
-- and share it for all files.
1198+
-- However, in large projects it might not be desirable to wait
1199+
-- for computing the entire module graph before starting to
1200+
-- typecheck a particular file.
1201+
-- Disabling this drastically decreases sharing and is likely to
1202+
-- increase memory usage if you have multiple files open
1203+
-- Disabling this also disables checking for import cycles
1204+
fullModuleGraph :: Bool
11941205
-- | Disable TH for improved performance in large codebases
11951206
, enableTemplateHaskell :: Bool
11961207
-- | Warning to show when TH is not supported by the current HLS binary
@@ -1227,7 +1238,7 @@ mainRule recorder RulesConfig{..} = do
12271238
reportImportCyclesRule recorder
12281239
typeCheckRule recorder
12291240
getDocMapRule recorder
1230-
loadGhcSession recorder def{checkForImportCycles}
1241+
loadGhcSession recorder def{fullModuleGraph}
12311242
getModIfaceFromDiskRule recorder
12321243
getModIfaceFromDiskAndIndexRule recorder
12331244
getModIfaceRule recorder

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -67,8 +67,7 @@ import Development.IDE (GetModuleGraph (.
6767
useNoFile_,
6868
useWithStale_,
6969
use_, uses_)
70-
import Development.IDE.Core.Rules (GhcSessionDepsConfig (..),
71-
ghcSessionDepsDefinition)
70+
import Development.IDE.Core.Rules (ghcSessionDepsDefinition)
7271
import Development.IDE.GHC.Compat hiding (typeKind,
7372
unitState)
7473
import qualified Development.IDE.GHC.Compat as Compat
@@ -571,8 +570,6 @@ runGetSession st nfp = liftIO $ runAction "eval" st $ do
571570
((_, res),_) <- liftIO $ loadSessionFun fp
572571
let env = fromMaybe (error $ "Unknown file: " <> fp) res
573572
ghcSessionDepsConfig = def
574-
{ checkForImportCycles = False
575-
}
576573
res <- fmap hscEnvWithImportPaths <$> ghcSessionDepsDefinition True ghcSessionDepsConfig env nfp
577574
return $ fromMaybe (error $ "Unable to load file: " <> fp) res
578575

0 commit comments

Comments
 (0)