@@ -148,6 +148,7 @@ import GHC.Fingerprint
148
148
import Language.LSP.Types.Capabilities
149
149
import OpenTelemetry.Eventlog
150
150
151
+ import Control.Concurrent.STM.Stats (atomicallyNamed )
151
152
import Control.Exception.Extra hiding (bracket_ )
152
153
import Data.Aeson (toJSON )
153
154
import qualified Data.ByteString.Char8 as BS8
@@ -342,7 +343,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
342
343
f <- MaybeT $ pure $ HMap. lookup (Key k) pmap
343
344
(dv,del,ver) <- MaybeT $ runIdeAction " lastValueIO" s $ f file
344
345
MaybeT $ pure $ (,del,ver) <$> fromDynamic dv
345
- atomically $ case mv of
346
+ atomicallyNamed " lastValueIO " $ case mv of
346
347
Nothing -> do
347
348
STM. focus (Focus. alter (alterValue $ Failed True )) (toKey k file) state
348
349
return Nothing
@@ -358,13 +359,13 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
358
359
-- Something already succeeded before, leave it alone
359
360
_ -> old
360
361
361
- atomically (STM. lookup (toKey k file) state) >>= \ case
362
+ atomicallyNamed " lastValueIO 4 " (STM. lookup (toKey k file) state) >>= \ case
362
363
Nothing -> readPersistent
363
364
Just (ValueWithDiagnostics v _) -> case v of
364
365
Succeeded ver (fromDynamic -> Just v) ->
365
- atomically $ Just . (v,) <$> mappingForVersion positionMapping file ver
366
+ atomicallyNamed " lastValueIO 5 " $ Just . (v,) <$> mappingForVersion positionMapping file ver
366
367
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
368
369
Failed p | not p -> readPersistent
369
370
_ -> pure Nothing
370
371
@@ -456,7 +457,6 @@ recordDirtyKeys ShakeExtras{dirtyKeys} key file = do
456
457
return $ withEventTrace " recordDirtyKeys" $ \ addEvent -> do
457
458
addEvent (fromString $ " dirty " <> show key) (fromString $ unlines $ map fromNormalizedFilePath file)
458
459
459
-
460
460
-- | We return Nothing if the rule has not run and Just Failed if it has failed to produce a value.
461
461
getValues ::
462
462
forall k v .
@@ -629,8 +629,8 @@ shakeRestart IdeState{..} reason acts =
629
629
(\ runner -> do
630
630
(stopTime,() ) <- duration (cancelShakeSession runner)
631
631
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
634
634
let profile = case res of
635
635
Just fp -> " , profile saved at " <> fp
636
636
_ -> " "
@@ -663,7 +663,7 @@ notifyTestingLogMessage extras msg = do
663
663
shakeEnqueue :: ShakeExtras -> DelayedAction a -> IO (IO a )
664
664
shakeEnqueue ShakeExtras {actionQueue, logger} act = do
665
665
(b, dai) <- instantiateDelayedAction act
666
- atomically $ pushQueue dai actionQueue
666
+ atomicallyNamed " actionQueue - push " $ pushQueue dai actionQueue
667
667
let wait' b =
668
668
waitBarrier b `catches`
669
669
[ Handler (\ BlockedIndefinitelyOnMVar ->
@@ -672,7 +672,7 @@ shakeEnqueue ShakeExtras{actionQueue, logger} act = do
672
672
, Handler (\ e@ AsyncCancelled -> do
673
673
logPriority logger Debug $ T. pack $ actionName act <> " was cancelled"
674
674
675
- atomically $ abortQueue dai actionQueue
675
+ atomicallyNamed " actionQueue - abort " $ abortQueue dai actionQueue
676
676
throw e)
677
677
]
678
678
return (wait' b >>= either throwIO return )
@@ -687,7 +687,7 @@ newSession
687
687
-> IO ShakeSession
688
688
newSession extras@ ShakeExtras {.. } shakeDb acts reason = do
689
689
IdeOptions {optRunSubset} <- getIdeOptionsIO extras
690
- reenqueued <- atomically $ peekInProgress actionQueue
690
+ reenqueued <- atomicallyNamed " actionQueue - peek " $ peekInProgress actionQueue
691
691
allPendingKeys <-
692
692
if optRunSubset
693
693
then Just <$> readTVarIO dirtyKeys
@@ -696,14 +696,14 @@ newSession extras@ShakeExtras{..} shakeDb acts reason = do
696
696
-- A daemon-like action used to inject additional work
697
697
-- Runs actions from the work queue sequentially
698
698
pumpActionThread otSpan = do
699
- d <- liftIO $ atomically $ popQueue actionQueue
699
+ d <- liftIO $ atomicallyNamed " action queue - pop " $ popQueue actionQueue
700
700
actionFork (run otSpan d) $ \ _ -> pumpActionThread otSpan
701
701
702
702
-- TODO figure out how to thread the otSpan into defineEarlyCutoff
703
703
run _otSpan d = do
704
704
start <- liftIO offsetTime
705
705
getAction d
706
- liftIO $ atomically $ doneQueue d actionQueue
706
+ liftIO $ atomicallyNamed " actionQueue - done " $ doneQueue d actionQueue
707
707
runTime <- liftIO start
708
708
let msg = T. pack $ " finish: " ++ actionName d
709
709
++ " (took " ++ showDuration runTime ++ " )"
@@ -806,7 +806,7 @@ garbageCollectKeys label maxAge checkParents agedKeys = do
806
806
| age > maxAge
807
807
, Just (kt,_) <- fromKeyType k
808
808
, not (kt `HSet.member` preservedKeys checkParents)
809
- = atomically $ do
809
+ = atomicallyNamed " GC " $ do
810
810
gotIt <- STM. focus (Focus. member <* Focus. delete) k values
811
811
when gotIt $
812
812
modifyTVar' dk (HSet. insert k)
@@ -910,7 +910,7 @@ useWithStaleFast' key file = do
910
910
wait <- delayedAction $ mkDelayedAction (" C:" ++ show key ++ " :" ++ fromNormalizedFilePath file) Debug $ use key file
911
911
912
912
s@ ShakeExtras {state} <- askShake
913
- r <- liftIO $ atomically $ getValues state key file
913
+ r <- liftIO $ atomicallyNamed " useStateFast " $ getValues state key file
914
914
liftIO $ case r of
915
915
-- block for the result if we haven't computed before
916
916
Nothing -> do
@@ -1019,7 +1019,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
1019
1019
(if optSkipProgress options key then id else inProgress progress file) $ do
1020
1020
val <- case old of
1021
1021
Just old | mode == RunDependenciesSame -> do
1022
- v <- liftIO $ atomically $ getValues state key file
1022
+ v <- liftIO $ atomicallyNamed " define - read 1 " $ getValues state key file
1023
1023
case v of
1024
1024
-- No changes in the dependencies and we have
1025
1025
-- an existing successful result.
@@ -1038,10 +1038,10 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
1038
1038
(do v <- action; liftIO $ evaluate $ force v) $
1039
1039
\ (e :: SomeException ) -> do
1040
1040
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)
1042
1042
(bs, res) <- case res of
1043
1043
Nothing -> do
1044
- staleV <- liftIO $ atomically $ getValues state key file
1044
+ staleV <- liftIO $ atomicallyNamed " define -read 3 " $ getValues state key file
1045
1045
pure $ case staleV of
1046
1046
Nothing -> (toShakeValue ShakeResult bs, Failed False )
1047
1047
Just v -> case v of
@@ -1052,7 +1052,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
1052
1052
(Failed b, _) ->
1053
1053
(toShakeValue ShakeResult bs, Failed b)
1054
1054
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)
1056
1056
doDiagnostics diags
1057
1057
let eq = case (bs, fmap decodeShakeValue old) of
1058
1058
(ShakeResult a, Just (ShakeResult b)) -> cmp a b
@@ -1064,7 +1064,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
1064
1064
(if eq then ChangedRecomputeSame else ChangedRecomputeDiff )
1065
1065
(encodeShakeValue bs) $
1066
1066
A res
1067
- liftIO $ atomically $ modifyTVar' dirtyKeys (HSet. delete $ toKey key file)
1067
+ liftIO $ atomicallyNamed " define - dirtyKeys " $ modifyTVar' dirtyKeys (HSet. delete $ toKey key file)
1068
1068
return res
1069
1069
1070
1070
traceA :: A v -> String
@@ -1152,7 +1152,7 @@ updateFileDiagnostics :: MonadIO m
1152
1152
-> [(ShowDiagnostic ,Diagnostic )] -- ^ current results
1153
1153
-> m ()
1154
1154
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)
1156
1156
let (currentShown, currentHidden) = partition ((== ShowDiag ) . fst ) current
1157
1157
uri = filePathToUri' fp
1158
1158
ver = vfsVersion =<< modTime
@@ -1162,13 +1162,13 @@ updateFileDiagnostics fp k ShakeExtras{logger, diagnostics, hiddenDiagnostics, p
1162
1162
-- published. Otherwise, we might never publish certain diagnostics if
1163
1163
-- an exception strikes between modifyVar but before
1164
1164
-- 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
1167
1167
let uri = filePathToUri' fp
1168
1168
let delay = if null newDiags then 0.1 else 0
1169
1169
registerEvent debouncer delay uri $ do
1170
1170
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
1172
1172
let action = when (lastPublish /= newDiags) $ case lspEnv of
1173
1173
Nothing -> -- Print an LSP event.
1174
1174
logInfo logger $ showDiagnosticsColored $ map (fp,ShowDiag ,) newDiags
0 commit comments