@@ -189,7 +189,9 @@ data ShakeExtras = ShakeExtras
189
189
lspEnv :: Maybe (LSP. LanguageContextEnv Config )
190
190
,debouncer :: Debouncer NormalizedUri
191
191
,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.
193
195
,state :: Values
194
196
,diagnostics :: STMDiagnosticStore
195
197
,hiddenDiagnostics :: STMDiagnosticStore
@@ -210,17 +212,18 @@ data ShakeExtras = ShakeExtras
210
212
-> IO ()
211
213
,ideNc :: IORef NameCache
212
214
-- | A mapping of module name to known target (or candidate targets, if missing)
213
- ,knownTargetsVar :: Var (Hashed KnownTargets )
215
+ ,knownTargetsVar :: TVar (Hashed KnownTargets )
214
216
-- | A mapping of exported identifiers for local modules. Updated on kick
215
- ,exportsMap :: Var ExportsMap
217
+ ,exportsMap :: TVar ExportsMap
216
218
-- | A work queue for actions added via 'runInShakeSession'
217
219
,actionQueue :: ActionQueue
218
220
,clientCapabilities :: ClientCapabilities
219
221
, hiedb :: HieDb -- ^ Use only to read.
220
222
, hiedbWriter :: HieDbWriter -- ^ use to write
221
- , persistentKeys :: Var (HMap. HashMap Key GetStalePersistent )
223
+ , persistentKeys :: TVar (HMap. HashMap Key GetStalePersistent )
222
224
-- ^ Registery for functions that compute/get "stale" results for the rule
223
225
-- (possibly from disk)
226
+ -- Small and immutable after startup, so not worth using an STM.Map.
224
227
, vfs :: VFSHandle
225
228
, defaultConfig :: Config
226
229
-- ^ Default HLS config, only relevant if the client does not provide any Config
@@ -258,7 +261,7 @@ getPluginConfig plugin = do
258
261
addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v ,PositionDelta ,TextDocumentVersion ))) -> Rules ()
259
262
addPersistentRule k getVal = do
260
263
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)
262
265
263
266
class Typeable a => IsIdeGlobal a where
264
267
@@ -282,15 +285,15 @@ addIdeGlobal x = do
282
285
283
286
addIdeGlobalExtras :: IsIdeGlobal a => ShakeExtras -> a -> IO ()
284
287
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
288
291
289
292
290
293
getIdeGlobalExtras :: forall a . IsIdeGlobal a => ShakeExtras -> IO a
291
294
getIdeGlobalExtras ShakeExtras {globals} = do
292
295
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
294
297
case x of
295
298
Just x
296
299
| Just x <- fromDynamic x -> pure x
@@ -333,7 +336,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
333
336
| IdeTesting testing <- ideTesting s -- Don't read stale persistent values in tests
334
337
, testing = pure Nothing
335
338
| otherwise = do
336
- pmap <- readVar persistentKeys
339
+ pmap <- readTVarIO persistentKeys
337
340
mv <- runMaybeT $ do
338
341
liftIO $ Logger. logDebug (logger s) $ T. pack $ " LOOKUP UP PERSISTENT FOR: " ++ show k
339
342
f <- MaybeT $ pure $ HMap. lookup (Key k) pmap
@@ -477,7 +480,7 @@ getValues state key file = do
477
480
knownTargets :: Action (Hashed KnownTargets )
478
481
knownTargets = do
479
482
ShakeExtras {knownTargetsVar} <- getShakeExtras
480
- liftIO $ readVar knownTargetsVar
483
+ liftIO $ readTVarIO knownTargetsVar
481
484
482
485
-- | Seq the result stored in the Shake value. This only
483
486
-- evaluates the value to WHNF not NF. We take care of the latter
@@ -508,25 +511,25 @@ shakeOpen lspEnv defaultConfig logger debouncer
508
511
us <- mkSplitUniqSupply ' r'
509
512
ideNc <- newIORef (initNameCache us knownKeyNames)
510
513
shakeExtras <- do
511
- globals <- newVar HMap. empty
514
+ globals <- newTVarIO HMap. empty
512
515
state <- STM. newIO
513
516
diagnostics <- STM. newIO
514
517
hiddenDiagnostics <- STM. newIO
515
518
publishedDiagnostics <- STM. newIO
516
519
positionMapping <- STM. newIO
517
- knownTargetsVar <- newVar $ hashed HMap. empty
520
+ knownTargetsVar <- newTVarIO $ hashed HMap. empty
518
521
let restartShakeSession = shakeRestart ideState
519
- persistentKeys <- newVar HMap. empty
522
+ persistentKeys <- newTVarIO HMap. empty
520
523
indexPending <- newTVarIO HMap. empty
521
524
indexCompleted <- newTVarIO 0
522
525
indexProgressToken <- newVar Nothing
523
526
let hiedbWriter = HieDbWriter {.. }
524
- exportsMap <- newVar mempty
527
+ exportsMap <- newTVarIO mempty
525
528
-- lazily initialize the exports map with the contents of the hiedb
526
529
_ <- async $ do
527
530
logDebug logger " Initializing exports map from hiedb"
528
531
em <- createExportsMapHieDb hiedb
529
- _ <- modifyVar ' exportsMap (<> em)
532
+ atomically $ modifyTVar ' exportsMap (<> em)
530
533
logDebug logger $ " Done initializing exports map from hiedb (" <> pack(show (ExportsMap. size em)) <> " )"
531
534
532
535
progress <- do
0 commit comments