Skip to content

Commit 89c44bf

Browse files
pepeiborrajneira
andauthored
Lockless iorefs (#2460)
* lock-less KnownTargets * lock-less exportsMap * lock-less globals * lock-less persistentKeys * switch to TVar * fix build in plugins * add comments Co-authored-by: Javier Neira <atreyu.bbb@gmail.com>
1 parent 0f49c0e commit 89c44bf

File tree

7 files changed

+43
-32
lines changed

7 files changed

+43
-32
lines changed

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

+14-9
Original file line numberDiff line numberDiff line change
@@ -73,11 +73,12 @@ import System.IO
7373
import System.Info
7474

7575
import Control.Applicative (Alternative ((<|>)))
76-
import Control.Exception (evaluate)
7776
import Data.Void
7877

79-
import Control.Concurrent.STM (atomically)
78+
import Control.Concurrent.STM.Stats (atomically, modifyTVar',
79+
readTVar, writeTVar)
8080
import Control.Concurrent.STM.TQueue
81+
import Data.Foldable (for_)
8182
import qualified Data.HashSet as Set
8283
import Database.SQLite.Simple
8384
import Development.IDE.Core.Tracing (withTrace)
@@ -265,13 +266,17 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
265266
TargetModule _ -> do
266267
found <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
267268
return (targetTarget, found)
268-
join $ atomically $ recordDirtyKeys extras GetKnownTargets [emptyFilePath]
269-
modifyVarIO' knownTargetsVar $ traverseHashed $ \known -> do
270-
let known' = HM.unionWith (<>) known $ HM.fromList $ map (second Set.fromList) knownTargets
271-
when (known /= known') $
269+
hasUpdate <- join $ atomically $ do
270+
known <- readTVar knownTargetsVar
271+
let known' = flip mapHashed known $ \k ->
272+
HM.unionWith (<>) k $ HM.fromList $ map (second Set.fromList) knownTargets
273+
hasUpdate = if known /= known' then Just (unhashed known') else Nothing
274+
writeTVar knownTargetsVar known'
275+
logDirtyKeys <- recordDirtyKeys extras GetKnownTargets [emptyFilePath]
276+
return (logDirtyKeys >> pure hasUpdate)
277+
for_ hasUpdate $ \x ->
272278
logDebug logger $ "Known files updated: " <>
273-
T.pack(show $ (HM.map . Set.map) fromNormalizedFilePath known')
274-
pure known'
279+
T.pack(show $ (HM.map . Set.map) fromNormalizedFilePath x)
275280

276281
-- Create a new HscEnv from a hieYaml root and a set of options
277282
-- If the hieYaml file already has an HscEnv, the new component is
@@ -405,7 +410,7 @@ loadSessionWithOptions SessionLoadingOptions{..} dir = do
405410
-- update exports map
406411
extras <- getShakeExtras
407412
let !exportsMap' = createExportsMap $ mapMaybe (fmap hirModIface) modIfaces
408-
liftIO $ modifyVar_ (exportsMap extras) $ evaluate . (exportsMap' <>)
413+
liftIO $ atomically $ modifyTVar' (exportsMap extras) (exportsMap' <>)
409414

410415
return (second Map.keys res)
411416

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

+3-2
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,8 @@ 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)
28+
import Control.Concurrent.STM.Stats (atomically,
29+
modifyTVar')
2930
import qualified Data.ByteString as BS
3031
import Data.Maybe (catMaybes)
3132
import Development.IDE.Core.ProgressReporting
@@ -114,7 +115,7 @@ kick = do
114115
-- Update the exports map
115116
results <- uses GenerateCore files <* uses GetHieAst files
116117
let mguts = catMaybes results
117-
void $ liftIO $ modifyVar' exportsMap (updateExportsMapMg mguts)
118+
void $ liftIO $ atomically $ modifyTVar' exportsMap (updateExportsMapMg mguts)
118119

119120
liftIO $ progressUpdate progress KickCompleted
120121

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

+19-16
Original file line numberDiff line numberDiff line change
@@ -189,7 +189,9 @@ data ShakeExtras = ShakeExtras
189189
lspEnv :: Maybe (LSP.LanguageContextEnv Config)
190190
,debouncer :: Debouncer NormalizedUri
191191
,logger :: Logger
192-
,globals :: Var (HMap.HashMap TypeRep Dynamic)
192+
,globals :: TVar (HMap.HashMap TypeRep Dynamic)
193+
-- ^ Registry of global state used by rules.
194+
-- Small and immutable after startup, so not worth using an STM.Map.
193195
,state :: Values
194196
,diagnostics :: STMDiagnosticStore
195197
,hiddenDiagnostics :: STMDiagnosticStore
@@ -210,17 +212,18 @@ data ShakeExtras = ShakeExtras
210212
-> IO ()
211213
,ideNc :: IORef NameCache
212214
-- | A mapping of module name to known target (or candidate targets, if missing)
213-
,knownTargetsVar :: Var (Hashed KnownTargets)
215+
,knownTargetsVar :: TVar (Hashed KnownTargets)
214216
-- | A mapping of exported identifiers for local modules. Updated on kick
215-
,exportsMap :: Var ExportsMap
217+
,exportsMap :: TVar ExportsMap
216218
-- | A work queue for actions added via 'runInShakeSession'
217219
,actionQueue :: ActionQueue
218220
,clientCapabilities :: ClientCapabilities
219221
, hiedb :: HieDb -- ^ Use only to read.
220222
, hiedbWriter :: HieDbWriter -- ^ use to write
221-
, persistentKeys :: Var (HMap.HashMap Key GetStalePersistent)
223+
, persistentKeys :: TVar (HMap.HashMap Key GetStalePersistent)
222224
-- ^ Registery for functions that compute/get "stale" results for the rule
223225
-- (possibly from disk)
226+
-- Small and immutable after startup, so not worth using an STM.Map.
224227
, vfs :: VFSHandle
225228
, defaultConfig :: Config
226229
-- ^ Default HLS config, only relevant if the client does not provide any Config
@@ -258,7 +261,7 @@ getPluginConfig plugin = do
258261
addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v,PositionDelta,TextDocumentVersion))) -> Rules ()
259262
addPersistentRule k getVal = do
260263
ShakeExtras{persistentKeys} <- getShakeExtrasRules
261-
void $ liftIO $ modifyVar' persistentKeys $ HMap.insert (Key k) (fmap (fmap (first3 toDyn)) . getVal)
264+
void $ liftIO $ atomically $ modifyTVar' persistentKeys $ HMap.insert (Key k) (fmap (fmap (first3 toDyn)) . getVal)
262265

