Skip to content

Commit dc08ce4

Browse files
committed
Improve recompilation avoidance in the presence of TH
The old recompilation avoidance scheme performs quite poorly when code generation is needed. We end up needed to recompile modules basically any time anything in their transitive dependency closure changes. Most versions of GHC we currently support don't have a working implementation of code unloading for object code, and no version of GHC supports this on certain platforms like Windows. This makes it completely infeasible for interactive use, as symbols from previous compiles will shadow over all future compiles. This means that we need to use bytecode when generating code for Template Haskell. Unfortunately, we can't serialize bytecode, so we will always need to recompile when the IDE starts. However, we can put in place a much tighter recompilation avoidance scheme for subsequent compiles: 1. If the source file changes, then we always need to recompile a. For files of interest, we will get explicit `textDocument/change` events that will let us invalidate our build products b. For files we read from disk, we can detect source file changes by comparing the mtime of the source file with the build product (.hi/.o) file on disk. 2. If GHC's recompilation avoidance scheme based on interface file hashes says that we need to recompile, the we need to recompile. 3. If the file in question requires code generation then, we need to recompile if we don't have the appropriate kind of build products. a. If we already have the build products in memory, and the conditions 1 and 2 hold, then we don't need to recompile b. If we are generating object code, then we can also search for it on disk and ensure it is up to date. Notably, we did _not_ previously re-use old bytecode from memory when hls-graph/shake decided to rebuild the 'HiFileResult' for some reason 4. If the file in question used Template Haskell on the previous compile, then we need to recompile if any `Linkable` in its transitive closure changed. This sounds bad, but it is possible to make some improvements. In particular, we only need to recompile if any of the `Linkable`s actually used during the previous compile change. How can we tell if a `Linkable` was actually used while running some TH? GHC provides a `hscCompileCoreExprHook` which lets us intercept bytecode as it is being compiled and linked. We can inspect the bytecode to see which `Linkable` dependencies it requires, and record this for use in recompilation checking. We record all the home package modules of the free names that occur in the bytecode. The `Linkable`s required are then the transitive closure of these modules in the home-package environment. This is the same scheme as used by GHC to find the correct things to link in before running bytecode. This works fine if we already have previous build products in memory, but what if we are reading an interface from disk? Well, we can smuggle in the necessary information (linkable `Module`s required as well as the time they were generated) using `Annotation`s, which provide a somewhat general purpose way to serialise arbitrary information along with interface files. Then when deciding whether to recompile, we need to check that the versions of the linkables used during a previous compile match whatever is currently in the HPT. The changes that were made to `ghcide` in order to implement this scheme include: 1. Add `RuleWithOldValue` to define Rules which have access to the previous value. This is the magic bit that lets us re-use bytecode from previous compiles 2. `IsHiFileStable` rule was removed as we don't need it with this scheme in place. 3. Everything in the store is properly versioned with a `FileVersion`, not just FOIs. 4. The VFSHandle type was removed. Instead we now take a VFS snapshot on every restart, and use this snapshot for all the `Rules` in that build. This ensures that Rules see a consistent version of the VFS and also makes The `setVirtualFileContents` function was removed since it was not being used anywhere. If needed in the future, we can easily just modify the VFS using functions from `lsp`. 5. Fix a bug with the `DependencyInformation` calculation, were modules at the top of the hierarchy (no incoming edges) weren't being recorded properly A possible future improvement is to use object-code on the first load (so we have a warm cache) and use bytecode for subsequent compiles.
1 parent 4650063 commit dc08ce4

File tree

7 files changed

+457
-72
lines changed

7 files changed

+457
-72
lines changed

Diff for: ghcide/src/Development/IDE/Core/Compile.hs

+270-57
Large diffs are not rendered by default.

Diff for: ghcide/src/Development/IDE/Core/RuleTypes.hs

+7-2
Original file line numberDiff line numberDiff line change
@@ -138,6 +138,9 @@ data TcModuleResult = TcModuleResult
138138
-- ^ Typechecked splice information
139139
, tmrDeferedError :: !Bool
140140
-- ^ Did we defer any type errors for this module?
141+
, tmrRuntimeModules :: !(ModuleEnv UTCTime)
142+
-- ^ Which modules did we need at runtime while compiling this file?
143+
-- Used for recompilation checking in the presence of TH
141144
}
142145
instance Show TcModuleResult where
143146
show = show . pm_mod_summary . tmrParsed
@@ -158,13 +161,15 @@ data HiFileResult = HiFileResult
158161
-- ^ Fingerprint for the ModIface
159162
, hirLinkableFp :: ByteString
160163
-- ^ Fingerprint for the Linkable
164+
, hirRuntimeModules :: !(ModuleEnv UTCTime)
165+
-- ^ same as tmrRuntimeModules
161166
}
162167

