Skip to content

Commit 8de10e9

Browse files
authored
Cache a ghc session per file of interest (#630)
* Cache a GHC session per module We set up a GHC session (load deps, setup finder cache) every time we want to: - typecheck a module - get the span infos This is very expensive, and can be cached. * cache the Ghc session for files of interest only * hlint * fix 8.4 build * Early cut-off for ModSummary rule This allows to bypass work when a module imports & pragmas haven't changed, e.g. GetDependencies, GetDependencyInformation, GetLocatedImports, etc. * remove extraneous reverse Not sure where that came from * review feedback
1 parent 0d806c3 commit 8de10e9

File tree

5 files changed

+111
-50
lines changed

5 files changed

+111
-50
lines changed

src/Development/IDE/Core/Compile.hs

Lines changed: 4 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ module Development.IDE.Core.Compile
2424
, loadInterface
2525
, loadDepModule
2626
, loadModuleHome
27+
, setupFinderCache
2728
) where
2829

2930
import Development.IDE.Core.RuleTypes
@@ -116,24 +117,16 @@ computePackageDeps env pkg = do
116117

117118
typecheckModule :: IdeDefer
118119
-> HscEnv
119-
-> [(ModSummary, (ModIface, Maybe Linkable))]
120120
-> ParsedModule
121121
-> IO (IdeResult (HscEnv, TcModuleResult))
122-
typecheckModule (IdeDefer defer) hsc depsIn pm = do
122+
typecheckModule (IdeDefer defer) hsc pm = do
123123
fmap (either (, Nothing) (second Just . sequence) . sequence) $
124124
runGhcEnv hsc $
125125
catchSrcErrors "typecheck" $ do
126-
-- Currently GetDependencies returns things in topological order so A comes before B if A imports B.
127-
-- We need to reverse this as GHC gets very unhappy otherwise and complains about broken interfaces.
128-
-- Long-term we might just want to change the order returned by GetDependencies
129-
let deps = reverse depsIn
130-
131-
setupFinderCache (map fst deps)
132126

133127
let modSummary = pm_mod_summary pm
134128
dflags = ms_hspp_opts modSummary
135129

136-
mapM_ (uncurry loadDepModule . snd) deps
137130
modSummary' <- initPlugins modSummary
138131
(warnings, tcm) <- withWarnings "typecheck" $ \tweak ->
139132
GHC.typecheckModule $ enableTopLevelWarnings
@@ -481,7 +474,8 @@ getModSummaryFromImports fp contents = do
481474
-- To avoid silent issues where something is not processed because the date
482475
-- has not changed, we make sure that things blow up if they depend on the date.
483476
, ms_hsc_src = sourceType
484-
, ms_hspp_buf = Nothing
477+
-- The contents are used by the GetModSummary rule
478+
, ms_hspp_buf = Just contents
485479
, ms_hspp_file = fp
486480
, ms_hspp_opts = dflags
487481
, ms_iface_date = Nothing

src/Development/IDE/Core/RuleTypes.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -88,6 +88,9 @@ type instance RuleResult GenerateByteCode = Linkable
8888
-- | A GHC session that we reuse.
8989
type instance RuleResult GhcSession = HscEnvEq
9090

91+
-- | A GHC session preloaded with all the dependencies
92+
type instance RuleResult GhcSessionDeps = HscEnvEq
93+
9194
-- | Resolve the imports in a module to the file path of a module
9295
-- in the same package or the package id of another package.
9396
type instance RuleResult GetLocatedImports = ([(Located ModuleName, Maybe ArtifactsLocation)], S.Set InstalledUnitId)
@@ -170,6 +173,11 @@ instance Hashable GhcSession
170173
instance NFData GhcSession
171174
instance Binary GhcSession
172175

176+
data GhcSessionDeps = GhcSessionDeps deriving (Eq, Show, Typeable, Generic)
177+
instance Hashable GhcSessionDeps
178+
instance NFData GhcSessionDeps
179+
instance Binary GhcSessionDeps
180+
173181
data GetModIfaceFromDisk = GetModIfaceFromDisk
174182
deriving (Eq, Show, Typeable, Generic)
175183
instance Hashable GetModIfaceFromDisk

src/Development/IDE/Core/Rules.hs

Lines changed: 80 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -78,6 +78,8 @@ import Control.Concurrent.Async (concurrently)
7878
import Control.Monad.State
7979
import System.IO.Error (isDoesNotExistError)
8080
import Control.Exception.Safe (IOException, catch)
81+
import FastString (FastString(uniq))
82+
import qualified HeaderInfo as Hdr
8183

