Skip to content

Commit 43bce9d

Browse files
committed
Tell Shake what has changed
1 parent 53747d1 commit 43bce9d

File tree

15 files changed

+162
-99
lines changed

15 files changed

+162
-99
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/FileStore.hs

Lines changed: 25 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,
@@ -38,8 +37,7 @@ import qualified Data.Rope.UTF16 as Rope
3837
import qualified Data.Text as T
3938
import Data.Time
4039
import Data.Time.Clock.POSIX
41-
import Development.IDE.Core.OfInterest (OfInterestVar (..),
42-
getFilesOfInterest)
40+
import Development.IDE.Core.OfInterest (OfInterestVar (..))
4341
import Development.IDE.Core.RuleTypes
4442
import Development.IDE.Core.Shake
4543
import Development.IDE.GHC.Orphans ()
@@ -48,6 +46,7 @@ import Development.IDE.Import.DependencyInformation
4846
import Development.IDE.Types.Diagnostics
4947
import Development.IDE.Types.Location
5048
import Development.IDE.Types.Options
49+
import Development.IDE.Types.Shake (SomeShakeValue)
5150
import HieDb.Create (deleteMissingRealFiles)
5251
import Ide.Plugin.Config (CheckParents (..))
5352
import System.IO.Error
@@ -63,6 +62,9 @@ import qualified Development.IDE.Types.Logger as L
6362

6463
import qualified Data.Binary as B
6564
import qualified Data.ByteString.Lazy as LBS
65+
import qualified Data.HashSet as HSet
66+
import Data.IORef.Extra (atomicModifyIORef_)
67+
import Data.List (foldl')
6668
import Language.LSP.Server hiding
6769
(getVirtualFile)
6870
import qualified Language.LSP.Server as LSP
@@ -95,20 +97,6 @@ makeLSPVFSHandle lspEnv = VFSHandle
9597
}
9698

9799

98-
isFileOfInterestRule :: Rules ()
99-
isFileOfInterestRule = defineEarlyCutoff $ RuleNoDiagnostics $ \IsFileOfInterest f -> do
100-
filesOfInterest <- getFilesOfInterest
101-
let foi = maybe NotFOI IsFOI $ f `HM.lookup` filesOfInterest
102-
fp = summarize foi
103-
res = (Just fp, Just foi)
104-
return res
105-
where
106-
summarize NotFOI = BS.singleton 0
107-
summarize (IsFOI OnDisk) = BS.singleton 1
108-
summarize (IsFOI (Modified False)) = BS.singleton 2
109-
summarize (IsFOI (Modified True)) = BS.singleton 3
110-
111-
112100
getModificationTimeRule :: VFSHandle -> (NormalizedFilePath -> Action Bool) -> Rules ()
113101
getModificationTimeRule vfs isWatched = defineEarlyCutoff $ Rule $ \(GetModificationTime_ missingFileDiags) file ->
114102
getModificationTimeImpl vfs isWatched missingFileDiags file
@@ -163,21 +151,23 @@ resetInterfaceStore state f = do
163151