263266
class Typeable a => IsIdeGlobal a where
264267

@@ -282,15 +285,15 @@ addIdeGlobal x = do
282285

283286
addIdeGlobalExtras :: IsIdeGlobal a => ShakeExtras -> a -> IO ()
284287
addIdeGlobalExtras ShakeExtras{globals} x@(typeOf -> ty) =
285-
void $ liftIO $ modifyVarIO' globals $ \mp -> case HMap.lookup ty mp of
286-
Just _ -> errorIO $ "Internal error, addIdeGlobalExtras, got the same type twice for " ++ show ty
287-
Nothing -> return $! HMap.insert ty (toDyn x) mp
288+
void $ liftIO $ atomically $ modifyTVar' globals $ \mp -> case HMap.lookup ty mp of
289+
Just _ -> error $ "Internal error, addIdeGlobalExtras, got the same type twice for " ++ show ty
290+
Nothing -> HMap.insert ty (toDyn x) mp
288291

289292

290293
getIdeGlobalExtras :: forall a . IsIdeGlobal a => ShakeExtras -> IO a
291294
getIdeGlobalExtras ShakeExtras{globals} = do
292295
let typ = typeRep (Proxy :: Proxy a)
293-
x <- HMap.lookup (typeRep (Proxy :: Proxy a)) <$> readVar globals
296+
x <- HMap.lookup (typeRep (Proxy :: Proxy a)) <$> readTVarIO globals
294297
case x of
295298
Just x
296299
| Just x <- fromDynamic x -> pure x
@@ -333,7 +336,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
333336
| IdeTesting testing <- ideTesting s -- Don't read stale persistent values in tests
334337
, testing = pure Nothing
335338
| otherwise = do
336-
pmap <- readVar persistentKeys
339+
pmap <- readTVarIO persistentKeys
337340
mv <- runMaybeT $ do
338341
liftIO $ Logger.logDebug (logger s) $ T.pack $ "LOOKUP UP PERSISTENT FOR: " ++ show k
339342
f <- MaybeT $ pure $ HMap.lookup (Key k) pmap
@@ -477,7 +480,7 @@ getValues state key file = do
477480
knownTargets :: Action (Hashed KnownTargets)
478481
knownTargets = do
479482
ShakeExtras{knownTargetsVar} <- getShakeExtras
480-
liftIO $ readVar knownTargetsVar
483+
liftIO $ readTVarIO knownTargetsVar
481484