163168
hiFileFingerPrint :: HiFileResult -> ByteString
164169
hiFileFingerPrint HiFileResult{..} = hirIfaceFp <> hirLinkableFp
165170

166-
mkHiFileResult :: ModSummary -> HomeModInfo -> HiFileResult
167-
mkHiFileResult hirModSummary hirHomeMod = HiFileResult{..}
171+
mkHiFileResult :: ModSummary -> HomeModInfo -> ModuleEnv UTCTime -> HiFileResult
172+
mkHiFileResult hirModSummary hirHomeMod hirRuntimeModules = HiFileResult{..}
168173
where
169174
hirIfaceFp = fingerprintToBS . getModuleHash . hm_iface $ hirHomeMod -- will always be two bytes
170175
hirLinkableFp = case hm_linkable hirHomeMod of

Diff for: ghcide/src/Development/IDE/Core/Rules.hs

+13-9
Original file line numberDiff line numberDiff line change
@@ -658,13 +658,11 @@ typeCheckRuleDefinition hsc pm = do
658658

659659
-- | Get all the linkables stored in the graph, i.e. the ones we *do not* need to unload.
660660
-- Doesn't actually contain the code, since we don't need it to unload
661-
currentLinkables :: Action [Linkable]
661+
currentLinkables :: Action (ModuleEnv UTCTime)
662662
currentLinkables = do
663663
compiledLinkables <- getCompiledLinkables <$> getIdeGlobalAction
664664
hm <- liftIO $ readVar compiledLinkables
665-
pure $ map go $ moduleEnvToList hm
666-
where
667-
go (mod, time) = LM time mod []
665+
pure hm
668666

669667
loadGhcSession :: GhcSessionDepsConfig -> Rules ()
670668
loadGhcSession ghcSessionDepsConfig = do
@@ -750,11 +748,17 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ RuleWithOldValue $ \GetModIfaceFro
750748
Just session -> do
751749
linkableType <- getLinkableType f
752750
ver <- use_ GetModificationTime f
753-
let sourceModified = case old of
754-
Shake.Succeeded (Just old_version) _ | old_version == ver -> SourceUnmodified
755-
Shake.Stale _ (Just old_version) _ | old_version == ver -> SourceUnmodified
756-
_ -> SourceModified
757-
r <- loadInterface (hscEnv session) ms sourceModified linkableType (regenerateHiFile session f ms)
751+
let m_old = case old of
752+
Shake.Succeeded (Just old_version) v -> Just (v, old_version)
753+
Shake.Stale _ (Just old_version) v -> Just (v, old_version)
754+
_ -> Nothing
755+
recompInfo = RecompilationInfo
756+
{ source_version = ver
757+
, old_value = m_old
758+
, get_file_version = use GetModificationTime_{missingFileDiagnostics = False}
759+
, regenerate = regenerateHiFile session f ms
760+
}
761+
r <- loadInterface (hscEnv session) ms linkableType recompInfo
758762
case r of
759763
(diags, Nothing) -> return (Nothing, (diags, Nothing))
760764
(diags, Just x) -> do

Diff for: ghcide/src/Development/IDE/GHC/Compat.hs

