Skip to content

Commit 3c0a9f6

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 7140ff1 commit 3c0a9f6

File tree

8 files changed

+473
-115
lines changed

8 files changed

+473
-115
lines changed

ghcide/src/Development/IDE.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,7 @@ import Development.IDE.Core.IdeConfiguration as X (IdeConfiguration (.
1717
isWorkspaceFile)
1818
import Development.IDE.Core.OfInterest as X (getFilesOfInterestUntracked)
1919
import Development.IDE.Core.RuleTypes as X
20-
import Development.IDE.Core.Rules as X (IsHiFileStable (..),
21-
getClientConfigAction,
20+
import Development.IDE.Core.Rules as X (getClientConfigAction,
2221
getParsedModule)
2322
import Development.IDE.Core.Service as X (runAction)
2423
import Development.IDE.Core.Shake as X (FastResult (..),

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

Lines changed: 270 additions & 57 deletions
Large diffs are not rendered by default.

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

Lines changed: 7 additions & 2 deletions
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

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

Lines changed: 15 additions & 45 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,6 @@ module Development.IDE.Core.Rules(
3030
usePropertyAction,
3131
-- * Rules
3232
CompiledLinkables(..),
33-
IsHiFileStable(..),
3433
getParsedModuleRule,
3534
getParsedModuleWithCommentsRule,
3635
getLocatedImportsRule,
@@ -42,7 +41,6 @@ module Development.IDE.Core.Rules(
4241
getModIfaceFromDiskRule,
4342
getModIfaceRule,
4443
getModSummaryRule,
45-
isHiFileStableRule,
4644
getModuleGraphRule,
4745
knownFilesRule,
4846
getClientSettingsRule,
@@ -660,13 +658,11 @@ typeCheckRuleDefinition hsc pm = do
660658

661659
-- | Get all the linkables stored in the graph, i.e. the ones we *do not* need to unload.
662660
-- Doesn't actually contain the code, since we don't need it to unload
663-
currentLinkables :: Action [Linkable]
661+
currentLinkables :: Action (ModuleEnv UTCTime)
664662
currentLinkables = do
665663
compiledLinkables <- getCompiledLinkables <$> getIdeGlobalAction
666664
hm <- liftIO $ readVar compiledLinkables
667-
pure $ map go $ moduleEnvToList hm
668-
where
669-
go (mod, time) = LM time mod []
665+
pure hm
670666

671667
loadGhcSession :: GhcSessionDepsConfig -> Rules ()
672668
loadGhcSession ghcSessionDepsConfig = do
@@ -744,15 +740,25 @@ ghcSessionDepsDefinition fullModSummary GhcSessionDepsConfig{..} env file = do
744740
-- | Load a iface from disk, or generate it if there isn't one or it is out of date
745741
-- This rule also ensures that the `.hie` and `.o` (if needed) files are written out.
746742
getModIfaceFromDiskRule :: Rules ()
747-
getModIfaceFromDiskRule = defineEarlyCutoff $ Rule $ \GetModIfaceFromDisk f -> do
743+
getModIfaceFromDiskRule = defineEarlyCutoff $ RuleWithOldValue $ \GetModIfaceFromDisk f old -> do
748744
ms <- msrModSummary <$> use_ GetModSummary f
749745
mb_session <- use GhcSessionDeps f
750746
case mb_session of
751747
Nothing -> return (Nothing, ([], Nothing))
752748
Just session -> do
753-
sourceModified <- use_ IsHiFileStable f
754749
linkableType <- getLinkableType f
755-
r <- loadInterface (hscEnv session) ms sourceModified linkableType (regenerateHiFile session f ms)
750+
ver <- use_ GetModificationTime f
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
756762
case r of
757763
(diags, Nothing) -> return (Nothing, (diags, Nothing))
758764
(diags, Just x) -> do
@@ -803,31 +809,6 @@ getModIfaceFromDiskAndIndexRule =
803809

804810
return (Just x)
805811

806-
isHiFileStableRule :: Rules ()
807-
isHiFileStableRule = defineEarlyCutoff $ RuleNoDiagnostics $ \IsHiFileStable f -> do
808-
ms <- msrModSummary <$> use_ GetModSummaryWithoutTimestamps f
809-
let hiFile = toNormalizedFilePath'
810-
$ Compat.ml_hi_file $ ms_location ms
811-
mbHiVersion <- use GetModificationTime_{missingFileDiagnostics=False} hiFile
812-
modVersion <- use_ GetModificationTime f
813-
sourceModified <- case mbHiVersion of
814-
Nothing -> pure SourceModified
815-
Just x ->
816-
if modificationTime x < modificationTime modVersion
817-
then pure SourceModified
818-
else do
819-
fileImports <- use_ GetLocatedImports f
820-
let imports = fmap artifactFilePath . snd <$> fileImports
821-
deps <- uses_ IsHiFileStable (catMaybes imports)
822-
pure $ if all (== SourceUnmodifiedAndStable) deps
823-
then SourceUnmodifiedAndStable
824-
else SourceUnmodified
825-
return (Just (summarize sourceModified), Just sourceModified)
826-
where
827-
summarize SourceModified = BS.singleton 1
828-
summarize SourceUnmodified = BS.singleton 2
829-
summarize SourceUnmodifiedAndStable = BS.singleton 3
830-
831812
displayTHWarning :: LspT c IO ()
832813
displayTHWarning
833814
| not isWindows && not hostIsDynamic = do
@@ -1123,7 +1104,6 @@ mainRule RulesConfig{..} = do
11231104
getModIfaceFromDiskAndIndexRule
11241105
getModIfaceRule
11251106
getModSummaryRule
1126-
isHiFileStableRule
11271107
getModuleGraphRule
11281108
knownFilesRule
11291109
getClientSettingsRule
@@ -1145,13 +1125,3 @@ mainRule RulesConfig{..} = do
11451125
persistentHieFileRule
11461126
persistentDocMapRule
11471127
persistentImportMapRule
1148-
1149-
-- | Given the path to a module src file, this rule returns True if the
1150-
-- corresponding `.hi` file is stable, that is, if it is newer
1151-
-- than the src file, and all its dependencies are stable too.
1152-
data IsHiFileStable = IsHiFileStable
1153-
deriving (Eq, Show, Typeable, Generic)
1154-
instance Hashable IsHiFileStable
1155-
instance NFData IsHiFileStable
1156-
1157-
type instance RuleResult IsHiFileStable = SourceModified

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

Lines changed: 13 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -986,6 +986,7 @@ data RuleBody k v
986986
{ newnessCheck :: BS.ByteString -> BS.ByteString -> Bool
987987
, build :: k -> NormalizedFilePath -> Action (Maybe BS.ByteString, Maybe v)
988988
}
989+
| RuleWithOldValue (k -> NormalizedFilePath -> Value v -> Action (Maybe BS.ByteString, IdeResult v))
989990

990991
-- | Define a new Rule with early cutoff
991992
defineEarlyCutoff
@@ -997,13 +998,13 @@ defineEarlyCutoff (Rule op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteSt
997998
let diagnostics diags = do
998999
traceDiagnostics diags
9991000
updateFileDiagnostics file (Key key) extras . map (\(_,y,z) -> (y,z)) $ diags
1000-
defineEarlyCutoff' diagnostics (==) key file old mode $ op key file
1001+
defineEarlyCutoff' diagnostics (==) key file old mode $ const $ op key file
10011002
defineEarlyCutoff (RuleNoDiagnostics op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \traceDiagnostics -> do
10021003
ShakeExtras{logger} <- getShakeExtras
10031004
let diagnostics diags = do
10041005
traceDiagnostics diags
10051006
mapM_ (\d -> liftIO $ logWarning logger $ showDiagnosticsColored [d]) diags
1006-
defineEarlyCutoff' diagnostics (==) key file old mode $ second (mempty,) <$> op key file
1007+
defineEarlyCutoff' diagnostics (==) key file old mode $ const $ second (mempty,) <$> op key file
10071008
defineEarlyCutoff RuleWithCustomNewnessCheck{..} =
10081009
addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode ->
10091010
otTracedAction key file mode traceA $ \ traceDiagnostics -> do
@@ -1012,7 +1013,13 @@ defineEarlyCutoff RuleWithCustomNewnessCheck{..} =
10121013
mapM_ (\d -> liftIO $ logWarning logger $ showDiagnosticsColored [d]) diags
10131014
traceDiagnostics diags
10141015
defineEarlyCutoff' diagnostics newnessCheck key file old mode $
1015-
second (mempty,) <$> build key file
1016+
const $ second (mempty,) <$> build key file
1017+
defineEarlyCutoff (RuleWithOldValue op) = addRule $ \(Q (key, file)) (old :: Maybe BS.ByteString) mode -> otTracedAction key file mode traceA $ \traceDiagnostics -> do
1018+
extras <- getShakeExtras
1019+
let diagnostics diags = do
1020+
traceDiagnostics diags
1021+
updateFileDiagnostics file (Key key) extras . map (\(_,y,z) -> (y,z)) $ diags
1022+
defineEarlyCutoff' diagnostics (==) key file old mode $ op key file
10161023

10171024
defineNoFile :: IdeRule k v => (k -> Action v) -> Rules ()
10181025
defineNoFile f = defineNoDiagnostics $ \k file -> do
@@ -1025,15 +1032,15 @@ defineEarlyCutOffNoFile f = defineEarlyCutoff $ RuleNoDiagnostics $ \k file -> d
10251032
fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file"
10261033

10271034
defineEarlyCutoff'
1028-
:: IdeRule k v
1035+
:: forall k v. IdeRule k v
10291036
=> ([FileDiagnostic] -> Action ()) -- ^ update diagnostics
10301037
-- | compare current and previous for freshness
10311038
-> (BS.ByteString -> BS.ByteString -> Bool)
10321039
-> k
10331040
-> NormalizedFilePath
10341041
-> Maybe BS.ByteString
10351042
-> RunMode
1036-
-> Action (Maybe BS.ByteString, IdeResult v)
1043+
-> (Value v -> Action (Maybe BS.ByteString, IdeResult v))
10371044
-> Action (RunResult (A (RuleResult k)))
10381045
defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
10391046
ShakeExtras{state, progress, dirtyKeys} <- getShakeExtras
@@ -1063,7 +1070,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
10631070
Just (Failed b, _) -> Failed b
10641071

10651072
(bs, (diags, res)) <- actionCatch
1066-
(do v <- action; liftIO $ evaluate $ force v) $
1073+
(do v <- action staleV; liftIO $ evaluate $ force v) $
10671074
\(e :: SomeException) -> do
10681075
pure (Nothing, ([ideErrorText file $ T.pack $ show e | not $ isBadDependency e],Nothing))
10691076

0 commit comments

Comments
 (0)