Skip to content

Commit a83c850

Browse files
pepeiborrajneiramergify[bot]
authored
Lockless FileExistsMap and position mapping (#2442)
* lock-less position mapping * lock-less FileExistsMap * Move to STM Co-authored-by: Javier Neira <[email protected]> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 85b51c4 commit a83c850

File tree

3 files changed

+45
-44
lines changed

3 files changed

+45
-44
lines changed

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

Lines changed: 19 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -10,14 +10,12 @@ module Development.IDE.Core.FileExists
1010
)
1111
where
1212

13-
import Control.Concurrent.STM.Stats
14-
import Control.Concurrent.Strict
13+
import Control.Concurrent.STM.Stats (atomically,
14+
atomicallyNamed)
1515
import Control.Exception
1616
import Control.Monad.Extra
1717
import Control.Monad.IO.Class
1818
import qualified Data.ByteString as BS
19-
import Data.HashMap.Strict (HashMap)
20-
import qualified Data.HashMap.Strict as HashMap
2119
import Data.List (partition)
2220
import Data.Maybe
2321
import Development.IDE.Core.FileStore
@@ -27,9 +25,11 @@ import Development.IDE.Core.Shake
2725
import Development.IDE.Graph
2826
import Development.IDE.Types.Location
2927
import Development.IDE.Types.Options
28+
import qualified Focus
3029
import Ide.Plugin.Config (Config)
3130
import Language.LSP.Server hiding (getVirtualFile)
3231
import Language.LSP.Types
32+
import qualified StmContainers.Map as STM
3333
import qualified System.Directory as Dir
3434
import qualified System.FilePath.Glob as Glob
3535

@@ -75,37 +75,38 @@ fast path by a check that the path also matches our watching patterns.
7575
-- | A map for tracking the file existence.
7676
-- If a path maps to 'True' then it exists; if it maps to 'False' then it doesn't exist'; and
7777
-- if it's not in the map then we don't know.
78-
type FileExistsMap = (HashMap NormalizedFilePath Bool)
78+
type FileExistsMap = STM.Map NormalizedFilePath Bool
7979

8080
-- | A wrapper around a mutable 'FileExistsState'
81-
newtype FileExistsMapVar = FileExistsMapVar (Var FileExistsMap)
81+
newtype FileExistsMapVar = FileExistsMapVar FileExistsMap
8282

8383
instance IsIdeGlobal FileExistsMapVar
8484

8585
-- | Grab the current global value of 'FileExistsMap' without acquiring a dependency
8686
getFileExistsMapUntracked :: Action FileExistsMap
8787
getFileExistsMapUntracked = do
8888
FileExistsMapVar v <- getIdeGlobalAction
89-
liftIO $ readVar v
89+
return v
9090

9191
-- | Modify the global store of file exists.
9292
modifyFileExists :: IdeState -> [(NormalizedFilePath, FileChangeType)] -> IO ()
9393
modifyFileExists state changes = do
9494
FileExistsMapVar var <- getIdeGlobalState state
95-
changesMap <- evaluate $ HashMap.fromList changes
9695
-- Masked to ensure that the previous values are flushed together with the map update
97-
mask $ \_ -> do
9896
-- update the map
99-
void $ modifyVar' var $ HashMap.union (HashMap.mapMaybe fromChange changesMap)
97+
mask_ $ join $ atomicallyNamed "modifyFileExists" $ do
98+
forM_ changes $ \(f,c) ->
99+
case fromChange c of
100+
Just c' -> STM.focus (Focus.insert c') f var
101+
Nothing -> pure ()
100102
-- See Note [Invalidating file existence results]
101103
-- flush previous values
102104
let (fileModifChanges, fileExistChanges) =
103-
partition ((== FcChanged) . snd) (HashMap.toList changesMap)
104-
join $ atomically $ do
105-
mapM_ (deleteValue (shakeExtras state) GetFileExists . fst) fileExistChanges
106-
io1 <- recordDirtyKeys (shakeExtras state) GetFileExists $ map fst fileExistChanges
107-
io2 <- recordDirtyKeys (shakeExtras state) GetModificationTime $ map fst fileModifChanges
108-
return (io1 <> io2)
105+
partition ((== FcChanged) . snd) changes
106+
mapM_ (deleteValue (shakeExtras state) GetFileExists . fst) fileExistChanges
107+
io1 <- recordDirtyKeys (shakeExtras state) GetFileExists $ map fst fileExistChanges
108+
io2 <- recordDirtyKeys (shakeExtras state) GetModificationTime $ map fst fileModifChanges
109+
return (io1 <> io2)
109110

110111
fromChange :: FileChangeType -> Maybe Bool
111112
fromChange FcCreated = Just True
@@ -164,7 +165,7 @@ fileExistsRules lspEnv vfs = do
164165
-- Create the global always, although it should only be used if we have fast rules.
165166
-- But there's a chance someone will send unexpected notifications anyway,
166167
-- e.g. https://github.com/haskell/ghcide/issues/599
167-
addIdeGlobal . FileExistsMapVar =<< liftIO (newVar [])
168+
addIdeGlobal . FileExistsMapVar =<< liftIO STM.newIO
168169

169170
extras <- getShakeExtrasRules
170171
opts <- liftIO $ getIdeOptionsIO extras
@@ -213,7 +214,7 @@ fileExistsFast vfs file = do
213214
-- Could in principle use 'alwaysRerun' here, but it's too slwo, See Note [Invalidating file existence results]
214215
mp <- getFileExistsMapUntracked
215216