164152
-- | Reset the GetModificationTime state of watched files
165153
resetFileStore :: IdeState -> [FileEvent] -> IO ()
166-
resetFileStore ideState changes = mask $ \_ ->
167-
forM_ changes $ \(FileEvent uri c) ->
154+
resetFileStore ideState changes = mask $ \_ -> do
155+
-- we record FOIs document versions in all the stored values
156+
-- so NEVER reset FOIs to avoid losing their versions
157+
OfInterestVar foisVar <- getIdeGlobalExtras (shakeExtras ideState)
158+
fois <- readVar foisVar
159+
forM_ changes $ \(FileEvent uri c) -> do
168160
case c of
169161
FcChanged
170162
| Just f <- uriToFilePath uri
163+
, nfp <- toNormalizedFilePath f
164+
, not $ HM.member nfp fois
171165
-> do
172-
-- we record FOIs document versions in all the stored values
173-
-- so NEVER reset FOIs to avoid losing their versions
174-
OfInterestVar foisVar <- getIdeGlobalExtras (shakeExtras ideState)
175-
fois <- readVar foisVar
176-
unless (HM.member (toNormalizedFilePath f) fois) $ do
177-
deleteValue (shakeExtras ideState) (GetModificationTime_ True) (toNormalizedFilePath' f)
178-
deleteValue (shakeExtras ideState) (GetModificationTime_ False) (toNormalizedFilePath' f)
166+
deleteValue (shakeExtras ideState) (GetModificationTime_ True) nfp
167+
deleteValue (shakeExtras ideState) (GetModificationTime_ False) nfp
179168
_ -> pure ()
180169

170+
181171
-- Dir.getModificationTime is surprisingly slow since it performs
182172
-- a ton of conversions. Since we do not actually care about
183173
-- the format of the time, we can get away with something cheaper.
@@ -243,7 +233,6 @@ fileStoreRules vfs isWatched = do
243233
addIdeGlobal vfs
244234
getModificationTimeRule vfs isWatched
245235
getFileContentsRule vfs
246-
isFileOfInterestRule
247236

248237
-- | Note that some buffer for a specific file has been modified but not
249238
-- with what changes.
@@ -261,7 +250,8 @@ setFileModified state saved nfp = do
261250
VFSHandle{..} <- getIdeGlobalState state
262251
when (isJust setVirtualFileContents) $
263252
fail "setFileModified can't be called on this type of VFSHandle"
264-
shakeRestart state []
253+
recordDirtyKeys (shakeExtras state) GetModificationTime [nfp]
254+
restartShakeSession (shakeExtras state) []
265255
when checkParents $
266256
typecheckParents state nfp
267257

@@ -281,14 +271,17 @@ typecheckParentsAction nfp = do
281271
`catch` \(e :: SomeException) -> log (show e)
282272
() <$ uses GetModIface rs
283273

284-
-- | Note that some buffer somewhere has been modified, but don't say what.
274+
-- | Note that some keys have been modified and restart the session
285275
-- Only valid if the virtual file system was initialised by LSP, as that
286276
-- independently tracks which files are modified.
287-
setSomethingModified :: IdeState -> IO ()
288-
setSomethingModified state = do
277+
setSomethingModified :: IdeState -> [SomeShakeValue] -> IO ()
278+
setSomethingModified state keys = do
289279
VFSHandle{..} <- getIdeGlobalState state
290280
when (isJust setVirtualFileContents) $
291281
fail "setSomethingModified can't be called on this type of VFSHandle"
292282
-- Update database to remove any files that might have been renamed/deleted
293283
atomically $ writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) deleteMissingRealFiles
294-
void $ shakeRestart state []
284+
285+
atomicModifyIORef_ (dirtyKeys $ shakeExtras state) $ \x ->
286+
foldl' (flip HSet.insert) x keys
287+
void $ restartShakeSession (shakeExtras state) []

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)
@@ -354,8 +353,6 @@ type instance RuleResult GetModSummary = ModSummaryResult
354353
-- | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff
355354
type instance RuleResult GetModSummaryWithoutTimestamps = ModSummaryResult
356355

357-
type instance RuleResult GetFilesOfInterest = HashMap NormalizedFilePath FileOfInterestStatus
358-
359356
data GetParsedModule = GetParsedModule
360357
deriving (Eq, Show, Typeable, Generic)
361358
instance Hashable GetParsedModule
@@ -513,12 +510,6 @@ instance Hashable GhcSessionIO
513510
instance NFData GhcSessionIO
514511
instance Binary GhcSessionIO
515512

516-
data GetFilesOfInterest = GetFilesOfInterest
517-
deriving (Eq, Show, Typeable, Generic)
518-
instance Hashable GetFilesOfInterest
519-
instance NFData GetFilesOfInterest
520-
instance Binary GetFilesOfInterest
521-
522513
makeLensesWith
523514
(lensRules & lensField .~ mappingNamer (pure . (++ "L")))
524515
''Splices

0 commit comments

Comments
 (0)