@@ -196,7 +196,7 @@ data ShakeExtras = ShakeExtras
196
196
,publishedDiagnostics :: STM. Map NormalizedUri [Diagnostic ]
197
197
-- ^ This represents the set of diagnostics that we have published.
198
198
-- Due to debouncing not every change might get published.
199
- ,positionMapping :: Var ( HMap. HashMap NormalizedUri (Map TextDocumentVersion (PositionDelta , PositionMapping ) ))
199
+ ,positionMapping :: STM. Map NormalizedUri (Map TextDocumentVersion (PositionDelta , PositionMapping ))
200
200
-- ^ Map from a text document version to a PositionMapping that describes how to map
201
201
-- positions in a version of that document to positions in the latest version
202
202
-- First mapping is delta from previous version and second one is an
@@ -328,7 +328,6 @@ getIdeOptionsIO ide = do
328
328
-- for the version of that value.
329
329
lastValueIO :: IdeRule k v => ShakeExtras -> k -> NormalizedFilePath -> IO (Maybe (v , PositionMapping ))
330
330
lastValueIO s@ ShakeExtras {positionMapping,persistentKeys,state} k file = do
331
- allMappings <- readVar positionMapping
332
331
333
332
let readPersistent
334
333
| IdeTesting testing <- ideTesting s -- Don't read stale persistent values in tests
@@ -340,13 +339,13 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
340
339
f <- MaybeT $ pure $ HMap. lookup (Key k) pmap
341
340
(dv,del,ver) <- MaybeT $ runIdeAction " lastValueIO" s $ f file
342
341
MaybeT $ pure $ (,del,ver) <$> fromDynamic dv
343
- case mv of
342
+ atomically $ case mv of
344
343
Nothing -> do
345
- void $ atomically $ STM. focus (Focus. alter (alterValue $ Failed True )) (toKey k file) state
344
+ STM. focus (Focus. alter (alterValue $ Failed True )) (toKey k file) state
346
345
return Nothing
347
346
Just (v,del,ver) -> do
348
- void $ atomically $ STM. focus (Focus. alter (alterValue $ Stale (Just del) ver (toDyn v))) (toKey k file) state
349
- return $ Just (v,addDelta del $ mappingForVersion allMappings file ver)
347
+ STM. focus (Focus. alter (alterValue $ Stale (Just del) ver (toDyn v))) (toKey k file) state
348
+ Just . (v,) . addDelta del <$> mappingForVersion positionMapping file ver
350
349
351
350
-- We got a new stale value from the persistent rule, insert it in the map without affecting diagnostics
352
351
alterValue new Nothing = Just (ValueWithDiagnostics new mempty ) -- If it wasn't in the map, give it empty diagnostics
@@ -359,8 +358,10 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
359
358
atomically (STM. lookup (toKey k file) state) >>= \ case
360
359
Nothing -> readPersistent
361
360
Just (ValueWithDiagnostics v _) -> case v of
362
- Succeeded ver (fromDynamic -> Just v) -> pure (Just (v, mappingForVersion allMappings file ver))
363
- Stale del ver (fromDynamic -> Just v) -> pure (Just (v, maybe id addDelta del $ mappingForVersion allMappings file ver))
361
+ Succeeded ver (fromDynamic -> Just v) ->
362
+ atomically $ Just . (v,) <$> mappingForVersion positionMapping file ver
363
+ Stale del ver (fromDynamic -> Just v) ->
364
+ atomically $ Just . (v,) . maybe id addDelta del <$> mappingForVersion positionMapping file ver
364
365
Failed p | not p -> readPersistent
365
366
_ -> pure Nothing
366
367
@@ -372,14 +373,13 @@ lastValue key file = do
372
373
liftIO $ lastValueIO s key file
373
374
374
375
mappingForVersion
375
- :: HMap. HashMap NormalizedUri (Map TextDocumentVersion (a , PositionMapping ))
376
+ :: STM. Map NormalizedUri (Map TextDocumentVersion (a , PositionMapping ))
376
377
-> NormalizedFilePath
377
378
-> TextDocumentVersion
378
- -> PositionMapping
379
- mappingForVersion allMappings file ver =
380
- maybe zeroMapping snd $
381
- Map. lookup ver =<<
382
- HMap. lookup (filePathToUri' file) allMappings
379
+ -> STM PositionMapping
380
+ mappingForVersion allMappings file ver = do
381
+ mapping <- STM. lookup (filePathToUri' file) allMappings
382
+ return $ maybe zeroMapping snd $ Map. lookup ver =<< mapping
383
383
384
384
type IdeRule k v =
385
385
( Shake. RuleResult k ~ v
@@ -513,7 +513,7 @@ shakeOpen lspEnv defaultConfig logger debouncer
513
513
diagnostics <- STM. newIO
514
514
hiddenDiagnostics <- STM. newIO
515
515
publishedDiagnostics <- STM. newIO
516
- positionMapping <- newVar HMap. empty
516
+ positionMapping <- STM. newIO
517
517
knownTargetsVar <- newVar $ hashed HMap. empty
518
518
let restartShakeSession = shakeRestart ideState
519
519
persistentKeys <- newVar HMap. empty
@@ -1222,18 +1222,17 @@ getAllDiagnostics ::
1222
1222
getAllDiagnostics =
1223
1223
fmap (concatMap (\ (k,v) -> map (fromUri k,ShowDiag ,) $ getDiagnosticsFromStore v)) . ListT. toList . STM. listT
1224
1224
1225
- updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> List TextDocumentContentChangeEvent -> IO ()
1226
- updatePositionMapping IdeState {shakeExtras = ShakeExtras {positionMapping}} VersionedTextDocumentIdentifier {.. } (List changes) = do
1227
- modifyVar_ positionMapping $ \ allMappings -> do
1228
- let uri = toNormalizedUri _uri
1229
- let mappingForUri = HMap. lookupDefault Map. empty uri allMappings
1230
- let (_, updatedMapping) =
1225
+ updatePositionMapping :: IdeState -> VersionedTextDocumentIdentifier -> List TextDocumentContentChangeEvent -> STM ()
1226
+ updatePositionMapping IdeState {shakeExtras = ShakeExtras {positionMapping}} VersionedTextDocumentIdentifier {.. } (List changes) =
1227
+ STM. focus (Focus. alter f) uri positionMapping
1228
+ where
1229
+ uri = toNormalizedUri _uri
1230
+ f = Just . f' . fromMaybe mempty
1231
+ f' mappingForUri = snd $
1231
1232
-- Very important to use mapAccum here so that the tails of
1232
1233
-- each mapping can be shared, otherwise quadratic space is
1233
1234
-- used which is evident in long running sessions.
1234
1235
Map. mapAccumRWithKey (\ acc _k (delta, _) -> let new = addDelta delta acc in (new, (delta, acc)))
1235
1236
zeroMapping
1236
1237
(Map. insert _version (shared_change, zeroMapping) mappingForUri)
1237
- pure $ HMap. insert uri updatedMapping allMappings
1238
- where
1239
- shared_change = mkDelta changes
1238
+ shared_change = mkDelta changes
0 commit comments