216-
let mbFilesWatched = HashMap.lookup file mp
217+
mbFilesWatched <- liftIO $ atomically $ STM.lookup file mp
217218
exist <- case mbFilesWatched of
218219
Just exist -> pure exist
219220
-- We don't know about it: use the slow route.

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

Lines changed: 23 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -196,7 +196,7 @@ data ShakeExtras = ShakeExtras
196196
,publishedDiagnostics :: STM.Map NormalizedUri [Diagnostic]
197197
-- ^ This represents the set of diagnostics that we have published.
198198
-- 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))
200200
-- ^ Map from a text document version to a PositionMapping that describes how to map
201201
-- positions in a version of that document to positions in the latest version
202202
-- First mapping is delta from previous version and second one is an
@@ -328,7 +328,6 @@ getIdeOptionsIO ide = do
328328
-- for the version of that value.
329329
lastValueIO :: IdeRule k v => ShakeExtras -> k -> NormalizedFilePath -> IO (Maybe (v, PositionMapping))
330330
lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
331-
allMappings <- readVar positionMapping
332331

333332
let readPersistent
334333
| 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
340339
f <- MaybeT $ pure $ HMap.lookup (Key k) pmap
341340
(dv,del,ver) <- MaybeT $ runIdeAction "lastValueIO" s $ f file
342341
MaybeT $ pure $ (,del,ver) <$> fromDynamic dv
343-
case mv of
342+
atomically $ case mv of
344343
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
346345
return Nothing
347346
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
350349

351350
-- We got a new stale value from the persistent rule, insert it in the map without affecting diagnostics
352351
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
359358
atomically (STM.lookup (toKey k file) state) >>= \case
360359
Nothing -> readPersistent
361360
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
364365
Failed p | not p -> readPersistent
365366
_ -> pure Nothing
366367

@@ -372,14 +373,13 @@ lastValue key file = do
372373
liftIO $ lastValueIO s key file
373374

374375
mappingForVersion
375-
:: HMap.HashMap NormalizedUri (Map TextDocumentVersion (a, PositionMapping))
376+
:: STM.Map NormalizedUri (Map TextDocumentVersion (a, PositionMapping))
376377
-> NormalizedFilePath
377378
-> 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
383383

384384
type IdeRule k v =
385385
( Shake.RuleResult k ~ v
@@ -513,7 +513,7 @@ shakeOpen lspEnv defaultConfig logger debouncer
513513
diagnostics <- STM.newIO
514514
hiddenDiagnostics <- STM.newIO
515515
publishedDiagnostics <- STM.newIO
516-
positionMapping <- newVar HMap.empty
516+
positionMapping <- STM.newIO
517517
knownTargetsVar <- newVar $ hashed HMap.empty
518518
let restartShakeSession = shakeRestart ideState
519519
persistentKeys <- newVar HMap.empty
@@ -1222,18 +1222,17 @@ getAllDiagnostics ::
12221222
getAllDiagnostics =
12231223
fmap (concatMap (\(k,v) -> map (fromUri k,ShowDiag,) $ getDiagnosticsFromStore v)) . ListT.toList . STM.listT
12241224

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 $
12311232
-- Very important to use mapAccum here so that the tails of
12321233
-- each mapping can be shared, otherwise quadratic space is
12331234
-- used which is evident in long running sessions.
12341235
Map.mapAccumRWithKey (\acc _k (delta, _) -> let new = addDelta delta acc in (new, (delta, acc)))
12351236
zeroMapping
12361237
(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

ghcide/src/Development/IDE/LSP/Notifications.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Development.IDE.LSP.Notifications
1414
import Language.LSP.Types
1515
import qualified Language.LSP.Types as LSP
1616

17+
import Control.Concurrent.STM.Stats (atomically)
1718
import Control.Monad.Extra
1819
import Control.Monad.IO.Class
1920
import qualified Data.HashMap.Strict as HM
@@ -42,7 +43,7 @@ descriptor :: PluginId -> PluginDescriptor IdeState
4243
descriptor plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers = mconcat
4344
[ mkPluginNotificationHandler LSP.STextDocumentDidOpen $
4445
\ide _ (DidOpenTextDocumentParams TextDocumentItem{_uri,_version}) -> liftIO $ do
45-
updatePositionMapping ide (VersionedTextDocumentIdentifier _uri (Just _version)) (List [])
46+
atomically $ updatePositionMapping ide (VersionedTextDocumentIdentifier _uri (Just _version)) (List [])
4647
whenUriFile _uri $ \file -> do
4748
-- We don't know if the file actually exists, or if the contents match those on disk
4849
-- For example, vscode restores previously unsaved contents on open
@@ -52,7 +53,7 @@ descriptor plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers =
5253

5354
, mkPluginNotificationHandler LSP.STextDocumentDidChange $
5455
\ide _ (DidChangeTextDocumentParams identifier@VersionedTextDocumentIdentifier{_uri} changes) -> liftIO $ do
55-
updatePositionMapping ide identifier changes
56+
atomically $ updatePositionMapping ide identifier changes
5657
whenUriFile _uri $ \file -> do
5758
addFileOfInterest ide file Modified{firstOpen=False}
5859
setFileModified ide False file

0 commit comments

Comments
 (0)