8284
-- | This is useful for rules to convert rules that can only produce errors or
8385
-- a result into the more general IdeResult type that supports producing
@@ -443,30 +445,30 @@ getSpanInfoRule =
443445
define $ \GetSpanInfo file -> do
444446
tc <- use_ TypeCheck file
445447
packageState <- hscEnv <$> use_ GhcSession file
446-
deps <- maybe (TransitiveDependencies [] [] []) fst <$> useWithStale GetDependencies file
447-
let tdeps = transitiveModuleDeps deps
448448

449449
-- When possible, rely on the haddocks embedded in our interface files
450450
-- This creates problems on ghc-lib, see comment on 'getDocumentationTryGhc'
451451
#if MIN_GHC_API_VERSION(8,6,0) && !defined(GHC_LIB)
452452
let parsedDeps = []
453453
#else
454+
deps <- maybe (TransitiveDependencies [] [] []) fst <$> useWithStale GetDependencies file
455+
let tdeps = transitiveModuleDeps deps
454456
parsedDeps <- mapMaybe (fmap fst) <$> usesWithStale GetParsedModule tdeps
455457
#endif
456458

457-
ifaces <- mapMaybe (fmap fst) <$> usesWithStale GetModIface tdeps
458459
(fileImports, _) <- use_ GetLocatedImports file
459460
let imports = second (fmap artifactFilePath) <$> fileImports
460-
x <- liftIO $ getSrcSpanInfos packageState imports tc parsedDeps (map hirModIface ifaces)
461+
x <- liftIO $ getSrcSpanInfos packageState imports tc parsedDeps
461462
return ([], Just x)
462463

463464
-- Typechecks a module.
464465
typeCheckRule :: Rules ()
465466
typeCheckRule = define $ \TypeCheck file -> do
466467
pm <- use_ GetParsedModule file
468+
hsc <- hscEnv <$> use_ GhcSessionDeps file
467469
-- do not generate interface files as this rule is called
468470
-- for files of interest on every keystroke
469-
typeCheckRuleDefinition file pm SkipGenerationOfInterfaceFiles
471+
typeCheckRuleDefinition hsc pm SkipGenerationOfInterfaceFiles
470472

471473
data GenerateInterfaceFiles
472474
= DoGenerateInterfaceFiles
@@ -478,29 +480,16 @@ data GenerateInterfaceFiles
478480
-- garbage collect all the intermediate typechecked modules rather than
479481
-- retain the information forever in the shake graph.
480482
typeCheckRuleDefinition
481-
:: NormalizedFilePath -- ^ Path to source file
483+
:: HscEnv
482484
-> ParsedModule
483485
-> GenerateInterfaceFiles -- ^ Should generate .hi and .hie files ?
484486
-> Action (IdeResult TcModuleResult)
485-
typeCheckRuleDefinition file pm generateArtifacts = do
486-
deps <- use_ GetDependencies file
487-
hsc <- hscEnv <$> use_ GhcSession file
488-
-- Figure out whether we need TemplateHaskell or QuasiQuotes support
489-
let graph_needs_th_qq = needsTemplateHaskellOrQQ $ hsc_mod_graph hsc
490-
file_uses_th_qq = uses_th_qq $ ms_hspp_opts (pm_mod_summary pm)
491-
any_uses_th_qq = graph_needs_th_qq || file_uses_th_qq
492-
mirs <- uses_ GetModIface (transitiveModuleDeps deps)
493-
bytecodes <- if any_uses_th_qq
494-
then -- If we use TH or QQ, we must obtain the bytecode
495-
fmap Just <$> uses_ GenerateByteCode (transitiveModuleDeps deps)
496-
else
497-
pure $ repeat Nothing
498-
487+
typeCheckRuleDefinition hsc pm generateArtifacts = do
499488
setPriority priorityTypeCheck
500489
IdeOptions { optDefer = defer } <- getIdeOptions
501490

502491
addUsageDependencies $ liftIO $ do
503-
res <- typecheckModule defer hsc (zipWith unpack mirs bytecodes) pm
492+
res <- typecheckModule defer hsc pm
504493
case res of
505494
(diags, Just (hsc,tcm)) | DoGenerateInterfaceFiles <- generateArtifacts -> do
506495
diagsHie <- generateAndWriteHieFile hsc (tmrModule tcm)
@@ -509,10 +498,6 @@ typeCheckRuleDefinition file pm generateArtifacts = do
509498
(diags, res) ->
510499
return (diags, snd <$> res)
511500
where
512-
unpack HiFileResult{..} bc = (hirModSummary, (hirModIface, bc))
513-
uses_th_qq dflags =
514-
xopt LangExt.TemplateHaskell dflags || xopt LangExt.QuasiQuotes dflags
515-
516501
addUsageDependencies :: Action (a, Maybe TcModuleResult) -> Action (a, Maybe TcModuleResult)
517502
addUsageDependencies a = do
518503
r@(_, mtc) <- a
@@ -588,6 +573,43 @@ loadGhcSession = do
588573
Nothing -> BS.pack (show (hash (snd val)))
589574
return (Just cutoffHash, val)
590575

