Skip to content

Commit 2ee2943

Browse files
authored
Technology preview: Keep track of changes to minimize rebuilds (#1862)
* Tell Shake what has changed * Insert placeholders for missing Shake features * disable run subset if the client doesn't support file watches * fix another cradle test
1 parent cee889e commit 2ee2943

File tree

18 files changed

+189
-113
lines changed

18 files changed

+189
-113
lines changed

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -236,8 +236,6 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
236236
-- Version of the mappings above
237237
version <- newVar 0
238238
let returnWithVersion fun = IdeGhcSession fun <$> liftIO (readVar version)
239-
let invalidateShakeCache = do
240-
void $ modifyVar' version succ
241239
-- This caches the mapping from Mod.hs -> hie.yaml
242240
cradleLoc <- liftIO $ memoIO $ \v -> do
243241
res <- findCradle v
@@ -253,6 +251,9 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
253251
return $ do
254252
extras@ShakeExtras{logger, restartShakeSession, ideNc, knownTargetsVar, lspEnv
255253
} <- getShakeExtras
254+
let invalidateShakeCache = do
255+
void $ modifyVar' version succ
256+
recordDirtyKeys extras GhcSessionIO [emptyFilePath]
256257

257258
IdeOptions{ optTesting = IdeTesting optTesting
258259
, optCheckProject = getCheckProject

ghcide/src/Development/IDE.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import Development.IDE.Core.FileExists as X (getFileExists)
1515
import Development.IDE.Core.FileStore as X (getFileContents)
1616
import Development.IDE.Core.IdeConfiguration as X (IdeConfiguration (..),
1717
isWorkspaceFile)
18-
import Development.IDE.Core.OfInterest as X (getFilesOfInterest)
18+
import Development.IDE.Core.OfInterest as X (getFilesOfInterestUntracked)
1919
import Development.IDE.Core.RuleTypes as X
2020
import Development.IDE.Core.Rules as X (IsHiFileStable (..),
2121
getClientConfigAction,

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -116,7 +116,7 @@ highlightAtPoint file pos = runMaybeT $ do
116116
refsAtPoint :: NormalizedFilePath -> Position -> Action [Location]
117117
refsAtPoint file pos = do
118118
ShakeExtras{hiedb} <- getShakeExtras
119-
fs <- HM.keys <$> getFilesOfInterest
119+
fs <- HM.keys <$> getFilesOfInterestUntracked
120120
asts <- HM.fromList . mapMaybe sequence . zip fs <$> usesWithStale GetHieAst fs
121121
AtPoint.referencesAtPoint hiedb file pos (AtPoint.FOIReferences asts)
122122

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

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -102,9 +102,11 @@ modifyFileExists state changes = do
102102
void $ modifyVar' var $ HashMap.union (HashMap.mapMaybe fromChange changesMap)
103103
-- See Note [Invalidating file existence results]
104104
-- flush previous values
105-
let (_fileModifChanges, fileExistChanges) =
105+
let (fileModifChanges, fileExistChanges) =
106106
partition ((== FcChanged) . snd) (HashMap.toList changesMap)
107107
mapM_ (deleteValue (shakeExtras state) GetFileExists . fst) fileExistChanges
108+
recordDirtyKeys (shakeExtras state) GetFileExists $ map fst fileExistChanges
109+
recordDirtyKeys (shakeExtras state) GetModificationTime $ map fst fileModifChanges
108110

109111
fromChange :: FileChangeType -> Maybe Bool
110112
fromChange FcCreated = Just True

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

Lines changed: 24 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,6 @@ module Development.IDE.Core.FileStore(
1414
VFSHandle,
1515
makeVFSHandle,
1616
makeLSPVFSHandle,
17-
isFileOfInterestRule,
1817
resetFileStore,
1918
resetInterfaceStore,
2019
getModificationTimeImpl,
@@ -40,8 +39,7 @@ import qualified Data.Rope.UTF16 as Rope
4039
import qualified Data.Text as T
4140
import Data.Time
4241
import Data.Time.Clock.POSIX
43-
import Development.IDE.Core.OfInterest (OfInterestVar (..),
44-
getFilesOfInterest)
42+
import Development.IDE.Core.OfInterest (OfInterestVar (..))
4543
import Development.IDE.Core.RuleTypes
4644
import Development.IDE.Core.Shake
4745
import Development.IDE.GHC.Orphans ()
@@ -50,6 +48,7 @@ import Development.IDE.Import.DependencyInformation
5048
import Development.IDE.Types.Diagnostics
5149
import Development.IDE.Types.Location
5250
import Development.IDE.Types.Options
51+
import Development.IDE.Types.Shake (SomeShakeValue)
5352
import HieDb.Create (deleteMissingRealFiles)
5453
import Ide.Plugin.Config (CheckParents (..),
5554
Config)
@@ -66,6 +65,9 @@ import qualified Development.IDE.Types.Logger as L
6665

6766
import qualified Data.Binary as B
6867
import qualified Data.ByteString.Lazy as LBS
68+
import qualified Data.HashSet as HSet
69+
import Data.IORef.Extra (atomicModifyIORef_)
70+
import Data.List (foldl')
6971
import qualified Data.Text as Text
7072
import Development.IDE.Core.IdeConfiguration (isWorkspaceFile)
7173
import Language.LSP.Server hiding
@@ -117,19 +119,6 @@ addWatchedFileRule isWatched = defineNoDiagnostics $ \AddWatchedFile f -> do
117119
registerFileWatches [fromNormalizedFilePath f]
118120
Nothing -> pure $ Just False
119121

120-
isFileOfInterestRule :: Rules ()
121-
isFileOfInterestRule = defineEarlyCutoff $ RuleNoDiagnostics $ \IsFileOfInterest f -> do
122-
filesOfInterest <- getFilesOfInterest
123-
let foi = maybe NotFOI IsFOI $ f `HM.lookup` filesOfInterest
124-
fp = summarize foi
125-
res = (Just fp, Just foi)
126-
return res
127-
where
128-
summarize NotFOI = BS.singleton 0
129-
summarize (IsFOI OnDisk) = BS.singleton 1
130-
summarize (IsFOI (Modified False)) = BS.singleton 2
131-
summarize (IsFOI (Modified True)) = BS.singleton 3
132-
133122

134123
getModificationTimeRule :: VFSHandle -> Rules ()
135124
getModificationTimeRule vfs = defineEarlyCutoff $ Rule $ \(GetModificationTime_ missingFileDiags) file ->
@@ -183,20 +172,21 @@ resetInterfaceStore state f = do
183172

184173
-- | Reset the GetModificationTime state of watched files
185174
resetFileStore :: IdeState -> [FileEvent] -> IO ()
186-
resetFileStore ideState changes = mask $ \_ ->
187-
forM_ changes $ \(FileEvent uri c) ->
175+
resetFileStore ideState changes = mask $ \_ -> do
176+
-- we record FOIs document versions in all the stored values
177+
-- so NEVER reset FOIs to avoid losing their versions
178+
OfInterestVar foisVar <- getIdeGlobalExtras (shakeExtras ideState)
179+
fois <- readVar foisVar
180+
forM_ changes $ \(FileEvent uri c) -> do
188181
case c of
189182
FcChanged
190183
| Just f <- uriToFilePath uri
191-
-> do
192-
-- we record FOIs document versions in all the stored values
193-
-- so NEVER reset FOIs to avoid losing their versions
194-
OfInterestVar foisVar <- getIdeGlobalExtras (shakeExtras ideState)
195-
fois <- readVar foisVar
196-
unless (HM.member (toNormalizedFilePath f) fois) $ do
197-
deleteValue (shakeExtras ideState) GetModificationTime (toNormalizedFilePath' f)
184+
, nfp <- toNormalizedFilePath f
185+
, not $ HM.member nfp fois
186+
-> deleteValue (shakeExtras ideState) GetModificationTime nfp
198187
_ -> pure ()
199188

189+
200190
-- Dir.getModificationTime is surprisingly slow since it performs
201191
-- a ton of conversions. Since we do not actually care about
202192
-- the format of the time, we can get away with something cheaper.
@@ -262,7 +252,6 @@ fileStoreRules vfs isWatched = do
262252
addIdeGlobal vfs
263253
getModificationTimeRule vfs
264254
getFileContentsRule vfs
265-
isFileOfInterestRule
266255
addWatchedFileRule isWatched
267256

268257
-- | Note that some buffer for a specific file has been modified but not
@@ -281,7 +270,8 @@ setFileModified state saved nfp = do
281270
VFSHandle{..} <- getIdeGlobalState state
282271
when (isJust setVirtualFileContents) $
283272
fail "setFileModified can't be called on this type of VFSHandle"
284-
shakeRestart state []
273+
recordDirtyKeys (shakeExtras state) GetModificationTime [nfp]
274+
restartShakeSession (shakeExtras state) []
285275
when checkParents $
286276
typecheckParents state nfp
287277

@@ -301,17 +291,19 @@ typecheckParentsAction nfp = do
301291
`catch` \(e :: SomeException) -> log (show e)
302292
() <$ uses GetModIface rs
303293

304-
-- | Note that some buffer somewhere has been modified, but don't say what.
294+
-- | Note that some keys have been modified and restart the session
305295
-- Only valid if the virtual file system was initialised by LSP, as that
306296
-- independently tracks which files are modified.
307-
setSomethingModified :: IdeState -> IO ()
308-
setSomethingModified state = do
297+
setSomethingModified :: IdeState -> [SomeShakeValue] -> IO ()
298+
setSomethingModified state keys = do
309299
VFSHandle{..} <- getIdeGlobalState state
310300
when (isJust setVirtualFileContents) $
311301
fail "setSomethingModified can't be called on this type of VFSHandle"
312302
-- Update database to remove any files that might have been renamed/deleted
313303
atomically $ writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) deleteMissingRealFiles
314-
void $ shakeRestart state []
304+
atomicModifyIORef_ (dirtyKeys $ shakeExtras state) $ \x ->
305+
foldl' (flip HSet.insert) x keys
306+
void $ restartShakeSession (shakeExtras state) []
315307

316308
registerFileWatches :: [String] -> LSP.LspT Config IO Bool
317309
registerFileWatches globs = do
@@ -338,7 +330,7 @@ registerFileWatches globs = do
338330
-- support that: https://github.com/bubba/lsp-test/issues/77
339331
watchers = [ watcher (Text.pack glob) | glob <- globs ]
340332

341-
void $ LSP.sendRequest LSP.SClientRegisterCapability regParams (const $ pure ())
333+
void $ LSP.sendRequest LSP.SClientRegisterCapability regParams (const $ pure ()) -- TODO handle response
342334
return True
343335
else return False
344336

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

Lines changed: 37 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -5,26 +5,28 @@
55
{-# LANGUAGE TypeFamilies #-}
66

77
-- | Utilities and state for the files of interest - those which are currently
8-
-- open in the editor. The useful function is 'getFilesOfInterest'.
8+
-- open in the editor. The rule is 'IsFileOfInterest'
99
module Development.IDE.Core.OfInterest(
1010
ofInterestRules,
11-
getFilesOfInterest, setFilesOfInterest, modifyFilesOfInterest,
11+
getFilesOfInterestUntracked,
12+
addFileOfInterest,
13+
deleteFileOfInterest,
14+
setFilesOfInterest,
1215
kick, FileOfInterestStatus(..),
1316
OfInterestVar(..)
1417
) where
1518

1619
import Control.Concurrent.Strict
1720
import Control.Monad
1821
import Control.Monad.IO.Class
19-
import Data.Binary
2022
import Data.HashMap.Strict (HashMap)
2123
import qualified Data.HashMap.Strict as HashMap
2224
import qualified Data.Text as T
2325
import Development.IDE.Graph
2426

2527
import Control.Monad.Trans.Class
2628
import Control.Monad.Trans.Maybe
27-
import qualified Data.ByteString.Lazy as LBS
29+
import qualified Data.ByteString as BS
2830
import Data.List.Extra (nubOrd)
2931
import Data.Maybe (catMaybes)
3032
import Development.IDE.Core.ProgressReporting
@@ -43,45 +45,59 @@ instance IsIdeGlobal OfInterestVar
4345
ofInterestRules :: Rules ()
4446
ofInterestRules = do
4547
addIdeGlobal . OfInterestVar =<< liftIO (newVar HashMap.empty)
46-
defineEarlyCutOffNoFile $ \GetFilesOfInterest -> do
48+
defineEarlyCutoff $ RuleNoDiagnostics $ \IsFileOfInterest f -> do
4749
alwaysRerun
4850
filesOfInterest <- getFilesOfInterestUntracked
49-
let !cutoff = LBS.toStrict $ encode $ HashMap.toList filesOfInterest
50-
pure (cutoff, filesOfInterest)
51+
let foi = maybe NotFOI IsFOI $ f `HashMap.lookup` filesOfInterest
52+
fp = summarize foi
53+
res = (Just fp, Just foi)
54+
return res
55+
where
56+
summarize NotFOI = BS.singleton 0
57+
summarize (IsFOI OnDisk) = BS.singleton 1
58+
summarize (IsFOI (Modified False)) = BS.singleton 2
59+
summarize (IsFOI (Modified True)) = BS.singleton 3
5160

52-
-- | Get the files that are open in the IDE.
53-
getFilesOfInterest :: Action (HashMap NormalizedFilePath FileOfInterestStatus)
54-
getFilesOfInterest = useNoFile_ GetFilesOfInterest
5561

5662
------------------------------------------------------------
5763
-- Exposed API
5864

5965
-- | Set the files-of-interest - not usually necessary or advisable.
6066
-- The LSP client will keep this information up to date.
6167
setFilesOfInterest :: IdeState -> HashMap NormalizedFilePath FileOfInterestStatus -> IO ()
62-
setFilesOfInterest state files = modifyFilesOfInterest state (const files)
68+
setFilesOfInterest state files = do
69+
OfInterestVar var <- getIdeGlobalState state
70+
writeVar var files
6371

6472
getFilesOfInterestUntracked :: Action (HashMap NormalizedFilePath FileOfInterestStatus)
6573
getFilesOfInterestUntracked = do
6674
OfInterestVar var <- getIdeGlobalAction
6775
liftIO $ readVar var
6876

69-
-- | Modify the files-of-interest - not usually necessary or advisable.
70-
-- The LSP client will keep this information up to date.
71-
modifyFilesOfInterest
72-
:: IdeState
73-
-> (HashMap NormalizedFilePath FileOfInterestStatus -> HashMap NormalizedFilePath FileOfInterestStatus)
74-
-> IO ()
75-
modifyFilesOfInterest state f = do
77+
addFileOfInterest :: IdeState -> NormalizedFilePath -> FileOfInterestStatus -> IO ()
78+
addFileOfInterest state f v = do
7679
OfInterestVar var <- getIdeGlobalState state
77-
files <- modifyVar' var f
78-
logDebug (ideLogger state) $ "Set files of interest to: " <> T.pack (show $ HashMap.toList files)
80+
(prev, files) <- modifyVar var $ \dict -> do
81+
let (prev, new) = HashMap.alterF (, Just v) f dict
82+
pure (new, (prev, dict))
83+
when (prev /= Just v) $
84+
recordDirtyKeys (shakeExtras state) IsFileOfInterest [f]
85+
logDebug (ideLogger state) $
86+
"Set files of interest to: " <> T.pack (show files)
87+
88+
deleteFileOfInterest :: IdeState -> NormalizedFilePath -> IO ()
89+
deleteFileOfInterest state f = do
90+
OfInterestVar var <- getIdeGlobalState state
91+
files <- modifyVar' var $ HashMap.delete f
92+
recordDirtyKeys (shakeExtras state) IsFileOfInterest [f]
93+
logDebug (ideLogger state) $ "Set files of interest to: " <> T.pack (show files)
94+
7995

8096
-- | Typecheck all the files of interest.
8197
-- Could be improved
8298
kick :: Action ()
8399
kick = do
84-
files <- HashMap.keys <$> getFilesOfInterest
100+
files <- HashMap.keys <$> getFilesOfInterestUntracked
85101
ShakeExtras{progress} <- getShakeExtras
86102
liftIO $ progressUpdate progress KickStarted
87103

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

Lines changed: 0 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,6 @@ import HscTypes (HomeModInfo,
4040
import qualified Data.Binary as B
4141
import Data.ByteString (ByteString)
4242
import qualified Data.ByteString.Lazy as LBS
43-
import Data.HashMap.Strict (HashMap)
4443
import Data.Text (Text)
4544
import Data.Time
4645
import Development.IDE.Import.FindImports (ArtifactsLocation)
@@ -356,8 +355,6 @@ type instance RuleResult GetModSummary = ModSummaryResult
356355
-- | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff
357356
type instance RuleResult GetModSummaryWithoutTimestamps = ModSummaryResult
358357

359-
type instance RuleResult GetFilesOfInterest = HashMap NormalizedFilePath FileOfInterestStatus
360-
361358
data GetParsedModule = GetParsedModule
362359
deriving (Eq, Show, Typeable, Generic)
363360
instance Hashable GetParsedModule
@@ -521,12 +518,6 @@ instance Hashable GhcSessionIO
521518
instance NFData GhcSessionIO
522519
instance Binary GhcSessionIO
523520

524-
data GetFilesOfInterest = GetFilesOfInterest
525-
deriving (Eq, Show, Typeable, Generic)
526-
instance Hashable GetFilesOfInterest
527-
instance NFData GetFilesOfInterest
528-
instance Binary GetFilesOfInterest
529-
530521
makeLensesWith
531522
(lensRules & lensField .~ mappingNamer (pure . (++ "L")))
532523
''Splices

0 commit comments

Comments
 (0)