+155-1
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ module Development.IDE.GHC.Compat(
2020
reLocA,
2121
getMessages',
2222
pattern PFailedWithErrorMessages,
23+
isObjectLinkable,
2324

2425
#if !MIN_VERSION_ghc(9,0,1)
2526
RefMap,
@@ -28,6 +29,7 @@ module Development.IDE.GHC.Compat(
2829
#if MIN_VERSION_ghc(9,2,0)
2930
extendModSummaryNoDeps,
3031
emsModSummary,
32+
myCoreToStgExpr,
3133
#endif
3234

3335
nodeInfo',
@@ -69,6 +71,39 @@ module Development.IDE.GHC.Compat(
6971
Option (..),
7072
runUnlit,
7173
runPp,
74+
75+
-- * Recompilation avoidance
76+
hscCompileCoreExprHook,
77+
CoreExpr,
78+
simplifyExpr,
79+
tidyExpr,
80+
emptyTidyEnv,
81+
corePrepExpr,
82+
lintInteractiveExpr,
83+
icInteractiveModule,
84+
HomePackageTable,
85+
lookupHpt,
86+
Dependencies(dep_mods),
87+
bcoFreeNames,
88+
ModIfaceAnnotation,
89+
pattern Annotation,
90+
AnnTarget(ModuleTarget),
91+
extendAnnEnvList,
92+
module UniqDSet,
93+
module UniqSet,
94+
module UniqDFM,
95+
getDependentMods,
96+
#if MIN_VERSION_ghc(9,2,0)
97+
loadExpr,
98+
byteCodeGen,
99+
bc_bcos,
100+
loadDecls,
101+
hscInterp,
102+
expectJust,
103+
#else
104+
coreExprToBCOs,
105+
linkExpr,
106+
#endif
72107
) where
73108

74109
import Development.IDE.GHC.Compat.Core
@@ -84,7 +119,48 @@ import Development.IDE.GHC.Compat.Util
84119
import GHC hiding (HasSrcSpan,
85120
ModLocation,
86121
RealSrcSpan, getLoc,
87-
lookupName)
122+
lookupName, exprType)
123+
#if MIN_VERSION_ghc(9,0,0)
124+
import GHC.Driver.Hooks (hscCompileCoreExprHook)
125+
import GHC.Core (CoreExpr, CoreProgram)
126+
import qualified GHC.Core.Opt.Pipeline as GHC
127+
import GHC.Core.Tidy (tidyExpr)
128+
import GHC.Types.Var.Env (emptyTidyEnv)
129+
import qualified GHC.CoreToStg.Prep as GHC
130+
import GHC.Core.Lint (lintInteractiveExpr)
131+
#if MIN_VERSION_ghc(9,2,0)
132+
import GHC.Unit.Home.ModInfo (lookupHpt, HomePackageTable)
133+
import GHC.Runtime.Context (icInteractiveModule)
134+
import GHC.Unit.Module.Deps (Dependencies(dep_mods))
135+
import GHC.Linker.Types (isObjectLinkable)
136+
import GHC.Linker.Loader (loadExpr)
137+
#else
138+
import GHC.CoreToByteCode (coreExprToBCOs)
139+
import GHC.Driver.Types (Dependencies(dep_mods), icInteractiveModule, lookupHpt, HomePackageTable)
140+
import GHC.Runtime.Linker (linkExpr)
141+
#endif
142+
import GHC.ByteCode.Asm (bcoFreeNames)
143+
import GHC.Types.Annotations (Annotation(..), AnnTarget(ModuleTarget), extendAnnEnvList)
144+
import GHC.Types.Unique.DSet as UniqDSet
145+
import GHC.Types.Unique.Set as UniqSet
146+
import GHC.Types.Unique.DFM as UniqDFM
147+
#else
148+
import Hooks (hscCompileCoreExprHook)
149+
import CoreSyn (CoreExpr)
150+
import qualified SimplCore as GHC
151+
import CoreTidy (tidyExpr)
152+
import VarEnv (emptyTidyEnv)
153+
import CorePrep (corePrepExpr)
154+
import CoreLint (lintInteractiveExpr)
155+
import ByteCodeGen (coreExprToBCOs)
156+
import HscTypes (icInteractiveModule, HomePackageTable, lookupHpt, Dependencies(dep_mods))
157+
import Linker (linkExpr)
158+
import ByteCodeAsm (bcoFreeNames)
159+
import Annotations (Annotation(..), AnnTarget(ModuleTarget), extendAnnEnvList)
160+
import UniqDSet
161+
import UniqSet
162+
import UniqDFM
163+
#endif
88164

89165
#if MIN_VERSION_ghc(9,0,0)
90166
import GHC.Data.StringBuffer
@@ -142,6 +218,67 @@ import qualified Data.Set as S
142218
import Bag (unitBag)
143219
#endif
144220

221+
#if MIN_VERSION_ghc(9,2,0)
222+
import GHC.Types.CostCentre
223+
import GHC.Stg.Syntax
224+
import GHC.Types.IPE
225+
import GHC.Stg.Syntax
226+
import GHC.Types.IPE
227+
import GHC.Types.CostCentre
228+
import GHC.Core
229+
import GHC.Builtin.Uniques
230+
import GHC.Runtime.Interpreter
231+
import GHC.StgToByteCode
232+
import GHC.Stg.Pipeline
233+
import GHC.ByteCode.Types
234+
import GHC.Linker.Loader (loadDecls)
235+
import GHC.Data.Maybe
236+
import GHC.CoreToStg
237+
#endif
238+
239+
type ModIfaceAnnotation = Annotation
240+
241+
#if MIN_VERSION_ghc(9,2,0)
242+
myCoreToStgExpr :: Logger -> DynFlags -> InteractiveContext
243+
-> Module -> ModLocation -> CoreExpr
244+
-> IO ( Id
245+
, [StgTopBinding]
246+
, InfoTableProvMap
247+
, CollectedCCs )
248+
myCoreToStgExpr logger dflags ictxt this_mod ml prepd_expr = do
249+
{- Create a temporary binding (just because myCoreToStg needs a
250+
binding for the stg2stg step) -}
251+
let bco_tmp_id = mkSysLocal (fsLit "BCO_toplevel")
252+
(mkPseudoUniqueE 0)
253+
Many
254+
(exprType prepd_expr)
255+
(stg_binds, prov_map, collected_ccs) <-
256+
myCoreToStg logger
257+
dflags
258+
ictxt
259+
this_mod
260+
ml
261+
[NonRec bco_tmp_id prepd_expr]
262+
return (bco_tmp_id, stg_binds, prov_map, collected_ccs)
263+
264+
myCoreToStg :: Logger -> DynFlags -> InteractiveContext
265+
-> Module -> ModLocation -> CoreProgram
266+
-> IO ( [StgTopBinding] -- output program
267+
, InfoTableProvMap
268+
, CollectedCCs ) -- CAF cost centre info (declared and used)
269+
myCoreToStg logger dflags ictxt this_mod ml prepd_binds = do
270+
let (stg_binds, denv, cost_centre_info)
271+
= {-# SCC "Core2Stg" #-}
272+
coreToStg dflags this_mod ml prepd_binds
273+
274+
stg_binds2
275+
<- {-# SCC "Stg2Stg" #-}
276+
stg2stg logger dflags ictxt this_mod stg_binds
277+
278+
return (stg_binds2, denv, cost_centre_info)
279+
#endif
280+
281+
145282
#if !MIN_VERSION_ghc(9,2,0)
146283
reLoc :: Located a -> Located a
147284
reLoc = id
@@ -150,6 +287,23 @@ reLocA :: Located a -> Located a
150287
reLocA = id
151288
#endif
152289

290+
getDependentMods :: ModIface -> [ModuleName]
291+
#if MIN_VERSION_ghc(9,0,0)
292+
getDependentMods = map gwib_mod . dep_mods . mi_deps
293+
#else
294+
getDependentMods = map fst . dep_mods . mi_deps
295+
#endif
296+
297+
simplifyExpr :: DynFlags -> HscEnv -> CoreExpr -> IO CoreExpr
298+
#if MIN_VERSION_ghc(9,0,0)
299+
simplifyExpr _ = GHC.simplifyExpr
300+
301+
corePrepExpr :: DynFlags -> HscEnv -> CoreExpr -> IO CoreExpr
302+
corePrepExpr _ = GHC.corePrepExpr
303+
#else
304+
simplifyExpr df _ = GHC.simplifyExpr df
305+
#endif
306+
153307
#if !MIN_VERSION_ghc(8,8,0)
154308
hPutStringBuffer :: Handle -> StringBuffer -> IO ()
155309
hPutStringBuffer hdl (StringBuffer buf len cur)

Diff for: ghcide/src/Development/IDE/GHC/Orphans.hs

+11-1
Original file line numberDiff line numberDiff line change
@@ -39,6 +39,11 @@ import Data.Aeson
3939
import Data.Bifunctor (Bifunctor (..))
4040
import Data.Hashable
4141
import Data.String (IsString (fromString))
42+
#if MIN_VERSION_ghc(9,0,0)
43+
import GHC.ByteCode.Types
44+
#else
45+
import ByteCodeTypes
46+
#endif
4247

4348
-- Orphan instances for types from the GHC API.
4449
instance Show CoreModule where show = prettyPrint
@@ -49,7 +54,12 @@ instance Show ModDetails where show = const "<moddetails>"
4954
instance NFData ModDetails where rnf = rwhnf
5055
instance NFData SafeHaskellMode where rnf = rwhnf
5156
instance Show Linkable where show = prettyPrint
52-
instance NFData Linkable where rnf = rwhnf
57+
instance NFData Linkable where rnf (LM a b c) = rnf a `seq` rnf b `seq` rnf c
58+
instance NFData Unlinked where
59+
rnf (DotO f) = rnf f
60+
rnf (DotA f) = rnf f
61+
rnf (DotDLL f) = rnf f
62+
rnf (BCOs a b) = seqCompiledByteCode a `seq` liftRnf rwhnf b
5363
instance Show PackageFlag where show = prettyPrint
5464
instance Show InteractiveImport where show = prettyPrint
5565
instance Show PackageName where show = prettyPrint

Diff for: ghcide/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ import qualified Data.Map.Strict as Map
3333
import Data.Maybe (fromJust, isNothing,
3434
mapMaybe)
3535
import qualified Data.Text as T
36-
import Development.IDE.GHC.Compat
36+
import Development.IDE.GHC.Compat hiding (Annotation)
3737
import Development.IDE.GHC.Error
3838
import Development.IDE.GHC.ExactPrint
3939
import Development.IDE.Spans.Common

Diff for: ghcide/src/Development/IDE/Types/Shake.hs

-1
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ import Development.IDE.Types.Diagnostics
3131
import Development.IDE.Types.Location
3232
import GHC.Generics
3333
import HieDb.Types (HieDb)
34-
import Language.LSP.Types
3534
import qualified StmContainers.Map as STM
3635
import Type.Reflection (SomeTypeRep (SomeTypeRep),
3736
pattern App, pattern Con,

0 commit comments

Comments
 (0)