Skip to content

Commit 711e19c

Browse files
authored
Use stm-stats to reduce contention in hls-graph (#2421)
* STM stats * Atomically stats in hls-graph * improve contention in hls-graph STM stats are not yet reported in the benchmark suite, so we need to run the benchmarks manually in verbose mode to observ them (and build hls-graph with the stm-stats Cabal flag). cabal build exe:ghcide ghcide-bench && cabal exec cabal run ghcide-bench -- -- -s "edit" --samples 10 --no-clean --example-module Distribution/Simple.hs --example-module Distribution/Types/Module.hs -v Lots of contention in `builder` and esp. `updateReverseDeps`. `incDatabase` should not have any retries, could be a bug. ``` STM transaction statistics (2021-11-30 16:51:48.260905 UTC): Transaction Commits Retries Ratio _anonymous_ 5 0 0.00 builder 80886 6000 0.07 compute 19175 141 0.01 incDatabase 27 100 3.70 updateReverseDeps 3827 765 0.20 ``` ``` STM transaction statistics (2021-11-30 19:45:30.904126927 UTC): Transaction Commits Retries Ratio _anonymous_ 1 0 0.00 builder 606254 22569 0.04 compute 324708 10428 0.03 incDatabase 15 0 0.00 updateReverseDeps 259755 489285 1.88 ``` ``` STM transaction statistics (2021-11-30 20:21:57.968789 UTC): Transaction Commits Retries Ratio _anonymous_ 48318 2 0.00 builder 1108126 1276 0.00 compute 22423 144 0.01 updateReverseDeps 65225 377 0.01 ``` ``` STM transaction statistics (2021-11-30 19:57:27.979412261 UTC): Transaction Commits Retries Ratio _anonymous_ 294 0 0.00 builder 861431 2914 0.00 compute 324708 1573 0.00 updateReverseDeps 858100 17816 0.02 ``` * added comments
1 parent 3e44c70 commit 711e19c

File tree

7 files changed

+224
-18
lines changed

7 files changed

+224
-18
lines changed

ghcide/src/Development/IDE/Main.hs

+2
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module Development.IDE.Main
1111
import Control.Concurrent.Extra (newLock, readVar,
1212
withLock,
1313
withNumCapabilities)
14+
import Control.Concurrent.STM.Stats (dumpSTMStats)
1415
import Control.Exception.Safe (Exception (displayException),
1516
catchAny)
1617
import Control.Monad.Extra (concatMapM, unless,
@@ -308,6 +309,7 @@ defaultMain Arguments{..} = do
308309
vfs
309310
hiedb
310311
hieChan
312+
dumpSTMStats
311313
Check argFiles -> do
312314
dir <- IO.getCurrentDirectory
313315
dbLoc <- getHieDbLoc dir

hls-graph/hls-graph.cabal

+9
Original file line numberDiff line numberDiff line change
@@ -31,12 +31,18 @@ flag embed-files
3131
manual: True
3232
description: Embed data files into the shake library
3333

34+
flag stm-stats
35+
default: False
36+
manual: True
37+
description: Collect STM transaction stats
38+
3439
source-repository head
3540
type: git
3641
location: https://github.com/haskell/haskell-language-server
3742

3843
library
3944
exposed-modules:
45+
Control.Concurrent.STM.Stats
4046
Development.IDE.Graph
4147
Development.IDE.Graph.Classes
4248
Development.IDE.Graph.Database
@@ -82,6 +88,9 @@ library
8288
build-depends:
8389
file-embed >= 0.0.11,
8490
template-haskell
91+
if flag(stm-stats)
92+
cpp-options: -DSTM_STATS
93+
8594

8695
ghc-options:
8796
-Wall -Wredundant-constraints -Wno-name-shadowing
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,184 @@
1+
{-# LANGUAGE CPP #-}
2+
{-# LANGUAGE RecordWildCards #-}
3+
{-# LANGUAGE ScopedTypeVariables #-}
4+
module Control.Concurrent.STM.Stats
5+
( atomicallyNamed
6+
, atomically
7+
, getSTMStats
8+
, dumpSTMStats
9+
, module Control.Concurrent.STM
10+
) where
11+
12+
import Control.Concurrent.STM hiding (atomically)
13+
import qualified Control.Concurrent.STM as STM
14+
import Data.Map (Map)
15+
#ifdef STM_STATS
16+
import Control.Exception (BlockedIndefinitelyOnSTM, Exception,
17+
catch, throwIO)
18+
import Control.Monad
19+
import Data.IORef
20+
import qualified Data.Map.Strict as M
21+
import Data.Time (getCurrentTime)
22+
import Data.Typeable (Typeable)
23+
import GHC.Conc (unsafeIOToSTM)
24+
import System.IO
25+
import System.IO.Unsafe
26+
import Text.Printf
27+
#endif
28+
29+
atomicallyNamed :: String -> STM a -> IO a
30+
atomically :: STM a -> IO a
31+
dumpSTMStats :: IO ()
32+
getSTMStats :: IO (Map String (Int,Int))
33+
34+
#ifndef STM_STATS
35+
36+
getSTMStats = pure mempty
37+
atomicallyNamed _ = atomically
38+
dumpSTMStats = pure ()
39+
atomically = STM.atomically
40+
41+
#else
42+
-- adapted from the STM.Stats package
43+
44+
atomicallyNamed = trackNamedSTM
45+
atomically = trackSTM
46+
47+
-- | Global state, seems to be unavoidable here.
48+
globalRetryCountMap :: IORef (Map String (Int,Int))
49+
globalRetryCountMap = unsafePerformIO (newIORef M.empty)
50+
{-# NOINLINE globalRetryCountMap #-}
51+
52+
53+
-- | For the most general transaction tracking function, 'trackSTMConf', all
54+
-- settings can be configured using a 'TrackSTMConf' value.
55+
data TrackSTMConf = TrackSTMConf
56+
{ tryThreshold :: Maybe Int
57+
-- ^ If the number of retries of one transaction run reaches this
58+
-- count, a warning is issued at runtime. If set to @Nothing@, disables the warnings completely.
59+
, globalTheshold :: Maybe Int
60+
-- ^ If the total number of retries of one named transaction reaches
61+
-- this count, a warning is issued. If set to @Nothing@, disables the
62+
-- warnings completely.
63+
, extendException :: Bool
64+
-- ^ If this is set, a 'BlockedIndefinitelyOnSTM' exception is replaced
65+
-- by a 'BlockedIndefinitelyOnNamedSTM' exception, carrying the name of
66+
-- the exception.
67+
, warnFunction :: String -> IO ()
68+
-- ^ Function to call when a warning is to be emitted.
69+
, warnInSTMFunction :: String -> IO ()
70+
-- ^ Function to call when a warning is to be emitted during an STM
71+
-- transaction. This is possibly dangerous, see the documentation to
72+
-- 'unsafeIOToSTM', but can be useful to detect transactions that keep
73+
-- retrying forever.
74+
}
75+
76+
-- | The default settings are:
77+
--
78+
-- > defaultTrackSTMConf = TrackSTMConf
79+
-- > { tryThreshold = Just 10
80+
-- > , globalTheshold = Just 3000
81+
-- > , exception = True
82+
-- > , warnFunction = hPutStrLn stderr
83+
-- > , warnInSTMFunction = \_ -> return ()
84+
-- > }
85+
defaultTrackSTMConf :: TrackSTMConf
86+
defaultTrackSTMConf = TrackSTMConf
87+
{ tryThreshold = Just 10
88+
, globalTheshold = Just 3000
89+
, extendException = True
90+
, warnFunction = hPutStrLn stderr
91+
, warnInSTMFunction = \_ -> return ()
92+
}
93+
94+
-- | A drop-in replacement for 'atomically'. The statistics will list this, and
95+
-- all other unnamed transactions, as \"@_anonymous_@\" and
96+
-- 'BlockedIndefinitelyOnSTM' exceptions will not be replaced.
97+
-- See below for variants that give more control over the statistics and
98+
-- generated warnings.
99+
trackSTM :: STM a -> IO a
100+
trackSTM = trackSTMConf defaultTrackSTMConf { extendException = False } "_anonymous_"
101+
102+
-- | Run 'atomically' and collect the retry statistics under the given name and using the default configuration, 'defaultTrackSTMConf'.
103+
trackNamedSTM :: String -> STM a -> IO a
104+
trackNamedSTM = trackSTMConf defaultTrackSTMConf
105+
106+
-- | Run 'atomically' and collect the retry statistics under the given name,
107+
-- while issuing warnings when the configured thresholds are exceeded.
108+
trackSTMConf :: TrackSTMConf -> String -> STM a -> IO a
109+
trackSTMConf (TrackSTMConf {..}) name txm = do
110+
counter <- newIORef 0
111+
let wrappedTx =
112+
do unsafeIOToSTM $ do
113+
i <- atomicModifyIORef' counter incCounter
114+
when (warnPred i) $
115+
warnInSTMFunction $ msgPrefix ++ " reached try count of " ++ show i
116+
txm
117+
res <- if extendException
118+
then STM.atomically wrappedTx
119+
`catch` (\(_::BlockedIndefinitelyOnSTM) ->
120+
throwIO (BlockedIndefinitelyOnNamedSTM name))
121+
else STM.atomically wrappedTx
122+
i <- readIORef counter
123+
doMB tryThreshold $ \threshold ->
124+
when (i > threshold) $
125+
warnFunction $ msgPrefix ++ " finished after " ++ show (i-1) ++ " retries"
126+
incGlobalRetryCount (i - 1)
127+
return res
128+
where
129+
doMB Nothing _ = return ()
130+
doMB (Just x) m = m x
131+
incCounter i = let j = i + 1 in (j, j)
132+
warnPred j = case tryThreshold of
133+
Nothing -> False
134+
Just n -> j >= 2*n && (j >= 4 * n || j `mod` (2 * n) == 0)
135+
msgPrefix = "STM transaction " ++ name
136+
incGlobalRetryCount i = do
137+
(k,k') <- atomicModifyIORef' globalRetryCountMap $ \m ->
138+
let (oldVal, m') = M.insertLookupWithKey
139+
(\_ (a1,b1) (a2,b2) -> ((,) $! a1+a2) $! b1+b2)
140+
name
141+
(1,i)
142+
m
143+
in (m', let j = maybe 0 snd oldVal in (j,j+i))
144+
doMB globalTheshold $ \globalRetryThreshold ->
145+
when (k `div` globalRetryThreshold /= k' `div` globalRetryThreshold) $
146+
warnFunction $ msgPrefix ++ " reached global retry count of " ++ show k'
147+
148+
-- | If 'extendException' is set (which is the case with 'trackNamedSTM'), an
149+
-- occurrence of 'BlockedIndefinitelyOnSTM' is replaced by
150+
-- 'BlockedIndefinitelyOnNamedSTM', carrying the name of the transaction and
151+
-- thus giving more helpful error messages.
152+
newtype BlockedIndefinitelyOnNamedSTM = BlockedIndefinitelyOnNamedSTM String
153+
deriving (Typeable)
154+
155+
instance Show BlockedIndefinitelyOnNamedSTM where
156+
showsPrec _ (BlockedIndefinitelyOnNamedSTM name) =
157+
showString $ "thread blocked indefinitely in STM transaction" ++ name
158+
159+
instance Exception BlockedIndefinitelyOnNamedSTM
160+
161+
162+
163+
-- | Fetches the current transaction statistics data.
164+
--
165+
-- The map maps transaction names to counts of transaction commits and
166+
-- transaction retries.
167+
getSTMStats = readIORef globalRetryCountMap
168+
169+
-- | Dumps the current transaction statistics data to 'System.IO.stderr'.
170+
dumpSTMStats = do
171+
stats <- getSTMStats
172+
time <- show <$> getCurrentTime
173+
hPutStrLn stderr $ "STM transaction statistics (" ++ time ++ "):"
174+
sequence_ $
175+
hPrintf stderr "%-22s %10s %10s %10s\n" "Transaction" "Commits" "Retries" "Ratio" :
176+
[ hPrintf stderr "%-22s %10d %10d %10.2f\n" name commits retries ratio
177+
| (name,(commits,retries)) <- M.toList stats
178+
, commits > 0 -- safeguard
179+
, let ratio = fromIntegral retries / fromIntegral commits :: Double
180+
]
181+
182+
183+
#endif
184+

hls-graph/src/Development/IDE/Graph/Database.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -12,8 +12,7 @@ module Development.IDE.Graph.Database(
1212
shakeGetDirtySet,
1313
shakeGetCleanKeys
1414
,shakeGetBuildEdges) where
15-
import Control.Concurrent.STM (atomically,
16-
readTVarIO)
15+
import Control.Concurrent.STM.Stats (readTVarIO)
1716
import Data.Dynamic
1817
import Data.Maybe
1918
import Development.IDE.Graph.Classes ()
@@ -57,14 +56,15 @@ shakeGetBuildStep (ShakeDatabase _ _ db) = do
5756
unvoid :: Functor m => m () -> m a
5857
unvoid = fmap undefined
5958

59+
-- | Assumes that the database is not running a build
6060
shakeRunDatabaseForKeys
6161
:: Maybe [Key]
6262
-- ^ Set of keys changed since last run. 'Nothing' means everything has changed
6363
-> ShakeDatabase
6464
-> [Action a]
6565
-> IO ([a], [IO ()])
6666
shakeRunDatabaseForKeys keysChanged (ShakeDatabase lenAs1 as1 db) as2 = do
67-
atomically $ incDatabase db keysChanged
67+
incDatabase db keysChanged
6868
as <- fmap (drop lenAs1) $ runActions db $ map unvoid as1 ++ as2
6969
return (as, [])
7070

hls-graph/src/Development/IDE/Graph/Internal/Database.hs

+24-13
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,8 @@ module Development.IDE.Graph.Internal.Database (newDatabase, incDatabase, build,
1616

1717
import Control.Concurrent.Async
1818
import Control.Concurrent.Extra
19-
import Control.Concurrent.STM (STM, atomically,
19+
import Control.Concurrent.STM.Stats (STM, atomically,
20+
atomicallyNamed,
2021
modifyTVar', newTVarIO,
2122
readTVarIO)
2223
import Control.Exception
@@ -49,20 +50,24 @@ newDatabase databaseExtra databaseRules = do
4950
databaseValues <- atomically SMap.new
5051
pure Database{..}
5152

52-
-- | Increment the step and mark dirty
53-
incDatabase :: Database -> Maybe [Key] -> STM ()
53+
-- | Increment the step and mark dirty.
54+
-- Assumes that the database is not running a build
55+
incDatabase :: Database -> Maybe [Key] -> IO ()
5456
-- only some keys are dirty
5557
incDatabase db (Just kk) = do
56-
modifyTVar' (databaseStep db) $ \(Step i) -> Step $ i + 1
58+
atomicallyNamed "incDatabase" $ modifyTVar' (databaseStep db) $ \(Step i) -> Step $ i + 1
5759
transitiveDirtyKeys <- transitiveDirtySet db kk
5860
for_ transitiveDirtyKeys $ \k ->
59-
SMap.focus updateDirty k (databaseValues db)
61+
-- Updating all the keys atomically is not necessary
62+
-- since we assume that no build is mutating the db.
63+
-- Therefore run one transaction per key to minimise contention.
64+
atomicallyNamed "incDatabase" $ SMap.focus updateDirty k (databaseValues db)
6065

6166
-- all keys are dirty
6267
incDatabase db Nothing = do
63-
modifyTVar' (databaseStep db) $ \(Step i) -> Step $ i + 1
68+
atomically $ modifyTVar' (databaseStep db) $ \(Step i) -> Step $ i + 1
6469
let list = SMap.listT (databaseValues db)
65-
flip ListT.traverse_ list $ \(k,_) -> do
70+
atomicallyNamed "incDatabase - all " $ flip ListT.traverse_ list $ \(k,_) ->
6671
SMap.focus updateDirty k (databaseValues db)
6772

6873
updateDirty :: Monad m => Focus.Focus KeyDetails m ()
@@ -93,7 +98,10 @@ builder db@Database{..} keys = withRunInIO $ \(RunInIO run) -> do
9398
-- Things that I need to force before my results are ready
9499
toForce <- liftIO $ newTVarIO []
95100
current <- liftIO $ readTVarIO databaseStep
96-
results <- liftIO $ atomically $ for keys $ \id -> do
101+
results <- liftIO $ for keys $ \id ->
102+
-- Updating the status of all the dependencies atomically is not necessary.
103+
-- Therefore, run one transaction per dep. to avoid contention
104+
atomicallyNamed "builder" $ do
97105
-- Spawn the id if needed
98106
status <- SMap.lookup id databaseValues
99107
val <- case viewDirty current $ maybe (Dirty Nothing) keyStatus status of
@@ -165,7 +173,7 @@ compute db@Database{..} key mode result = do
165173
(getResultDepsDefault [] previousDeps)
166174
(HSet.fromList deps)
167175
_ -> pure ()
168-
atomically $ SMap.focus (updateStatus $ Clean res) key databaseValues
176+
atomicallyNamed "compute" $ SMap.focus (updateStatus $ Clean res) key databaseValues
169177
pure res
170178

171179
updateStatus :: Monad m => Status -> Focus.Focus KeyDetails m ()
@@ -214,7 +222,7 @@ updateReverseDeps
214222
-> [Key] -- ^ Previous direct dependencies of Id
215223
-> HashSet Key -- ^ Current direct dependencies of Id
216224
-> IO ()
217-
updateReverseDeps myId db prev new = uninterruptibleMask_ $ atomically $ do
225+
updateReverseDeps myId db prev new = uninterruptibleMask_ $ do
218226
forM_ prev $ \d ->
219227
unless (d `HSet.member` new) $
220228
doOne (HSet.delete myId) d
@@ -223,20 +231,23 @@ updateReverseDeps myId db prev new = uninterruptibleMask_ $ atomically $ do
223231
where
224232
alterRDeps f =
225233
Focus.adjust (onKeyReverseDeps f)
226-
doOne f id =
234+
-- updating all the reverse deps atomically is not needed.
235+
-- Therefore, run individual transactions for each update
236+
-- in order to avoid contention
237+
doOne f id = atomicallyNamed "updateReverseDeps" $
227238
SMap.focus (alterRDeps f) id (databaseValues db)
228239

229240
getReverseDependencies :: Database -> Key -> STM (Maybe (HashSet Key))
230241
getReverseDependencies db = (fmap.fmap) keyReverseDeps . flip SMap.lookup (databaseValues db)
231242

232-
transitiveDirtySet :: Foldable t => Database -> t Key -> STM (HashSet Key)
243+
transitiveDirtySet :: Foldable t => Database -> t Key -> IO (HashSet Key)
233244
transitiveDirtySet database = flip State.execStateT HSet.empty . traverse_ loop
234245
where
235246
loop x = do
236247
seen <- State.get
237248
if x `HSet.member` seen then pure () else do
238249
State.put (HSet.insert x seen)
239-
next <- lift $ getReverseDependencies database x
250+
next <- lift $ atomically $ getReverseDependencies database x
240251
traverse_ loop (maybe mempty HSet.toList next)
241252

242253
-- | IO extended to track created asyncs to clean them up when the thread is killed,

hls-graph/src/Development/IDE/Graph/Internal/Profile.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@
77

88
module Development.IDE.Graph.Internal.Profile (writeProfile) where
99

10-
import Control.Concurrent.STM (readTVarIO)
10+
import Control.Concurrent.STM.Stats (readTVarIO)
1111
import Data.Bifunctor
1212
import qualified Data.ByteString.Lazy.Char8 as LBS
1313
import Data.Char

hls-graph/src/Development/IDE/Graph/Internal/Types.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ module Development.IDE.Graph.Internal.Types where
1414
import Control.Applicative
1515
import Control.Monad.Catch
1616
-- Needed in GHC 8.6.5
17-
import Control.Concurrent.STM (TVar, atomically)
17+
import Control.Concurrent.STM.Stats (TVar, atomically)
1818
import Control.Monad.Fail
1919
import Control.Monad.IO.Class
2020
import Control.Monad.Trans.Reader

0 commit comments

Comments
 (0)