Skip to content

Commit 3b581a1

Browse files
Decrease contention in Progress reporting (#2357)
* STM stats in ghcide * improve contention in progress reporting BEFORE ====== ``` STM transaction statistics (2021-12-12 09:30:40.138006 UTC): Transaction Commits Retries Ratio _anonymous_ 15297 118 0.01 action queue - pop 2 2 1.00 actionQueue - done 2 0 0.00 actionQueue - peek 29 0 0.00 actionQueue - push 2 0 0.00 builder 282354 853 0.00 compute 16882 16 0.00 debouncer 6842 195 0.03 define - dirtyKeys 16895 2 0.00 define - read 1 10710 11 0.00 define - read 2 6232 5 0.00 define - write 6225 1 0.00 diagnostics - hidden 6871 9 0.00 diagnostics - publish 4073 188 0.05 diagnostics - read 6886 4 0.00 diagnostics - update 6871 23 0.00 incDatabase 10966 0 0.00 lastValueIO 4 2200 0 0.00 lastValueIO 5 2200 0 0.00 recordProgress 31238 13856 0.44 updateReverseDeps 64994 358 0.01 ``` AFTER ===== ``` STM transaction statistics (2021-12-12 09:24:24.769304 UTC): Transaction Commits Retries Ratio _anonymous_ 15199 134 0.01 action queue - pop 2 2 1.00 actionQueue - done 2 0 0.00 actionQueue - peek 29 0 0.00 actionQueue - push 2 0 0.00 builder 282244 744 0.00 compute 16882 26 0.00 debouncer 6847 220 0.03 define - dirtyKeys 16908 1 0.00 define - read 1 10710 8 0.00 define - read 2 6244 2 0.00 define - write 6236 1 0.00 diagnostics - hidden 6876 18 0.00 diagnostics - publish 3978 184 0.05 diagnostics - read 6886 2 0.00 diagnostics - update 6876 24 0.00 incDatabase 10966 0 0.00 lastValueIO 4 2200 1 0.00 lastValueIO 5 2200 0 0.00 recordProgress 31252 403 0.01 recordProgress2 31252 207 0.01 updateReverseDeps 64994 430 0.01 ``` * fix tests * Remove reads (@michaelpj suggestion) After ===== ``` STM transaction statistics (2021-12-12 22:11:20.016977 UTC): Transaction Commits Retries Ratio _anonymous_ 15227 116 0.01 action queue - pop 2 2 1.00 actionQueue - done 2 0 0.00 actionQueue - peek 29 0 0.00 actionQueue - push 2 0 0.00 builder 282373 771 0.00 compute 16882 32 0.00 debouncer 6864 215 0.03 define - dirtyKeys 16900 0 0.00 define - read 1 10710 3 0.00 define - read 2 6254 3 0.00 define - write 6248 1 0.00 diagnostics - hidden 6893 10 0.00 diagnostics - publish 4006 200 0.05 diagnostics - read 6901 1 0.00 diagnostics - update 6893 22 0.00 incDatabase 10966 0 0.00 lastValueIO 4 2200 0 0.00 lastValueIO 5 2200 0 0.00 recordProgress 31238 387 0.01 recordProgress2 31238 79 0.00 updateReverseDeps 64994 387 0.01 ``` Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 0c3f1c4 commit 3b581a1

File tree

4 files changed

+39
-43
lines changed

4 files changed

+39
-43
lines changed

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

+1-1
Original file line numberDiff line numberDiff line change
@@ -96,7 +96,7 @@ import GHC (GetDocsFailure (..),
9696
parsedSource)
9797

9898
import Control.Concurrent.Extra
99-
import Control.Concurrent.STM hiding (orElse)
99+
import Control.Concurrent.STM.Stats hiding (orElse)
100100
import Data.Aeson (toJSON)
101101
import Data.Binary
102102
import Data.Coerce

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

+14-18
Original file line numberDiff line numberDiff line change
@@ -14,9 +14,9 @@ module Development.IDE.Core.ProgressReporting
1414
where
1515

1616
import Control.Concurrent.Async
17-
import Control.Concurrent.STM.Stats (STM, TVar, atomically,
18-
newTVarIO, readTVar,
19-
readTVarIO, writeTVar)
17+
import Control.Concurrent.STM.Stats (TVar, atomicallyNamed,
18+
modifyTVar', newTVarIO,
19+
readTVarIO)
2020
import Control.Concurrent.Strict
2121
import Control.Monad.Extra
2222
import Control.Monad.IO.Class
@@ -82,21 +82,17 @@ data InProgressState = InProgressState
8282
newInProgress :: IO InProgressState
8383
newInProgress = InProgressState <$> newTVarIO 0 <*> newTVarIO 0 <*> STM.newIO
8484

85-
recordProgress :: InProgressState -> NormalizedFilePath -> (Int -> Int) -> STM ()
85+
recordProgress :: InProgressState -> NormalizedFilePath -> (Int -> Int) -> IO ()
8686
recordProgress InProgressState{..} file shift = do
87-
done <- readTVar doneVar
88-
todo <- readTVar todoVar
89-
(prev, new) <- STM.focus alterPrevAndNew file currentVar
90-
let (done',todo') =
91-
case (prev,new) of
92-
(Nothing,0) -> (done+1, todo+1)
93-
(Nothing,_) -> (done, todo+1)
94-
(Just 0, 0) -> (done , todo)
95-
(Just 0, _) -> (done-1, todo)
96-
(Just _, 0) -> (done+1, todo)
97-
(Just _, _) -> (done , todo)
98-
writeTVar todoVar todo'
99-
writeTVar doneVar done'
87+
(prev, new) <- atomicallyNamed "recordProgress" $ STM.focus alterPrevAndNew file currentVar
88+
atomicallyNamed "recordProgress2" $ do
89+
case (prev,new) of
90+
(Nothing,0) -> modifyTVar' doneVar (+1) >> modifyTVar' todoVar (+1)
91+
(Nothing,_) -> modifyTVar' todoVar (+1)
92+
(Just 0, 0) -> pure ()
93+
(Just 0, _) -> modifyTVar' doneVar pred
94+
(Just _, 0) -> modifyTVar' doneVar (+1)
95+
(Just _, _) -> pure()
10096
where
10197
alterPrevAndNew = do
10298
prev <- Focus.lookup
@@ -186,7 +182,7 @@ delayedProgressReporting before after lspEnv optProgressStyle = do
186182
-- Do not remove the eta-expansion without profiling a session with at
187183
-- least 1000 modifications.
188184
where
189-
f shift = atomically $ recordProgress inProgress file shift
185+
f shift = recordProgress inProgress file shift
190186

191187
mRunLspT :: Applicative m => Maybe (LSP.LanguageContextEnv c ) -> LSP.LspT c m () -> m ()
192188
mRunLspT (Just lspEnv) f = LSP.runLspT lspEnv f

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

+23-23
Original file line numberDiff line numberDiff line change
@@ -148,6 +148,7 @@ import GHC.Fingerprint
148148
import Language.LSP.Types.Capabilities
149149
import OpenTelemetry.Eventlog
150150

151+
import Control.Concurrent.STM.Stats (atomicallyNamed)
151152
import Control.Exception.Extra hiding (bracket_)
152153
import Data.Aeson (toJSON)
153154
import qualified Data.ByteString.Char8 as BS8
@@ -342,7 +343,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
342343
f <- MaybeT $ pure $ HMap.lookup (Key k) pmap
343344
(dv,del,ver) <- MaybeT $ runIdeAction "lastValueIO" s $ f file
344345
MaybeT $ pure $ (,del,ver) <$> fromDynamic dv
345-
atomically $ case mv of
346+
atomicallyNamed "lastValueIO" $ case mv of
346347
Nothing -> do
347348
STM.focus (Focus.alter (alterValue $ Failed True)) (toKey k file) state
348349
return Nothing
@@ -358,13 +359,13 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
358359
-- Something already succeeded before, leave it alone
359360
_ -> old
360361

361-
atomically (STM.lookup (toKey k file) state) >>= \case
362+
atomicallyNamed "lastValueIO 4" (STM.lookup (toKey k file) state) >>= \case
362363
Nothing -> readPersistent
363364
Just (ValueWithDiagnostics v _) -> case v of
364365
Succeeded ver (fromDynamic -> Just v) ->
365-
atomically $ Just . (v,) <$> mappingForVersion positionMapping file ver
366+
atomicallyNamed "lastValueIO 5" $ Just . (v,) <$> mappingForVersion positionMapping file ver
366367
Stale del ver (fromDynamic -> Just v) ->
367-
atomically $ Just . (v,) . maybe id addDelta del <$> mappingForVersion positionMapping file ver
368+
atomicallyNamed "lastValueIO 6" $ Just . (v,) . maybe id addDelta del <$> mappingForVersion positionMapping file ver
368369
Failed p | not p -> readPersistent
369370
_ -> pure Nothing
370371

@@ -456,7 +457,6 @@ recordDirtyKeys ShakeExtras{dirtyKeys} key file = do
456457
return $ withEventTrace "recordDirtyKeys" $ \addEvent -> do
457458
addEvent (fromString $ "dirty " <> show key) (fromString $ unlines $ map fromNormalizedFilePath file)
458459

459-
460460
-- | We return Nothing if the rule has not run and Just Failed if it has failed to produce a value.
461461
getValues ::
462462
forall k v.
@@ -629,8 +629,8 @@ shakeRestart IdeState{..} reason acts =
629629
(\runner -> do
630630
(stopTime,()) <- duration (cancelShakeSession runner)
631631
res <- shakeDatabaseProfile shakeDb
632-
backlog <- readTVarIO (dirtyKeys shakeExtras)
633-
queue <- atomically $ peekInProgress $ actionQueue shakeExtras
632+
backlog <- readTVarIO $ dirtyKeys shakeExtras
633+
queue <- atomicallyNamed "actionQueue - peek" $ peekInProgress $ actionQueue shakeExtras
634634
let profile = case res of
635635
Just fp -> ", profile saved at " <> fp
636636
_ -> ""
@@ -663,7 +663,7 @@ notifyTestingLogMessage extras msg = do
663663
shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a)
664664
shakeEnqueue ShakeExtras{actionQueue, logger} act = do
665665
(b, dai) <- instantiateDelayedAction act
666-
atomically $ pushQueue dai actionQueue
666+
atomicallyNamed "actionQueue - push" $ pushQueue dai actionQueue
667667
let wait' b =
668668
waitBarrier b `catches`
669669
[ Handler(\BlockedIndefinitelyOnMVar ->
@@ -672,7 +672,7 @@ shakeEnqueue ShakeExtras{actionQueue, logger} act = do
672672
, Handler (\e@AsyncCancelled -> do
673673
logPriority logger Debug $ T.pack $ actionName act <> " was cancelled"
674674

675-
atomically $ abortQueue dai actionQueue
675+
atomicallyNamed "actionQueue - abort" $ abortQueue dai actionQueue
676676
throw e)
677677
]
678678
return (wait' b >>= either throwIO return)
@@ -687,7 +687,7 @@ newSession
687687
-> IO ShakeSession
688688
newSession extras@ShakeExtras{..} shakeDb acts reason = do
689689
IdeOptions{optRunSubset} <- getIdeOptionsIO extras
690-
reenqueued <- atomically $ peekInProgress actionQueue
690+
reenqueued <- atomicallyNamed "actionQueue - peek" $ peekInProgress actionQueue
691691
allPendingKeys <-
692692
if optRunSubset
693693
then Just <$> readTVarIO dirtyKeys
@@ -696,14 +696,14 @@ newSession extras@ShakeExtras{..} shakeDb acts reason = do
696696
-- A daemon-like action used to inject additional work
697697
-- Runs actions from the work queue sequentially
698698
pumpActionThread otSpan = do
699-
d <- liftIO $ atomically $ popQueue actionQueue
699+
d <- liftIO $ atomicallyNamed "action queue - pop" $ popQueue actionQueue
700700
actionFork (run otSpan d) $ \_ -> pumpActionThread otSpan
701701

702702
-- TODO figure out how to thread the otSpan into defineEarlyCutoff
703703
run _otSpan d = do
704704
start <- liftIO offsetTime
705705
getAction d
706-
liftIO $ atomically $ doneQueue d actionQueue
706+
liftIO $ atomicallyNamed "actionQueue - done" $ doneQueue d actionQueue
707707
runTime <- liftIO start
708708
let msg = T.pack $ "finish: " ++ actionName d
709709
++ " (took " ++ showDuration runTime ++ ")"
@@ -806,7 +806,7 @@ garbageCollectKeys label maxAge checkParents agedKeys = do
806806
| age > maxAge
807807
, Just (kt,_) <- fromKeyType k
808808
, not(kt `HSet.member` preservedKeys checkParents)
809-
= atomically $ do
809+
= atomicallyNamed "GC" $ do
810810
gotIt <- STM.focus (Focus.member <* Focus.delete) k values
811811
when gotIt $
812812
modifyTVar' dk (HSet.insert k)
@@ -910,7 +910,7 @@ useWithStaleFast' key file = do
910910
wait <- delayedAction $ mkDelayedAction ("C:" ++ show key ++ ":" ++ fromNormalizedFilePath file) Debug $ use key file
911911

912912
s@ShakeExtras{state} <- askShake
913-
r <- liftIO $ atomically $ getValues state key file
913+
r <- liftIO $ atomicallyNamed "useStateFast" $ getValues state key file
914914
liftIO $ case r of
915915
-- block for the result if we haven't computed before
916916
Nothing -> do
@@ -1019,7 +1019,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
10191019
(if optSkipProgress options key then id else inProgress progress file) $ do
10201020
val <- case old of
10211021
Just old | mode == RunDependenciesSame -> do
1022-
v <- liftIO $ atomically $ getValues state key file
1022+
v <- liftIO $ atomicallyNamed "define - read 1" $ getValues state key file
10231023
case v of
10241024
-- No changes in the dependencies and we have
10251025
-- an existing successful result.
@@ -1038,10 +1038,10 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
10381038
(do v <- action; liftIO $ evaluate $ force v) $
10391039
\(e :: SomeException) -> do
10401040
pure (Nothing, ([ideErrorText file $ T.pack $ show e | not $ isBadDependency e],Nothing))
1041-
modTime <- liftIO $ (currentValue . fst =<<) <$> atomically (getValues state GetModificationTime file)
1041+
modTime <- liftIO $ (currentValue . fst =<<) <$> atomicallyNamed "define - read 2" (getValues state GetModificationTime file)
10421042
(bs, res) <- case res of
10431043
Nothing -> do
1044-
staleV <- liftIO $ atomically $ getValues state key file
1044+
staleV <- liftIO $ atomicallyNamed "define -read 3" $ getValues state key file
10451045
pure $ case staleV of
10461046
Nothing -> (toShakeValue ShakeResult bs, Failed False)
10471047
Just v -> case v of
@@ -1052,7 +1052,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
10521052
(Failed b, _) ->
10531053
(toShakeValue ShakeResult bs, Failed b)
10541054
Just v -> pure (maybe ShakeNoCutoff ShakeResult bs, Succeeded (vfsVersion =<< modTime) v)
1055-
liftIO $ atomically $ setValues state key file res (Vector.fromList diags)
1055+
liftIO $ atomicallyNamed "define - write" $ setValues state key file res (Vector.fromList diags)
10561056
doDiagnostics diags
10571057
let eq = case (bs, fmap decodeShakeValue old) of
10581058
(ShakeResult a, Just (ShakeResult b)) -> cmp a b
@@ -1064,7 +1064,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
10641064
(if eq then ChangedRecomputeSame else ChangedRecomputeDiff)
10651065
(encodeShakeValue bs) $
10661066
A res
1067-
liftIO $ atomically $ modifyTVar' dirtyKeys (HSet.delete $ toKey key file)
1067+
liftIO $ atomicallyNamed "define - dirtyKeys" $ modifyTVar' dirtyKeys (HSet.delete $ toKey key file)
10681068
return res
10691069

10701070
traceA :: A v -> String
@@ -1152,7 +1152,7 @@ updateFileDiagnostics :: MonadIO m
11521152
-> [(ShowDiagnostic,Diagnostic)] -- ^ current results
11531153
-> m ()
11541154
updateFileDiagnostics fp k ShakeExtras{logger, diagnostics, hiddenDiagnostics, publishedDiagnostics, state, debouncer, lspEnv} current = liftIO $ do
1155-
modTime <- (currentValue . fst =<<) <$> atomically (getValues state GetModificationTime fp)
1155+
modTime <- (currentValue . fst =<<) <$> atomicallyNamed "diagnostics - read" (getValues state GetModificationTime fp)
11561156
let (currentShown, currentHidden) = partition ((== ShowDiag) . fst) current
11571157
uri = filePathToUri' fp
11581158
ver = vfsVersion =<< modTime
@@ -1162,13 +1162,13 @@ updateFileDiagnostics fp k ShakeExtras{logger, diagnostics, hiddenDiagnostics, p
11621162
-- published. Otherwise, we might never publish certain diagnostics if
11631163
-- an exception strikes between modifyVar but before
11641164
-- publishDiagnosticsNotification.
1165-
newDiags <- liftIO $ atomically $ update (map snd currentShown) diagnostics
1166-
_ <- liftIO $ atomically $ update (map snd currentHidden) hiddenDiagnostics
1165+
newDiags <- liftIO $ atomicallyNamed "diagnostics - update" $ update (map snd currentShown) diagnostics
1166+
_ <- liftIO $ atomicallyNamed "diagnostics - hidden" $ update (map snd currentHidden) hiddenDiagnostics
11671167
let uri = filePathToUri' fp
11681168
let delay = if null newDiags then 0.1 else 0
11691169
registerEvent debouncer delay uri $ do
11701170
join $ mask_ $ do
1171-
lastPublish <- atomically $ STM.focus (Focus.lookupWithDefault [] <* Focus.insert newDiags) uri publishedDiagnostics
1171+
lastPublish <- atomicallyNamed "diagnostics - publish" $ STM.focus (Focus.lookupWithDefault [] <* Focus.insert newDiags) uri publishedDiagnostics
11721172
let action = when (lastPublish /= newDiags) $ case lspEnv of
11731173
Nothing -> -- Print an LSP event.
11741174
logInfo logger $ showDiagnosticsColored $ map (fp,ShowDiag,) newDiags

ghcide/test/exe/Progress.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ reportProgressTests = testGroup "recordProgress"
3535
decrease = recordProgressModel "A" succ increase
3636
done = recordProgressModel "A" pred decrease
3737
recordProgressModel key change state =
38-
model state $ \st -> atomically $ recordProgress st key change
38+
model state $ \st -> recordProgress st key change
3939
model stateModelIO k = do
4040
state <- fromModel =<< stateModelIO
4141
k state

0 commit comments

Comments
 (0)