Skip to content

Commit 3c24c20

Browse files
authored
Avoid race conditions with VFS and VFS versions (#2789)
* Avoid race conditions with VFS and VFS version We need to take VFS snapshots as soon as we get a change notification. Consider the following interleaving of events: 1. Change Notification A (updates LSP VFS) 2. Restart Shake Session (A changed) initiated 3. Change Notification B (updates LSP VFS) 4. Restart Shake Session (A changed) takes VFS snapshot and possibly performs more computation 5. Restart Shake Session (B changed) In particular, between step 3 and 5, we took a snapshot for a previous build, but this snapshot included changes from a newer VFS state that the build should not have seen. To fix this, we need to take snapshots as soon as a notification handler is called, before forking any threads. This works because LSP calls all handlers in a single threaded fashion and these handlers block message processing. It is essential to this on the LSP handler thread rather than the reactor thread that GHCIDE sets up in order to maintin the property. * Disable flaky test 'add missing module (non workspace)'
1 parent 2da5931 commit 3c24c20

File tree

13 files changed

+70
-51
lines changed

13 files changed

+70
-51
lines changed

exe/Main.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ main = do
4646
-- This plugin just installs a handler for the `initialized` notification, which then
4747
-- picks up the LSP environment and feeds it to our recorders
4848
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback")
49-
{ pluginNotificationHandlers = mkPluginNotificationHandler LSP.SInitialized $ \_ _ _ -> do
49+
{ pluginNotificationHandlers = mkPluginNotificationHandler LSP.SInitialized $ \_ _ _ _ -> do
5050
env <- LSP.getLspEnv
5151
liftIO $ (cb1 <> cb2) env
5252
}

ghcide/exe/Main.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ main = withTelemetryLogger $ \telemetryLogger -> do
9494
-- This plugin just installs a handler for the `initialized` notification, which then
9595
-- picks up the LSP environment and feeds it to our recorders
9696
let lspRecorderPlugin = (defaultPluginDescriptor "LSPRecorderCallback")
97-
{ pluginNotificationHandlers = mkPluginNotificationHandler LSP.SInitialized $ \_ _ _ -> do
97+
{ pluginNotificationHandlers = mkPluginNotificationHandler LSP.SInitialized $ \_ _ _ _ -> do
9898
env <- LSP.getLspEnv
9999
liftIO $ (cb1 <> cb2) env
100100
}

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

+3-1
Original file line numberDiff line numberDiff line change
@@ -581,7 +581,9 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
581581

582582
-- Invalidate all the existing GhcSession build nodes by restarting the Shake session
583583
invalidateShakeCache
584-
restartShakeSession "new component" []
584+
585+
-- The VFS doesn't change on cradle edits, re-use the old one.
586+
restartShakeSession VFSUnmodified "new component" []
585587

586588
-- Typecheck all files in the project on startup
587589
checkProject <- getCheckProject

ghcide/src/Development/IDE.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,8 @@ import Development.IDE.Core.Shake as X (FastResult (..),
4040
useWithStaleFast,
4141
useWithStaleFast',
4242
useWithStale_,
43-
use_, uses, uses_)
43+
use_, uses, uses_,
44+
VFSModified(..))
4445
import Development.IDE.GHC.Compat as X (GhcVersion (..),
4546
ghcVersion)
4647
import Development.IDE.GHC.Error as X

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

+6-5
Original file line numberDiff line numberDiff line change
@@ -223,19 +223,20 @@ fileStoreRules recorder isWatched = do
223223
-- | Note that some buffer for a specific file has been modified but not
224224
-- with what changes.
225225
setFileModified :: Recorder (WithPriority Log)
226+
-> VFSModified
226227
-> IdeState
227228
-> Bool -- ^ Was the file saved?
228229
-> NormalizedFilePath
229230
-> IO ()
230-
setFileModified recorder state saved nfp = do
231+
setFileModified recorder vfs state saved nfp = do
231232
ideOptions <- getIdeOptionsIO $ shakeExtras state
232233
doCheckParents <- optCheckParents ideOptions
233234
let checkParents = case doCheckParents of
234235
AlwaysCheck -> True
235236
CheckOnSave -> saved
236237
_ -> False
237238
join $ atomically $ recordDirtyKeys (shakeExtras state) GetModificationTime [nfp]
238-
restartShakeSession (shakeExtras state) (fromNormalizedFilePath nfp ++ " (modified)") []
239+
restartShakeSession (shakeExtras state) vfs (fromNormalizedFilePath nfp ++ " (modified)") []
239240
when checkParents $
240241
typecheckParents recorder state nfp
241242

@@ -256,14 +257,14 @@ typecheckParentsAction recorder nfp = do
256257
-- | Note that some keys have been modified and restart the session
257258
-- Only valid if the virtual file system was initialised by LSP, as that
258259
-- independently tracks which files are modified.
259-
setSomethingModified :: IdeState -> [Key] -> String -> IO ()
260-
setSomethingModified state keys reason = do
260+
setSomethingModified :: VFSModified -> IdeState -> [Key] -> String -> IO ()
261+
setSomethingModified vfs state keys reason = do
261262
-- Update database to remove any files that might have been renamed/deleted
262263
atomically $ do
263264
writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) (\withHieDb -> withHieDb deleteMissingRealFiles)
264265
modifyTVar' (dirtyKeys $ shakeExtras state) $ \x ->
265266
foldl' (flip HSet.insert) x keys
266-
void $ restartShakeSession (shakeExtras state) reason []
267+
void $ restartShakeSession (shakeExtras state) vfs reason []
267268

268269
registerFileWatches :: [String] -> LSP.LspT Config IO Bool
269270
registerFileWatches globs = do

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -558,7 +558,7 @@ getHieAstsRule recorder =
558558
persistentHieFileRule :: Recorder (WithPriority Log) -> Rules ()
559559
persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybeT $ do
560560
res <- readHieFileForSrcFromDisk recorder file
561-
vfsRef <- asks vfs
561+
vfsRef <- asks vfsVar
562562
vfsData <- liftIO $ vfsMap <$> readTVarIO vfsRef
563563
(currentSource, ver) <- liftIO $ case M.lookup (filePathToUri' file) vfsData of
564564
Nothing -> (,Nothing) . T.decodeUtf8 <$> BS.readFile (fromNormalizedFilePath file)

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

+21-11
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,8 @@ module Development.IDE.Core.Shake(
7575
addPersistentRule,
7676
garbageCollectDirtyKeys,
7777
garbageCollectDirtyKeysOlderThan,
78-
Log(..)
78+
Log(..),
79+
VFSModified(..)
7980
) where
8081

8182
import Control.Concurrent.Async
@@ -253,7 +254,8 @@ data ShakeExtras = ShakeExtras
253254
,ideTesting :: IdeTesting
254255
-- ^ Whether to enable additional lsp messages used by the test suite for checking invariants
255256
,restartShakeSession
256-
:: String
257+
:: VFSModified
258+
-> String
257259
-> [DelayedAction ()]
258260
-> IO ()
259261
,ideNc :: IORef NameCache
@@ -269,7 +271,7 @@ data ShakeExtras = ShakeExtras
269271
, persistentKeys :: TVar (HMap.HashMap Key GetStalePersistent)
270272
-- ^ Registery for functions that compute/get "stale" results for the rule
271273
-- (possibly from disk)
272-
, vfs :: TVar VFS
274+
, vfsVar :: TVar VFS
273275
-- ^ A snapshot of the current state of the virtual file system. Updated on shakeRestart
274276
-- VFS state is managed by LSP. However, the state according to the lsp library may be newer than the state of the current session,
275277
-- leaving us vulnerable to suble race conditions. To avoid this, we take a snapshot of the state of the VFS on every
@@ -318,7 +320,7 @@ class Typeable a => IsIdeGlobal a where
318320
-- | Read a virtual file from the current snapshot
319321
getVirtualFile :: NormalizedFilePath -> Action (Maybe VirtualFile)
320322
getVirtualFile nf = do
321-
vfs <- fmap vfsMap . liftIO . readTVarIO . vfs =<< getShakeExtras
323+
vfs <- fmap vfsMap . liftIO . readTVarIO . vfsVar =<< getShakeExtras
322324
pure $! Map.lookup (filePathToUri' nf) vfs -- Don't leak a reference to the entire map
323325

324326
-- Take a snapshot of the current LSP VFS
@@ -598,7 +600,7 @@ shakeOpen recorder lspEnv defaultConfig logger debouncer
598600

599601
dirtyKeys <- newTVarIO mempty
600602
-- Take one VFS snapshot at the start
601-
vfs <- newTVarIO =<< vfsSnapshot lspEnv
603+
vfsVar <- newTVarIO =<< vfsSnapshot lspEnv
602604
pure ShakeExtras{..}
603605
shakeDb <-
604606
shakeNewDatabase
@@ -640,7 +642,10 @@ startTelemetry db extras@ShakeExtras{..}
640642
-- | Must be called in the 'Initialized' handler and only once
641643
shakeSessionInit :: Recorder (WithPriority Log) -> IdeState -> IO ()
642644
shakeSessionInit recorder ide@IdeState{..} = do
643-
initSession <- newSession recorder shakeExtras shakeDb [] "shakeSessionInit"
645+
-- Take a snapshot of the VFS - it should be empty as we've recieved no notifications
646+
-- till now, but it can't hurt to be in sync with the `lsp` library.
647+
vfs <- vfsSnapshot (lspEnv shakeExtras)
648+
initSession <- newSession recorder shakeExtras (VFSModified vfs) shakeDb [] "shakeSessionInit"
644649
putMVar shakeSession initSession
645650
logDebug (ideLogger ide) "Shake session initialized"
646651

@@ -679,8 +684,8 @@ delayedAction a = do
679684
-- | Restart the current 'ShakeSession' with the given system actions.
680685
-- Any actions running in the current session will be aborted,
681686
-- but actions added via 'shakeEnqueue' will be requeued.
682-
shakeRestart :: Recorder (WithPriority Log) -> IdeState -> String -> [DelayedAction ()] -> IO ()
683-
shakeRestart recorder IdeState{..} reason acts =
687+
shakeRestart :: Recorder (WithPriority Log) -> IdeState -> VFSModified -> String -> [DelayedAction ()] -> IO ()
688+
shakeRestart recorder IdeState{..} vfs reason acts =
684689
withMVar'
685690
shakeSession
686691
(\runner -> do
@@ -707,7 +712,7 @@ shakeRestart recorder IdeState{..} reason acts =
707712
-- between spawning the new thread and updating shakeSession.
708713
-- See https://github.com/haskell/ghcide/issues/79
709714
(\() -> do
710-
(,()) <$> newSession recorder shakeExtras shakeDb acts reason)
715+
(,()) <$> newSession recorder shakeExtras vfs shakeDb acts reason)
711716
where
712717
logErrorAfter :: Seconds -> Recorder (WithPriority Log) -> IO () -> IO ()
713718
logErrorAfter seconds recorder action = flip withAsync (const action) $ do
@@ -743,19 +748,24 @@ shakeEnqueue ShakeExtras{actionQueue, logger} act = do
743748
]
744749
return (wait' b >>= either throwIO return)
745750

751+
data VFSModified = VFSUnmodified | VFSModified !VFS
752+
746753
-- | Set up a new 'ShakeSession' with a set of initial actions
747754
-- Will crash if there is an existing 'ShakeSession' running.
748755
newSession
749756
:: Recorder (WithPriority Log)
750757
-> ShakeExtras
758+
-> VFSModified
751759
-> ShakeDatabase
752760
-> [DelayedActionInternal]
753761
-> String
754762
-> IO ShakeSession
755-
newSession recorder extras@ShakeExtras{..} shakeDb acts reason = do
763+
newSession recorder extras@ShakeExtras{..} vfsMod shakeDb acts reason = do
756764

757765
-- Take a new VFS snapshot
758-
atomically . writeTVar vfs =<< vfsSnapshot lspEnv
766+
case vfsMod of
767+
VFSUnmodified -> pure ()
768+
VFSModified vfs -> atomically $ writeTVar vfsVar vfs
759769

760770
IdeOptions{optRunSubset} <- getIdeOptionsIO extras
761771
reenqueued <- atomicallyNamed "actionQueue - peek" $ peekInProgress actionQueue

ghcide/src/Development/IDE/LSP/Notifications.hs

+14-14
Original file line numberDiff line numberDiff line change
@@ -55,41 +55,41 @@ whenUriFile uri act = whenJust (LSP.uriToFilePath uri) $ act . toNormalizedFileP
5555
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
5656
descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers = mconcat
5757
[ mkPluginNotificationHandler LSP.STextDocumentDidOpen $
58-
\ide _ (DidOpenTextDocumentParams TextDocumentItem{_uri,_version}) -> liftIO $ do
58+
\ide vfs _ (DidOpenTextDocumentParams TextDocumentItem{_uri,_version}) -> liftIO $ do
5959
atomically $ updatePositionMapping ide (VersionedTextDocumentIdentifier _uri (Just _version)) (List [])
6060
whenUriFile _uri $ \file -> do
6161
-- We don't know if the file actually exists, or if the contents match those on disk
6262
-- For example, vscode restores previously unsaved contents on open
6363
addFileOfInterest ide file Modified{firstOpen=True}
64-
setFileModified (cmapWithPrio LogFileStore recorder) ide False file
64+
setFileModified (cmapWithPrio LogFileStore recorder) (VFSModified vfs) ide False file
6565
logDebug (ideLogger ide) $ "Opened text document: " <> getUri _uri
6666

6767
, mkPluginNotificationHandler LSP.STextDocumentDidChange $
68-
\ide _ (DidChangeTextDocumentParams identifier@VersionedTextDocumentIdentifier{_uri} changes) -> liftIO $ do
68+
\ide vfs _ (DidChangeTextDocumentParams identifier@VersionedTextDocumentIdentifier{_uri} changes) -> liftIO $ do
6969
atomically $ updatePositionMapping ide identifier changes
7070
whenUriFile _uri $ \file -> do
7171
addFileOfInterest ide file Modified{firstOpen=False}
72-
setFileModified (cmapWithPrio LogFileStore recorder) ide False file
72+
setFileModified (cmapWithPrio LogFileStore recorder) (VFSModified vfs) ide False file
7373
logDebug (ideLogger ide) $ "Modified text document: " <> getUri _uri
7474

7575
, mkPluginNotificationHandler LSP.STextDocumentDidSave $
76-
\ide _ (DidSaveTextDocumentParams TextDocumentIdentifier{_uri} _) -> liftIO $ do
76+
\ide vfs _ (DidSaveTextDocumentParams TextDocumentIdentifier{_uri} _) -> liftIO $ do
7777
whenUriFile _uri $ \file -> do
7878
addFileOfInterest ide file OnDisk
79-
setFileModified (cmapWithPrio LogFileStore recorder) ide True file
79+
setFileModified (cmapWithPrio LogFileStore recorder) (VFSModified vfs) ide True file
8080
logDebug (ideLogger ide) $ "Saved text document: " <> getUri _uri
8181

8282
, mkPluginNotificationHandler LSP.STextDocumentDidClose $
83-
\ide _ (DidCloseTextDocumentParams TextDocumentIdentifier{_uri}) -> liftIO $ do
83+
\ide vfs _ (DidCloseTextDocumentParams TextDocumentIdentifier{_uri}) -> liftIO $ do
8484
whenUriFile _uri $ \file -> do
8585
deleteFileOfInterest ide file
8686
let msg = "Closed text document: " <> getUri _uri
8787
scheduleGarbageCollection ide
88-
setSomethingModified ide [] $ Text.unpack msg
88+
setSomethingModified (VFSModified vfs) ide [] $ Text.unpack msg
8989
logDebug (ideLogger ide) msg
9090

9191
, mkPluginNotificationHandler LSP.SWorkspaceDidChangeWatchedFiles $
92-
\ide _ (DidChangeWatchedFilesParams (List fileEvents)) -> liftIO $ do
92+
\ide vfs _ (DidChangeWatchedFilesParams (List fileEvents)) -> liftIO $ do
9393
-- See Note [File existence cache and LSP file watchers] which explains why we get these notifications and
9494
-- what we do with them
9595
-- filter out files of interest, since we already know all about those
@@ -106,24 +106,24 @@ descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHa
106106
logDebug (ideLogger ide) $ "Watched file events: " <> Text.pack msg
107107
modifyFileExists ide fileEvents'
108108
resetFileStore ide fileEvents'
109-
setSomethingModified ide [] msg
109+
setSomethingModified (VFSModified vfs) ide [] msg
110110

111111
, mkPluginNotificationHandler LSP.SWorkspaceDidChangeWorkspaceFolders $
112-
\ide _ (DidChangeWorkspaceFoldersParams events) -> liftIO $ do
112+
\ide _ _ (DidChangeWorkspaceFoldersParams events) -> liftIO $ do
113113
let add = S.union
114114
substract = flip S.difference
115115
modifyWorkspaceFolders ide
116116
$ add (foldMap (S.singleton . parseWorkspaceFolder) (_added events))
117117
. substract (foldMap (S.singleton . parseWorkspaceFolder) (_removed events))
118118

119119
, mkPluginNotificationHandler LSP.SWorkspaceDidChangeConfiguration $
120-
\ide _ (DidChangeConfigurationParams cfg) -> liftIO $ do
120+
\ide vfs _ (DidChangeConfigurationParams cfg) -> liftIO $ do
121121
let msg = Text.pack $ show cfg
122122
logDebug (ideLogger ide) $ "Configuration changed: " <> msg
123123
modifyClientSettings ide (const $ Just cfg)
124-
setSomethingModified ide [toKey GetClientSettings emptyFilePath] "config change"
124+
setSomethingModified (VFSModified vfs) ide [toKey GetClientSettings emptyFilePath] "config change"
125125

126-
, mkPluginNotificationHandler LSP.SInitialized $ \ide _ _ -> do
126+
, mkPluginNotificationHandler LSP.SInitialized $ \ide _ _ _ -> do
127127
--------- Initialize Shake session --------------------------------------------------------------------
128128
liftIO $ shakeSessionInit (cmapWithPrio LogShake recorder) ide
129129

ghcide/src/Development/IDE/LSP/Server.hs

+7-4
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ import Ide.Types (HasTracing, traceWithSpan)
2222
import Language.LSP.Server (Handlers, LspM)
2323
import qualified Language.LSP.Server as LSP
2424
import Language.LSP.Types
25+
import Language.LSP.VFS
2526
import UnliftIO.Chan
2627

2728
data ReactorMessage
@@ -48,14 +49,16 @@ requestHandler m k = LSP.requestHandler m $ \RequestMessage{_method,_id,_params}
4849
notificationHandler
4950
:: forall (m :: Method FromClient Notification) c. (HasTracing (MessageParams m)) =>
5051
SMethod m
51-
-> (IdeState -> MessageParams m -> LspM c ())
52+
-> (IdeState -> VFS -> MessageParams m -> LspM c ())
5253
-> Handlers (ServerM c)
5354
notificationHandler m k = LSP.notificationHandler m $ \NotificationMessage{_params,_method}-> do
5455
(chan,ide) <- ask
5556
env <- LSP.getLspEnv
57+
-- Take a snapshot of the VFS state on every notification
58+
-- We only need to do this here because the VFS state is only updated
59+
-- on notifications
60+
vfs <- LSP.getVirtualFiles
5661
let trace x = otTracedHandler "Notification" (show _method) $ \sp -> do
5762
traceWithSpan sp _params
5863
x
59-
writeChan chan $ ReactorNotification (trace $ LSP.runLspT env $ k ide _params)
60-
61-
64+
writeChan chan $ ReactorNotification (trace $ LSP.runLspT env $ k ide vfs _params)

ghcide/src/Development/IDE/Plugin/HLS.hs

+4-3
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ import Ide.Plugin.Config
3333
import Ide.PluginUtils (getClientConfig)
3434
import Ide.Types as HLS
3535
import qualified Language.LSP.Server as LSP
36+
import Language.LSP.VFS
3637
import Language.LSP.Types
3738
import qualified Language.LSP.Types as J
3839
import Text.Regex.TDFA.Text ()
@@ -190,7 +191,7 @@ extensibleNotificationPlugins recorder xs = mempty { P.pluginHandlers = handlers
190191
hs
191192
handlers = mconcat $ do
192193
(IdeNotification m :=> IdeNotificationHandler fs') <- DMap.assocs handlers'
193-
pure $ notificationHandler m $ \ide params -> do
194+
pure $ notificationHandler m $ \ide vfs params -> do
194195
config <- Ide.PluginUtils.getClientConfig
195196
let fs = filter (\(pid,_) -> plcGlobalOn $ configForPlugin config pid) fs'
196197
case nonEmpty fs of
@@ -200,7 +201,7 @@ extensibleNotificationPlugins recorder xs = mempty { P.pluginHandlers = handlers
200201
Just fs -> do
201202
-- We run the notifications in order, so the core ghcide provider
202203
-- (which restarts the shake process) hopefully comes last
203-
mapM_ (\(pid,f) -> otTracedProvider pid (fromString $ show m) $ f ide params) fs
204+
mapM_ (\(pid,f) -> otTracedProvider pid (fromString $ show m) $ f ide vfs params) fs
204205

205206
-- ---------------------------------------------------------------------
206207

@@ -226,7 +227,7 @@ newtype IdeHandler (m :: J.Method FromClient Request)
226227

227228
-- | Combine the 'PluginHandler' for all plugins
228229
newtype IdeNotificationHandler (m :: J.Method FromClient Notification)
229-
= IdeNotificationHandler [(PluginId, IdeState -> MessageParams m -> LSP.LspM Config ())]
230+
= IdeNotificationHandler [(PluginId, IdeState -> VFS -> MessageParams m -> LSP.LspM Config ())]
230231
-- type NotificationHandler (m :: Method FromClient Notification) = MessageParams m -> IO ()`
231232

232233
-- | Combine the 'PluginHandlers' for all plugins

ghcide/test/exe/Main.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -421,7 +421,7 @@ diagnosticTests = testGroup "diagnostics"
421421
let contentA = T.unlines [ "module ModuleA where" ]
422422
_ <- createDoc "ModuleA.hs" "haskell" contentA
423423
expectDiagnostics [("ModuleB.hs", [])]
424-
, ignoreInWindowsBecause "Broken in windows" $ testSessionWait "add missing module (non workspace)" $ do
424+
, ignoreTestBecause "Flaky #2831" $ testSessionWait "add missing module (non workspace)" $ do
425425
-- need to canonicalize in Mac Os
426426
tmpDir <- liftIO $ canonicalizePath =<< getTemporaryDirectory
427427
let contentB = T.unlines
@@ -6417,7 +6417,7 @@ unitTests recorder logger = do
64176417
let plugins = pluginDescToIdePlugins $
64186418
[ (defaultPluginDescriptor $ fromString $ show i)
64196419
{ pluginNotificationHandlers = mconcat
6420-
[ mkPluginNotificationHandler LSP.STextDocumentDidOpen $ \_ _ _ ->
6420+
[ mkPluginNotificationHandler LSP.STextDocumentDidOpen $ \_ _ _ _ ->
64216421
liftIO $ atomicModifyIORef_ orderRef (i:)
64226422
]
64236423
}

0 commit comments

Comments
 (0)