Skip to content

Commit 84ece63

Browse files
authored
Lockless diagnostics (#2434)
* lock-less publishedDiagnostics * lock-less diagnostics * move deleteValue and recordDirtyKeys to STM * Move getDiagnostics to STM * fix plugins * Do not send stderr output to a file in func-tests Stderr output is very useful to diagnose test failures when interleaved with the LSP log. Sending it to a file disrupts this interleaving and makes it harder to retrieve from CI
1 parent 53eb7da commit 84ece63

File tree

14 files changed

+75
-64
lines changed

14 files changed

+75
-64
lines changed

Diff for: ghcide/session-loader/Development/IDE/Session.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -247,7 +247,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
247247
} <- getShakeExtras
248248
let invalidateShakeCache = do
249249
void $ modifyVar' version succ
250-
recordDirtyKeys extras GhcSessionIO [emptyFilePath]
250+
atomically $ recordDirtyKeys extras GhcSessionIO [emptyFilePath]
251251

252252
IdeOptions{ optTesting = IdeTesting optTesting
253253
, optCheckProject = getCheckProject
@@ -264,7 +264,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
264264
TargetModule _ -> do
265265
found <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
266266
return (targetTarget, found)
267-
recordDirtyKeys extras GetKnownTargets [emptyFilePath]
267+
atomically $ recordDirtyKeys extras GetKnownTargets [emptyFilePath]
268268
modifyVarIO' knownTargetsVar $ traverseHashed $ \known -> do
269269
let known' = HM.unionWith (<>) known $ HM.fromList $ map (second Set.fromList) knownTargets
270270
when (known /= known') $

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

+6-3
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Development.IDE.Core.FileExists
1010
)
1111
where
1212

13+
import Control.Concurrent.STM.Stats
1314
import Control.Concurrent.Strict
1415
import Control.Exception
1516
import Control.Monad.Extra
@@ -100,9 +101,11 @@ modifyFileExists state changes = do
100101
-- flush previous values
101102
let (fileModifChanges, fileExistChanges) =
102103
partition ((== FcChanged) . snd) (HashMap.toList changesMap)
103-
mapM_ (deleteValue (shakeExtras state) GetFileExists . fst) fileExistChanges
104-
recordDirtyKeys (shakeExtras state) GetFileExists $ map fst fileExistChanges
105-
recordDirtyKeys (shakeExtras state) GetModificationTime $ map fst fileModifChanges
104+
join $ atomically $ do
105+
mapM_ (deleteValue (shakeExtras state) GetFileExists . fst) fileExistChanges
106+
io1 <- recordDirtyKeys (shakeExtras state) GetFileExists $ map fst fileExistChanges
107+
io2 <- recordDirtyKeys (shakeExtras state) GetModificationTime $ map fst fileModifChanges
108+
return (io1 <> io2)
106109

107110
fromChange :: FileChangeType -> Maybe Bool
108111
fromChange FcCreated = Just True

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

+5-4
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ module Development.IDE.Core.FileStore(
2424
registerFileWatches
2525
) where
2626

27-
import Control.Concurrent.STM (atomically,
27+
import Control.Concurrent.STM.Stats (STM, atomically,
2828
modifyTVar')
2929
import Control.Concurrent.STM.TQueue (writeTQueue)
3030
import Control.Concurrent.Strict
@@ -160,7 +160,7 @@ isInterface :: NormalizedFilePath -> Bool
160160
isInterface f = takeExtension (fromNormalizedFilePath f) `elem` [".hi", ".hi-boot"]
161161

162162
-- | Reset the GetModificationTime state of interface files
163-
resetInterfaceStore :: ShakeExtras -> NormalizedFilePath -> IO ()
163+
resetInterfaceStore :: ShakeExtras -> NormalizedFilePath -> STM ()
164164
resetInterfaceStore state f = do
165165
deleteValue state GetModificationTime f
166166

@@ -175,7 +175,8 @@ resetFileStore ideState changes = mask $ \_ -> do
175175
case c of
176176
FcChanged
177177
-- already checked elsewhere | not $ HM.member nfp fois
178-
-> deleteValue (shakeExtras ideState) GetModificationTime nfp
178+
-> atomically $
179+
deleteValue (shakeExtras ideState) GetModificationTime nfp
179180
_ -> pure ()
180181

181182

@@ -262,7 +263,7 @@ setFileModified state saved nfp = do
262263
VFSHandle{..} <- getIdeGlobalState state
263264
when (isJust setVirtualFileContents) $
264265
fail "setFileModified can't be called on this type of VFSHandle"
265-
recordDirtyKeys (shakeExtras state) GetModificationTime [nfp]
266+
atomically $ recordDirtyKeys (shakeExtras state) GetModificationTime [nfp]
266267
restartShakeSession (shakeExtras state) (fromNormalizedFilePath nfp ++ " (modified)") []
267268
when checkParents $
268269
typecheckParents state nfp

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

+3-2
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ import qualified Data.HashMap.Strict as HashMap
2525
import qualified Data.Text as T
2626
import Development.IDE.Graph
2727

28+
import Control.Concurrent.STM.Stats (atomically)
2829
import qualified Data.ByteString as BS
2930
import Data.Maybe (catMaybes)
3031
import Development.IDE.Core.ProgressReporting
@@ -86,15 +87,15 @@ addFileOfInterest state f v = do
8687
let (prev, new) = HashMap.alterF (, Just v) f dict
8788
pure (new, (prev, new))
8889
when (prev /= Just v) $
89-
recordDirtyKeys (shakeExtras state) IsFileOfInterest [f]
90+
join $ atomically $ recordDirtyKeys (shakeExtras state) IsFileOfInterest [f]
9091
logDebug (ideLogger state) $
9192
"Set files of interest to: " <> T.pack (show files)
9293

9394
deleteFileOfInterest :: IdeState -> NormalizedFilePath -> IO ()
9495
deleteFileOfInterest state f = do
9596
OfInterestVar var <- getIdeGlobalState state
9697
files <- modifyVar' var $ HashMap.delete f
97-
recordDirtyKeys (shakeExtras state) IsFileOfInterest [f]
98+
join $ atomically $ recordDirtyKeys (shakeExtras state) IsFileOfInterest [f]
9899
logDebug (ideLogger state) $ "Set files of interest to: " <> T.pack (show files)
99100

100101
scheduleGarbageCollection :: IdeState -> IO ()

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

+2-1
Original file line numberDiff line numberDiff line change
@@ -148,6 +148,7 @@ import Ide.Plugin.Properties (HasProperty,
148148
import Ide.PluginUtils (configForPlugin)
149149
import Ide.Types (DynFlagsModifications (dynFlagsModifyGlobal, dynFlagsModifyParser),
150150
PluginId)
151+
import Control.Concurrent.STM.Stats (atomically)
151152

152153
-- | This is useful for rules to convert rules that can only produce errors or
153154
-- a result into the more general IdeResult type that supports producing
@@ -1061,7 +1062,7 @@ writeHiFileAction hsc hiFile = do
10611062
extras <- getShakeExtras
10621063
let targetPath = Compat.ml_hi_file $ ms_location $ hirModSummary hiFile
10631064
liftIO $ do
1064-
resetInterfaceStore extras $ toNormalizedFilePath' targetPath
1065+
atomically $ resetInterfaceStore extras $ toNormalizedFilePath' targetPath
10651066
writeHiFile hsc hiFile
10661067

10671068
data RulesConfig = RulesConfig

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

+41-43
Original file line numberDiff line numberDiff line change
@@ -191,9 +191,9 @@ data ShakeExtras = ShakeExtras
191191
,logger :: Logger
192192
,globals :: Var (HMap.HashMap TypeRep Dynamic)
193193
,state :: Values
194-
,diagnostics :: Var DiagnosticStore
195-
,hiddenDiagnostics :: Var DiagnosticStore
196-
,publishedDiagnostics :: Var (HMap.HashMap NormalizedUri [Diagnostic])
194+
,diagnostics :: STMDiagnosticStore
195+
,hiddenDiagnostics :: STMDiagnosticStore
196+
,publishedDiagnostics :: STM.Map NormalizedUri [Diagnostic]
197197
-- ^ This represents the set of diagnostics that we have published.
198198
-- Due to debouncing not every change might get published.
199199
,positionMapping :: Var (HMap.HashMap NormalizedUri (Map TextDocumentVersion (PositionDelta, PositionMapping)))
@@ -437,8 +437,8 @@ deleteValue
437437
=> ShakeExtras
438438
-> k
439439
-> NormalizedFilePath
440-
-> IO ()
441-
deleteValue ShakeExtras{dirtyKeys, state} key file = atomically $ do
440+
-> STM ()
441+
deleteValue ShakeExtras{dirtyKeys, state} key file = do
442442
STM.delete (toKey key file) state
443443
modifyTVar' dirtyKeys $ HSet.insert (toKey key file)
444444

@@ -447,10 +447,11 @@ recordDirtyKeys
447447
=> ShakeExtras
448448
-> k
449449
-> [NormalizedFilePath]
450-
-> IO ()
451-
recordDirtyKeys ShakeExtras{dirtyKeys} key file = withEventTrace "recordDirtyKeys" $ \addEvent -> do
452-
atomically $ modifyTVar' dirtyKeys $ \x -> foldl' (flip HSet.insert) x (toKey key <$> file)
453-
addEvent (fromString $ "dirty " <> show key) (fromString $ unlines $ map fromNormalizedFilePath file)
450+
-> STM (IO ())
451+
recordDirtyKeys ShakeExtras{dirtyKeys} key file = do
452+
modifyTVar' dirtyKeys $ \x -> foldl' (flip HSet.insert) x (toKey key <$> file)
453+
return $ withEventTrace "recordDirtyKeys" $ \addEvent -> do
454+
addEvent (fromString $ "dirty " <> show key) (fromString $ unlines $ map fromNormalizedFilePath file)
454455

455456

456457
-- | We return Nothing if the rule has not run and Just Failed if it has failed to produce a value.
@@ -509,9 +510,9 @@ shakeOpen lspEnv defaultConfig logger debouncer
509510
shakeExtras <- do
510511
globals <- newVar HMap.empty
511512
state <- STM.newIO
512-
diagnostics <- newVar mempty
513-
hiddenDiagnostics <- newVar mempty
514-
publishedDiagnostics <- newVar mempty
513+
diagnostics <- STM.newIO
514+
hiddenDiagnostics <- STM.newIO
515+
publishedDiagnostics <- STM.newIO
515516
positionMapping <- newVar HMap.empty
516517
knownTargetsVar <- newVar $ hashed HMap.empty
517518
let restartShakeSession = shakeRestart ideState
@@ -756,15 +757,13 @@ instantiateDelayedAction (DelayedAction _ s p a) = do
756757
d' = DelayedAction (Just u) s p a'
757758
return (b, d')
758759

759-
getDiagnostics :: IdeState -> IO [FileDiagnostic]
760+
getDiagnostics :: IdeState -> STM [FileDiagnostic]
760761
getDiagnostics IdeState{shakeExtras = ShakeExtras{diagnostics}} = do
761-
val <- readVar diagnostics
762-
return $ getAllDiagnostics val
762+
getAllDiagnostics diagnostics
763763

764-
getHiddenDiagnostics :: IdeState -> IO [FileDiagnostic]
764+
getHiddenDiagnostics :: IdeState -> STM [FileDiagnostic]
765765
getHiddenDiagnostics IdeState{shakeExtras = ShakeExtras{hiddenDiagnostics}} = do
766-
val <- readVar hiddenDiagnostics
767-
return $ getAllDiagnostics val
766+
getAllDiagnostics hiddenDiagnostics
768767

769768
-- | Find and release old keys from the state Hashmap
770769
-- For the record, there are other state sources that this process does not release:
@@ -1154,30 +1153,26 @@ updateFileDiagnostics fp k ShakeExtras{logger, diagnostics, hiddenDiagnostics, p
11541153
let (currentShown, currentHidden) = partition ((== ShowDiag) . fst) current
11551154
uri = filePathToUri' fp
11561155
ver = vfsVersion =<< modTime
1157-
update new store =
1158-
let store' = setStageDiagnostics uri ver (T.pack $ show k) new store
1159-
new' = getUriDiagnostics uri store'
1160-
in (store', new')
1156+
update new store = setStageDiagnostics uri ver (T.pack $ show k) new store
11611157
mask_ $ do
11621158
-- Mask async exceptions to ensure that updated diagnostics are always
11631159
-- published. Otherwise, we might never publish certain diagnostics if
11641160
-- an exception strikes between modifyVar but before
11651161
-- publishDiagnosticsNotification.
1166-
newDiags <- modifyVar diagnostics $ pure . update (map snd currentShown)
1167-
_ <- modifyVar hiddenDiagnostics $ pure . update (map snd currentHidden)
1162+
newDiags <- liftIO $ atomically $ update (map snd currentShown) diagnostics
1163+
_ <- liftIO $ atomically $ update (map snd currentHidden) hiddenDiagnostics
11681164
let uri = filePathToUri' fp
11691165
let delay = if null newDiags then 0.1 else 0
11701166
registerEvent debouncer delay uri $ do
1171-
join $ mask_ $ modifyVar publishedDiagnostics $ \published -> do
1172-
let lastPublish = HMap.lookupDefault [] uri published
1173-
!published' = HMap.insert uri newDiags published
1174-
action = when (lastPublish /= newDiags) $ case lspEnv of
1167+
join $ mask_ $ do
1168+
lastPublish <- atomically $ STM.focus (Focus.lookupWithDefault [] <* Focus.insert newDiags) uri publishedDiagnostics
1169+
let action = when (lastPublish /= newDiags) $ case lspEnv of
11751170
Nothing -> -- Print an LSP event.
11761171
logInfo logger $ showDiagnosticsColored $ map (fp,ShowDiag,) newDiags
11771172
Just env -> LSP.runLspT env $
11781173
LSP.sendNotification LSP.STextDocumentPublishDiagnostics $
11791174
LSP.PublishDiagnosticsParams (fromNormalizedUri uri) ver (List newDiags)
1180-
return (published', action)
1175+
return action
11811176

11821177
newtype Priority = Priority Double
11831178

@@ -1192,10 +1187,21 @@ actionLogger = do
11921187
ShakeExtras{logger} <- getShakeExtras
11931188
return logger
11941189

1190+
--------------------------------------------------------------------------------
1191+
type STMDiagnosticStore = STM.Map NormalizedUri StoreItem
11951192

11961193
getDiagnosticsFromStore :: StoreItem -> [Diagnostic]
11971194
getDiagnosticsFromStore (StoreItem _ diags) = concatMap SL.fromSortedList $ Map.elems diags
11981195

1196+
updateSTMDiagnostics :: STMDiagnosticStore
1197+
-> NormalizedUri -> TextDocumentVersion -> DiagnosticsBySource
1198+
-> STM [LSP.Diagnostic]
1199+
updateSTMDiagnostics store uri mv newDiagsBySource =
1200+
getDiagnosticsFromStore . fromJust <$> STM.focus (Focus.alter update *> Focus.lookup) uri store
1201+
where
1202+
update (Just(StoreItem mvs dbs))
1203+
| mvs == mv = Just (StoreItem mv (newDiagsBySource <> dbs))
1204+
update _ = Just (StoreItem mv newDiagsBySource)
11991205

12001206
-- | Sets the diagnostics for a file and compilation step
12011207
-- if you want to clear the diagnostics call this with an empty list
@@ -1204,25 +1210,17 @@ setStageDiagnostics
12041210
-> TextDocumentVersion -- ^ the time that the file these diagnostics originate from was last edited
12051211
-> T.Text
12061212
-> [LSP.Diagnostic]
1207-
-> DiagnosticStore
1208-
-> DiagnosticStore
1209-
setStageDiagnostics uri ver stage diags ds = updateDiagnostics ds uri ver updatedDiags
1213+
-> STMDiagnosticStore
1214+
-> STM [LSP.Diagnostic]
1215+
setStageDiagnostics uri ver stage diags ds = updateSTMDiagnostics ds uri ver updatedDiags
12101216
where
12111217
updatedDiags = Map.singleton (Just stage) (SL.toSortedList diags)
12121218

12131219
getAllDiagnostics ::
1214-
DiagnosticStore ->
1215-
[FileDiagnostic]
1220+
STMDiagnosticStore ->
1221+
STM [FileDiagnostic]
12161222
getAllDiagnostics =
1217-
concatMap (\(k,v) -> map (fromUri k,ShowDiag,) $ getDiagnosticsFromStore v) . HMap.toList
1218-
1219-
getUriDiagnostics ::
1220-
NormalizedUri ->
1221-
DiagnosticStore ->
1222-
[LSP.Diagnostic]
1223-
getUriDiagnostics uri ds =
1224-
maybe [] getDiagnosticsFromStore $
1225-
HMap.lookup uri ds
1223+
fmap (concatMap (\(k,v) -> map (fromUri k,ShowDiag,) $ getDiagnosticsFromStore v)) . ListT.toList . STM.listT
12261224

12271225
updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> List TextDocumentContentChangeEvent -> IO ()
12281226
updatePositionMapping IdeState{shakeExtras = ShakeExtras{positionMapping}} VersionedTextDocumentIdentifier{..} (List changes) = do

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

+2-1
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ module Development.IDE.Plugin.CodeAction
2121
import Control.Applicative ((<|>))
2222
import Control.Arrow (second,
2323
(>>>))
24+
import Control.Concurrent.STM.Stats (atomically)
2425
import Control.Monad (guard, join)
2526
import Control.Monad.IO.Class
2627
import Data.Char
@@ -90,7 +91,7 @@ codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range Cod
9091
liftIO $ do
9192
let text = Rope.toText . (_text :: VirtualFile -> Rope.Rope) <$> contents
9293
mbFile = toNormalizedFilePath' <$> uriToFilePath uri
93-
diag <- fmap (\(_, _, d) -> d) . filter (\(p, _, _) -> mbFile == Just p) <$> getDiagnostics state
94+
diag <- atomically $ fmap (\(_, _, d) -> d) . filter (\(p, _, _) -> mbFile == Just p) <$> getDiagnostics state
9495
(join -> parsedModule) <- runAction "GhcideCodeActions.getParsedModule" state $ getParsedModule `traverse` mbFile
9596
let
9697
actions = caRemoveRedundantImports parsedModule text diag xs uri

Diff for: ghcide/src/Development/IDE/Plugin/TypeLenses.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Development.IDE.Plugin.TypeLenses (
1212
GlobalBindingTypeSigsResult (..),
1313
) where
1414

15+
import Control.Concurrent.STM.Stats (atomically)
1516
import Control.DeepSeq (rwhnf)
1617
import Control.Monad (mzero)
1718
import Control.Monad.Extra (whenMaybe)
@@ -100,8 +101,8 @@ codeLensProvider ideState pId CodeLensParams{_textDocument = TextDocumentIdentif
100101
bindings <- runAction "codeLens.GetBindings" ideState (use GetBindings filePath)
101102
gblSigs <- runAction "codeLens.GetGlobalBindingTypeSigs" ideState (use GetGlobalBindingTypeSigs filePath)
102103

103-
diag <- getDiagnostics ideState
104-
hDiag <- getHiddenDiagnostics ideState
104+
diag <- atomically $ getDiagnostics ideState
105+
hDiag <- atomically $ getHiddenDiagnostics ideState
105106

106107
let toWorkSpaceEdit tedit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing Nothing
107108
generateLensForGlobal sig@GlobalBindingTypeSig{..} = do

Diff for: haskell-language-server.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -368,6 +368,7 @@ executable haskell-language-server
368368
, safe-exceptions
369369
, hls-graph
370370
, sqlite-simple
371+
, stm
371372
, temporary
372373
, transformers
373374
, unordered-containers

Diff for: plugins/default/src/Ide/Plugin/Example.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Ide.Plugin.Example
1414
descriptor
1515
) where
1616

17+
import Control.Concurrent.STM
1718
import Control.DeepSeq (NFData)
1819
import Control.Monad.IO.Class
1920
import Control.Monad.Trans.Maybe
@@ -126,8 +127,8 @@ codeLens ideState plId CodeLensParams{_textDocument=TextDocumentIdentifier uri}
126127
case uriToFilePath' uri of
127128
Just (toNormalizedFilePath -> filePath) -> do
128129
_ <- runIdeAction "Example.codeLens" (shakeExtras ideState) $ runMaybeT $ useE TypeCheck filePath
129-
_diag <- getDiagnostics ideState
130-
_hDiag <- getHiddenDiagnostics ideState
130+
_diag <- atomically $ getDiagnostics ideState
131+
_hDiag <- atomically $ getHiddenDiagnostics ideState
131132
let
132133
title = "Add TODO Item via Code Lens"
133134
-- tedit = [TextEdit (Range (Position 3 0) (Position 3 0))

Diff for: plugins/default/src/Ide/Plugin/Example2.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Ide.Plugin.Example2
1414
descriptor
1515
) where
1616

17+
import Control.Concurrent.STM
1718
import Control.DeepSeq (NFData)
1819
import Control.Monad.IO.Class
1920
import Control.Monad.Trans.Maybe
@@ -116,8 +117,8 @@ codeLens ideState plId CodeLensParams{_textDocument=TextDocumentIdentifier uri}
116117
case uriToFilePath' uri of
117118
Just (toNormalizedFilePath -> filePath) -> do
118119
_ <- runIdeAction (fromNormalizedFilePath filePath) (shakeExtras ideState) $ runMaybeT $ useE TypeCheck filePath
119-
_diag <- getDiagnostics ideState
120-
_hDiag <- getHiddenDiagnostics ideState
120+
_diag <- atomically $ getDiagnostics ideState
121+
_hDiag <- atomically $ getHiddenDiagnostics ideState
121122
let
122123
title = "Add TODO2 Item via Code Lens"
123124
range = Range (Position 3 0) (Position 4 0)

Diff for: plugins/hls-hlint-plugin/hls-hlint-plugin.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -63,6 +63,7 @@ library
6363
, lens
6464
, lsp
6565
, regex-tdfa
66+
, stm
6667
, temporary
6768
, text
6869
, transformers

Diff for: plugins/hls-hlint-plugin/src/Ide/Plugin/Hlint.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -26,6 +26,7 @@ module Ide.Plugin.Hlint
2626
--, provider
2727
) where
2828
import Control.Arrow ((&&&))
29+
import Control.Concurrent.STM
2930
import Control.DeepSeq
3031
import Control.Exception
3132
import Control.Lens ((^.))
@@ -308,7 +309,7 @@ codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right
308309
where
309310

310311
getCodeActions = do
311-
allDiags <- getDiagnostics ideState
312+
allDiags <- atomically $ getDiagnostics ideState
312313
let docNfp = toNormalizedFilePath' <$> uriToFilePath' (docId ^. LSP.uri)
313314
numHintsInDoc = length
314315
[d | (nfp, _, d) <- allDiags

0 commit comments

Comments
 (0)