576+
define $ \GhcSessionDeps file -> ghcSessionDepsDefinition file
577+
578+
ghcSessionDepsDefinition :: NormalizedFilePath -> Action (IdeResult HscEnvEq)
579+
ghcSessionDepsDefinition file = do
580+
hsc <- hscEnv <$> use_ GhcSession file
581+
(ms,_) <- useWithStale_ GetModSummary file
582+
(deps,_) <- useWithStale_ GetDependencies file
583+
let tdeps = transitiveModuleDeps deps
584+
ifaces <- uses_ GetModIface tdeps
585+
586+
-- Figure out whether we need TemplateHaskell or QuasiQuotes support
587+
let graph_needs_th_qq = needsTemplateHaskellOrQQ $ hsc_mod_graph hsc
588+
file_uses_th_qq = uses_th_qq $ ms_hspp_opts ms
589+
any_uses_th_qq = graph_needs_th_qq || file_uses_th_qq
590+
591+
bytecodes <- if any_uses_th_qq
592+
then -- If we use TH or QQ, we must obtain the bytecode
593+
fmap Just <$> uses_ GenerateByteCode (transitiveModuleDeps deps)
594+
else
595+
pure $ repeat Nothing
596+
597+
-- Currently GetDependencies returns things in topological order so A comes before B if A imports B.
598+
-- We need to reverse this as GHC gets very unhappy otherwise and complains about broken interfaces.
599+
-- Long-term we might just want to change the order returned by GetDependencies
600+
let inLoadOrder = reverse (zipWith unpack ifaces bytecodes)
601+
602+
(session',_) <- liftIO $ runGhcEnv hsc $ do
603+
setupFinderCache (map hirModSummary ifaces)
604+
mapM_ (uncurry loadDepModule) inLoadOrder
605+
606+
res <- liftIO $ newHscEnvEq session' []
607+
return ([], Just res)
608+
where
609+
unpack HiFileResult{..} bc = (hirModIface, bc)
610+
uses_th_qq dflags =
611+
xopt LangExt.TemplateHaskell dflags || xopt LangExt.QuasiQuotes dflags
612+
591613
getModIfaceFromDiskRule :: Rules ()
592614
getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
593615
-- get all dependencies interface files, to check for freshness
@@ -623,12 +645,33 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
623645
pure (Nothing, ([], Nothing))
624646

625647
getModSummaryRule :: Rules ()
626-
getModSummaryRule = define $ \GetModSummary f -> do
648+
getModSummaryRule = defineEarlyCutoff $ \GetModSummary f -> do
627649
dflags <- hsc_dflags . hscEnv <$> use_ GhcSession f
628650
(_, mFileContent) <- getFileContents f
629651
modS <- liftIO $ evalWithDynFlags dflags $ runExceptT $
630652
getModSummaryFromImports (fromNormalizedFilePath f) (textToStringBuffer <$> mFileContent)
631-
return $ either (,Nothing) (([], ) . Just) modS
653+
case modS of
654+
Right ms -> do
655+
-- Clear the contents as no longer needed
656+
let !ms' = ms{ms_hspp_buf=Nothing}
657+
return ( Just (computeFingerprint f dflags ms), ([], Just ms'))
658+
Left diags -> return (Nothing, (diags, Nothing))
659+
where
660+
-- Compute a fingerprint from the contents of `ModSummary`,
661+
-- eliding the timestamps and other non relevant fields.
662+
computeFingerprint f dflags ModSummary{..} =
663+
let fingerPrint =
664+
( moduleNameString (moduleName ms_mod)
665+
, ms_hspp_file
666+
, map unLoc opts
667+
, ml_hs_file ms_location
668+
, fingerPrintImports ms_srcimps
669+
, fingerPrintImports ms_textual_imps
670+
)
671+
fingerPrintImports = map (fmap uniq *** (moduleNameString . unLoc))
672+
opts = Hdr.getOptions dflags (fromJust ms_hspp_buf) (fromNormalizedFilePath f)
673+
fp = hash fingerPrint
674+
in BS.pack (show fp)
632675

633676
getModIfaceRule :: Rules ()
634677
getModIfaceRule = define $ \GetModIface f -> do
@@ -667,10 +710,16 @@ getModIfaceRule = define $ \GetModIface f -> do
667710
case mb_pm of
668711
Nothing -> return (diags, Nothing)
669712
Just pm -> do
670-
(diags', tmr) <- typeCheckRuleDefinition f pm DoGenerateInterfaceFiles
671-
-- Bang pattern is important to avoid leaking 'tmr'
672-
let !res = extract tmr
673-
return (diags <> diags', res)
713+
-- We want GhcSessionDeps cache objects only for files of interest
714+
-- As that's no the case here, call the implementation directly
715+
(diags, mb_hsc) <- ghcSessionDepsDefinition f
716+
case mb_hsc of
717+
Nothing -> return (diags, Nothing)
718+
Just hsc -> do
719+
(diags', tmr) <- typeCheckRuleDefinition (hscEnv hsc) pm DoGenerateInterfaceFiles
720+
-- Bang pattern is important to avoid leaking 'tmr'
721+
let !res = extract tmr
722+
return (diags <> diags', res)
674723
where
675724
extract Nothing = Nothing
676725
extract (Just tmr) =

src/Development/IDE/Core/Shake.hs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,8 +28,10 @@ module Development.IDE.Core.Shake(
2828
shakeRestart,
2929
shakeEnqueue,
3030
shakeProfile,
31-
use, useWithStale, useNoFile, uses, usesWithStale,
31+
use, useNoFile, uses,
3232
use_, useNoFile_, uses_,
33+
useWithStale, usesWithStale,
34+
useWithStale_, usesWithStale_,
3335
define, defineEarlyCutoff, defineOnDisk, needOnDisk, needOnDisks,
3436
getDiagnostics, unsafeClearDiagnostics,
3537
getHiddenDiagnostics,
@@ -578,6 +580,17 @@ useWithStale :: IdeRule k v
578580
=> k -> NormalizedFilePath -> Action (Maybe (v, PositionMapping))
579581
useWithStale key file = head <$> usesWithStale key [file]
580582

583+
useWithStale_ :: IdeRule k v
584+
=> k -> NormalizedFilePath -> Action (v, PositionMapping)
585+
useWithStale_ key file = head <$> usesWithStale_ key [file]
586+
587+
usesWithStale_ :: IdeRule k v => k -> [NormalizedFilePath] -> Action [(v, PositionMapping)]
588+
usesWithStale_ key files = do
589+
res <- usesWithStale key files
590+
case sequence res of
591+
Nothing -> liftIO $ throwIO $ BadDependency (show key)
592+
Just v -> return v
593+
581594
useNoFile :: IdeRule k v => k -> Action (Maybe v)
582595
useNoFile key = use key emptyFilePath
583596

src/Development/IDE/Spans/Calculate.hs

Lines changed: 5 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -52,21 +52,19 @@ getSrcSpanInfos
5252
:: HscEnv
5353
-> [(Located ModuleName, Maybe NormalizedFilePath)] -- ^ Dependencies in topological order
5454
-> TcModuleResult
55-
-> [ParsedModule] -- ^ Dependencies parsed, optional
56-
-> [ModIface] -- ^ Dependencies module interfaces, required
55+
-> [ParsedModule] -- ^ Dependencies parsed, optional if the 'HscEnv' already contains docs
5756
-> IO SpansInfo
58-
getSrcSpanInfos env imports tc parsedDeps deps =
57+
getSrcSpanInfos env imports tc parsedDeps =
5958
evalGhcEnv env $
60-
getSpanInfo imports (tmrModule tc) parsedDeps deps
59+
getSpanInfo imports (tmrModule tc) parsedDeps
6160

6261
-- | Get ALL source spans in the module.
6362
getSpanInfo :: GhcMonad m
6463
=> [(Located ModuleName, Maybe NormalizedFilePath)] -- ^ imports
6564
-> TypecheckedModule
6665
-> [ParsedModule]
67-
-> [ModIface]
6866
-> m SpansInfo
69-
getSpanInfo mods tcm@TypecheckedModule{..} parsedDeps deps =
67+
getSpanInfo mods tcm@TypecheckedModule{..} parsedDeps =
7068
do let tcs = tm_typechecked_source
7169
bs = listifyAllSpans tcs :: [LHsBind GhcTc]
7270
es = listifyAllSpans tcs :: [LHsExpr GhcTc]
@@ -75,8 +73,7 @@ getSpanInfo mods tcm@TypecheckedModule{..} parsedDeps deps =
7573
allModules = tm_parsed_module : parsedDeps
7674
funBinds = funBindMap tm_parsed_module
7775

78-
-- Load all modules in HPT to make their interface documentation available
79-
mapM_ (`loadDepModule` Nothing) (reverse deps)
76+
-- Load this module in HPT to make its interface documentation available
8077
forM_ (modInfoIface tm_checked_module_info) $ \modIface ->
8178
modifySession (loadModuleHome $ HomeModInfo modIface (snd tm_internals_) Nothing)
8279

0 commit comments

Comments
 (0)