482485
-- | Seq the result stored in the Shake value. This only
483486
-- evaluates the value to WHNF not NF. We take care of the latter
@@ -508,25 +511,25 @@ shakeOpen lspEnv defaultConfig logger debouncer
508511
us <- mkSplitUniqSupply 'r'
509512
ideNc <- newIORef (initNameCache us knownKeyNames)
510513
shakeExtras <- do
511-
globals <- newVar HMap.empty
514+
globals <- newTVarIO HMap.empty
512515
state <- STM.newIO
513516
diagnostics <- STM.newIO
514517
hiddenDiagnostics <- STM.newIO
515518
publishedDiagnostics <- STM.newIO
516519
positionMapping <- STM.newIO
517-
knownTargetsVar <- newVar $ hashed HMap.empty
520+
knownTargetsVar <- newTVarIO $ hashed HMap.empty
518521
let restartShakeSession = shakeRestart ideState
519-
persistentKeys <- newVar HMap.empty
522+
persistentKeys <- newTVarIO HMap.empty
520523
indexPending <- newTVarIO HMap.empty
521524
indexCompleted <- newTVarIO 0
522525
indexProgressToken <- newVar Nothing
523526
let hiedbWriter = HieDbWriter{..}
524-
exportsMap <- newVar mempty
527+
exportsMap <- newTVarIO mempty
525528
-- lazily initialize the exports map with the contents of the hiedb
526529
_ <- async $ do
527530
logDebug logger "Initializing exports map from hiedb"
528531
em <- createExportsMapHieDb hiedb
529-
_ <- modifyVar' exportsMap (<> em)
532+
atomically $ modifyTVar' exportsMap (<> em)
530533
logDebug logger $ "Done initializing exports map from hiedb (" <> pack(show (ExportsMap.size em)) <> ")"
531534

532535
progress <- do

ghcide/src/Development/IDE/Plugin/CodeAction/Args.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ module Development.IDE.Plugin.CodeAction.Args
1414
)
1515
where
1616

17-
import Control.Concurrent.Extra
17+
import Control.Concurrent.STM.Stats (readTVarIO)
1818
import Control.Monad.Reader
1919
import Control.Monad.Trans.Maybe
2020
import Data.Either (fromRight)
@@ -59,7 +59,7 @@ runGhcideCodeAction state (CodeActionParams _ _ (TextDocumentIdentifier uri) _ra
5959
runRule GhcSession >>= \case
6060
Just env -> do
6161
pkgExports <- envPackageExports env
62-
localExports <- readVar (exportsMap $ shakeExtras state)
62+
localExports <- readTVarIO (exportsMap $ shakeExtras state)
6363
pure $ localExports <> pkgExports
6464
_ -> pure mempty
6565
caaIdeOptions <- onceIO $ runAction "GhcideCodeActions.getIdeOptions" state getIdeOptions

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

+2-2
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module Development.IDE.Plugin.Completions
88
) where
99

1010
import Control.Concurrent.Async (concurrently)
11-
import Control.Concurrent.Extra
11+
import Control.Concurrent.STM.Stats (readTVarIO)
1212
import Control.Monad.Extra
1313
import Control.Monad.IO.Class
1414
import Control.Monad.Trans.Maybe
@@ -138,7 +138,7 @@ getCompletionsLSP ide plId
138138
-- set up the exports map including both package and project-level identifiers
139139
packageExportsMapIO <- fmap(envPackageExports . fst) <$> useWithStaleFast GhcSession npath
140140
packageExportsMap <- mapM liftIO packageExportsMapIO
141-
projectExportsMap <- liftIO $ readVar (exportsMap $ shakeExtras ide)
141+
projectExportsMap <- liftIO $ readTVarIO (exportsMap $ shakeExtras ide)
142142
let exportsMap = fromMaybe mempty packageExportsMap <> projectExportsMap
143143

144144
let moduleExports = getModuleExportsMap exportsMap

plugins/hls-retrie-plugin/hls-retrie-plugin.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ library
3030
, lsp-types
3131
, retrie >=0.1.1.0
3232
, safe-exceptions
33+
, stm
3334
, text
3435
, transformers
3536
, unordered-containers

plugins/hls-retrie-plugin/src/Ide/Plugin/Retrie.hs

+2-1
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@
1717
module Ide.Plugin.Retrie (descriptor) where
1818

1919
import Control.Concurrent.Extra (readVar)
20+
import Control.Concurrent.STM (readTVarIO)
2021
import Control.Exception.Safe (Exception (..),
2122
SomeException, catch,
2223
throwIO, try)
@@ -356,7 +357,7 @@ callRetrie ::
356357
Bool ->
357358
IO ([CallRetrieError], WorkspaceEdit)
358359
callRetrie state session rewrites origin restrictToOriginatingFile = do
359-
knownFiles <- toKnownFiles . unhashed <$> readVar (knownTargetsVar $ shakeExtras state)
360+
knownFiles <- toKnownFiles . unhashed <$> readTVarIO (knownTargetsVar $ shakeExtras state)
360361
let reuseParsedModule f = do
361362
pm <-
362363
useOrFail "GetParsedModule" NoParse GetParsedModule f

0 commit comments

Comments
 (0)