Skip to content

Commit 527b650

Browse files
committed
Track closed files in the VFS
Add data structure which represents a closed file in the VFS. This structure only stores the language kind of the closed file as of now. The VFS now stores VFS entries which can be either open or closed files.
1 parent 81f8b94 commit 527b650

File tree

4 files changed

+58
-14
lines changed

4 files changed

+58
-14
lines changed

lsp-test/src/Language/LSP/Test.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -371,7 +371,7 @@ envOverrideConfig cfg = do
371371
documentContents :: TextDocumentIdentifier -> Session T.Text
372372
documentContents doc = do
373373
vfs <- vfs <$> get
374-
let Just file = vfs ^. vfsMap . at (toNormalizedUri (doc ^. L.uri))
374+
let Just file = vfs ^? vfsMap . ix (toNormalizedUri (doc ^. L.uri)) . _Open
375375
return (virtualFileText file)
376376

377377
{- | Parses an ApplyEditRequest, checks that it is for the passed document
@@ -801,7 +801,7 @@ resolveAndExecuteCodeAction ca = executeCodeAction ca
801801
getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier
802802
getVersionedDoc (TextDocumentIdentifier uri) = do
803803
vfs <- vfs <$> get
804-
let ver = vfs ^? vfsMap . ix (toNormalizedUri uri) . to virtualFileVersion
804+
let ver = vfs ^? vfsMap . ix (toNormalizedUri uri) . _Open . to virtualFileVersion
805805
-- TODO: is this correct? Could return an OptionalVersionedTextDocumentIdentifier,
806806
-- but that complicated callers...
807807
return (VersionedTextDocumentIdentifier uri (fromMaybe 0 ver))

lsp-test/src/Language/LSP/Test/Session.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -446,7 +446,7 @@ updateState (FromServerMess SMethod_WorkspaceApplyEdit r) = do
446446
modify $ \s ->
447447
let oldVFS = vfs s
448448
update (VirtualFile _ file_ver t _kind) = VirtualFile v (file_ver +1) t _kind
449-
newVFS = oldVFS & vfsMap . ix (toNormalizedUri uri) %~ update
449+
newVFS = oldVFS & vfsMap . ix (toNormalizedUri uri) . _Open %~ update
450450
in s { vfs = newVFS }
451451

452452
where
@@ -486,7 +486,7 @@ updateState (FromServerMess SMethod_WorkspaceApplyEdit r) = do
486486
-- where n is the current version
487487
textDocumentVersions uri = do
488488
vfs <- vfs <$> get
489-
let curVer = fromMaybe 0 $ vfs ^? vfsMap . ix (toNormalizedUri uri) . lsp_version
489+
let curVer = fromMaybe 0 $ vfs ^? vfsMap . ix (toNormalizedUri uri) . _Open . lsp_version
490490
pure $ map (VersionedTextDocumentIdentifier uri) [curVer + 1..]
491491

492492
textDocumentEdits uri edits = do

lsp/src/Language/LSP/Server/Core.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ import Colog.Core (
2121
)
2222
import Control.Concurrent.Extra as C
2323
import Control.Concurrent.STM
24-
import Control.Lens (at, (^.), (^?), _Just)
24+
import Control.Lens (ix, (^.), (^?), _Just)
2525
import Control.Monad
2626
import Control.Monad.Catch (
2727
MonadCatch,
@@ -433,7 +433,7 @@ sendRequest m params resHandler = do
433433
getVirtualFile :: MonadLsp config m => NormalizedUri -> m (Maybe VirtualFile)
434434
getVirtualFile uri = do
435435
dat <- vfsData <$> getsState resVFS
436-
pure $ dat ^. vfsMap . at uri
436+
pure $ dat ^? vfsMap . ix uri . _Open
437437
{-# INLINE getVirtualFile #-}
438438

439439
getVirtualFiles :: MonadLsp config m => m VFS

lsp/src/Language/LSP/VFS.hs

Lines changed: 52 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -18,12 +18,19 @@ module Language.LSP.VFS (
1818
VFS (..),
1919
vfsMap,
2020
VirtualFile (..),
21+
ClosedVirtualFile (..),
22+
VirtualFileEntry (..),
2123
lsp_version,
2224
file_version,
2325
file_text,
26+
language_id,
27+
_Open,
28+
_Closed,
2429
virtualFileText,
2530
virtualFileVersion,
2631
virtualFileLanguageKind,
32+
closedVirtualFileLanguageKind,
33+
virtualFileEntryLanguageKind,
2734
VfsLog (..),
2835

2936
-- * Managing the VFS
@@ -102,13 +109,27 @@ data VirtualFile = VirtualFile
102109
}
103110
deriving (Show)
104111

112+
{- | Represents a closed file in the VFS
113+
We are keeping track of this in order to be able to get information
114+
on virtual files after they were closed.
115+
-}
116+
data ClosedVirtualFile = ClosedVirtualFile
117+
{ _language_id :: !(Maybe J.LanguageKind)
118+
-- ^ see 'VirtualFile._language_id'
119+
}
120+
deriving (Show)
121+
122+
data VirtualFileEntry = Open VirtualFile | Closed ClosedVirtualFile
123+
deriving (Show)
124+
105125
data VFS = VFS
106-
{ _vfsMap :: !(Map.Map J.NormalizedUri VirtualFile)
126+
{ _vfsMap :: !(Map.Map J.NormalizedUri VirtualFileEntry)
107127
}
108128
deriving (Show)
109129

110130
data VfsLog
111131
= SplitInsideCodePoint Utf16.Position Rope
132+
| ApplyChangeToClosedFile J.NormalizedUri
112133
| URINotFound J.NormalizedUri
113134
| Opening J.NormalizedUri
114135
| Closing J.NormalizedUri
@@ -120,6 +141,7 @@ data VfsLog
120141
instance Pretty VfsLog where
121142
pretty (SplitInsideCodePoint pos r) =
122143
"VFS: asked to make change inside code point. Position" <+> viaShow pos <+> "in" <+> viaShow r
144+
pretty (ApplyChangeToClosedFile uri) = "VFS: trying to apply a change to a closed file" <+> pretty uri
123145
pretty (URINotFound uri) = "VFS: don't know about URI" <+> pretty uri
124146
pretty (Opening uri) = "VFS: opening" <+> pretty uri
125147
pretty (Closing uri) = "VFS: closing" <+> pretty uri
@@ -129,7 +151,9 @@ instance Pretty VfsLog where
129151
pretty (DeleteNonExistent uri) = "VFS: asked to delete non-existent file" <+> pretty uri
130152

131153
makeFieldsNoPrefix ''VirtualFile
154+
makeFieldsNoPrefix ''ClosedVirtualFile
132155
makeFieldsNoPrefix ''VFS
156+
makePrisms ''VirtualFileEntry
133157

134158
---
135159

@@ -140,7 +164,20 @@ virtualFileVersion :: VirtualFile -> Int32
140164
virtualFileVersion vf = _lsp_version vf
141165

142166
virtualFileLanguageKind :: VirtualFile -> Maybe J.LanguageKind
143-
virtualFileLanguageKind vf = _language_id vf
167+
virtualFileLanguageKind vf = vf ^. language_id
168+
169+
closedVirtualFileLanguageKind :: ClosedVirtualFile -> Maybe J.LanguageKind
170+
closedVirtualFileLanguageKind vf = vf ^. language_id
171+
172+
virtualFileEntryLanguageKind :: VirtualFileEntry -> Maybe J.LanguageKind
173+
virtualFileEntryLanguageKind (Open vf) = virtualFileLanguageKind vf
174+
virtualFileEntryLanguageKind (Closed vf) = closedVirtualFileLanguageKind vf
175+
176+
toClosedVirtualFile :: VirtualFile -> ClosedVirtualFile
177+
toClosedVirtualFile vf =
178+
ClosedVirtualFile
179+
{ _language_id = virtualFileLanguageKind vf
180+
}
144181

145182
---
146183

@@ -155,7 +192,7 @@ openVFS logger msg = do
155192
let J.TextDocumentItem (J.toNormalizedUri -> uri) languageId version text = msg ^. J.params . J.textDocument
156193
vfile = VirtualFile version 0 (Rope.fromText text) (Just languageId)
157194
logger <& Opening uri `WithSeverity` Debug
158-
vfsMap . at uri .= Just vfile
195+
vfsMap . at uri .= (Just $ Open vfile)
159196

160197
-- ---------------------------------------------------------------------
161198

@@ -168,9 +205,10 @@ changeFromClientVFS logger msg = do
168205
J.VersionedTextDocumentIdentifier (J.toNormalizedUri -> uri) version = vid
169206
vfs <- get
170207
case vfs ^. vfsMap . at uri of
171-
Just (VirtualFile _ file_ver contents kind) -> do
208+
Just (Open (VirtualFile _ file_ver contents kind)) -> do
172209
contents' <- applyChanges logger contents changes
173-
vfsMap . at uri .= Just (VirtualFile version (file_ver + 1) contents' kind)
210+
vfsMap . at uri .= Just (Open (VirtualFile version (file_ver + 1) contents' kind))
211+
Just (Closed (ClosedVirtualFile _)) -> logger <& ApplyChangeToClosedFile uri `WithSeverity` Warning
174212
Nothing -> logger <& URINotFound uri `WithSeverity` Warning
175213

176214
-- ---------------------------------------------------------------------
@@ -181,7 +219,7 @@ applyCreateFile (J.CreateFile _ann _kind (J.toNormalizedUri -> uri) options) =
181219
%= Map.insertWith
182220
(\new old -> if shouldOverwrite then new else old)
183221
uri
184-
(VirtualFile 0 0 mempty Nothing)
222+
(Open (VirtualFile 0 0 mempty Nothing))
185223
where
186224
shouldOverwrite :: Bool
187225
shouldOverwrite = case options of
@@ -308,7 +346,8 @@ persistFileVFS :: (MonadIO m) => LogAction m (WithSeverity VfsLog) -> FilePath -
308346
persistFileVFS logger dir vfs uri =
309347
case vfs ^. vfsMap . at uri of
310348
Nothing -> Nothing
311-
Just vf ->
349+
(Just (Closed _)) -> Nothing
350+
(Just (Open vf)) ->
312351
let tfn = virtualFileName dir uri vf
313352
action = do
314353
exists <- liftIO $ doesFileExist tfn
@@ -329,7 +368,12 @@ closeVFS :: (MonadState VFS m) => LogAction m (WithSeverity VfsLog) -> J.TMessag
329368
closeVFS logger msg = do
330369
let J.DidCloseTextDocumentParams (J.TextDocumentIdentifier (J.toNormalizedUri -> uri)) = msg ^. J.params
331370
logger <& Closing uri `WithSeverity` Debug
332-
vfsMap . at uri .= Nothing
371+
vfsMap . ix uri
372+
%= ( \mf ->
373+
case mf of
374+
Open f -> Closed $ toClosedVirtualFile f
375+
Closed f -> Closed f
376+
)
333377

334378
-- ---------------------------------------------------------------------
335379

0 commit comments

Comments
 (0)