Skip to content

Commit 349249a

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 349249a

File tree

4 files changed

+52
-13
lines changed

4 files changed

+52
-13
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: 46 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -18,9 +18,15 @@ module Language.LSP.VFS (
1818
VFS (..),
1919
vfsMap,
2020
VirtualFile (..),
21+
VirtualFileGhost (..),
22+
VirtualFileEntry (..),
2123
lsp_version,
2224
file_version,
2325
file_text,
26+
language_id,
27+
ghost_language_id,
28+
_Open,
29+
_Closed,
2430
virtualFileText,
2531
virtualFileVersion,
2632
virtualFileLanguageKind,
@@ -102,13 +108,36 @@ data VirtualFile = VirtualFile
102108
}
103109
deriving (Show)
104110

111+
{- | Represents a closed file in the VFS
112+
We are keeping track of this in order to be able to get information
113+
on virtual files after they were closed.
114+
-}
115+
data VirtualFileGhost = VirtualFileGhost
116+
{ _ghost_language_id :: !(Maybe J.LanguageKind)
117+
-- ^ The text document's language identifier
118+
-- This is a Maybe, since when we use the VFS as a client
119+
-- we don't have this information, since server sends WorkspaceEdit
120+
-- notifications without a language kind.
121+
-- When using the VFS in a server, this should always be Just.
122+
}
123+
deriving (Show)
124+
125+
ghostify :: VirtualFile -> VirtualFileGhost
126+
ghostify vf =
127+
VirtualFileGhost
128+
{ _ghost_language_id = _language_id vf
129+
}
130+
data VirtualFileEntry = Open VirtualFile | Closed VirtualFileGhost
131+
deriving (Show)
132+
105133
data VFS = VFS
106-
{ _vfsMap :: !(Map.Map J.NormalizedUri VirtualFile)
134+
{ _vfsMap :: !(Map.Map J.NormalizedUri VirtualFileEntry)
107135
}
108136
deriving (Show)
109137

110138
data VfsLog
111139
= SplitInsideCodePoint Utf16.Position Rope
140+
| ClosedVirtualFile
112141
| URINotFound J.NormalizedUri
113142
| Opening J.NormalizedUri
114143
| Closing J.NormalizedUri
@@ -120,6 +149,7 @@ data VfsLog
120149
instance Pretty VfsLog where
121150
pretty (SplitInsideCodePoint pos r) =
122151
"VFS: asked to make change inside code point. Position" <+> viaShow pos <+> "in" <+> viaShow r
152+
pretty ClosedVirtualFile = "VFS: trying to handle closed virtual file"
123153
pretty (URINotFound uri) = "VFS: don't know about URI" <+> pretty uri
124154
pretty (Opening uri) = "VFS: opening" <+> pretty uri
125155
pretty (Closing uri) = "VFS: closing" <+> pretty uri
@@ -129,7 +159,9 @@ instance Pretty VfsLog where
129159
pretty (DeleteNonExistent uri) = "VFS: asked to delete non-existent file" <+> pretty uri
130160

131161
makeFieldsNoPrefix ''VirtualFile
162+
makeFieldsNoPrefix ''VirtualFileGhost
132163
makeFieldsNoPrefix ''VFS
164+
makePrisms ''VirtualFileEntry
133165

134166
---
135167

@@ -155,7 +187,7 @@ openVFS logger msg = do
155187
let J.TextDocumentItem (J.toNormalizedUri -> uri) languageId version text = msg ^. J.params . J.textDocument
156188
vfile = VirtualFile version 0 (Rope.fromText text) (Just languageId)
157189
logger <& Opening uri `WithSeverity` Debug
158-
vfsMap . at uri .= Just vfile
190+
vfsMap . at uri .= (Just $ Open vfile)
159191

160192
-- ---------------------------------------------------------------------
161193

@@ -168,9 +200,10 @@ changeFromClientVFS logger msg = do
168200
J.VersionedTextDocumentIdentifier (J.toNormalizedUri -> uri) version = vid
169201
vfs <- get
170202
case vfs ^. vfsMap . at uri of
171-
Just (VirtualFile _ file_ver contents kind) -> do
203+
Just (Open (VirtualFile _ file_ver contents kind)) -> do
172204
contents' <- applyChanges logger contents changes
173-
vfsMap . at uri .= Just (VirtualFile version (file_ver + 1) contents' kind)
205+
vfsMap . at uri .= Just (Open (VirtualFile version (file_ver + 1) contents' kind))
206+
Just (Closed (VirtualFileGhost _)) -> logger <& ClosedVirtualFile `WithSeverity` Warning
174207
Nothing -> logger <& URINotFound uri `WithSeverity` Warning
175208

176209
-- ---------------------------------------------------------------------
@@ -181,7 +214,7 @@ applyCreateFile (J.CreateFile _ann _kind (J.toNormalizedUri -> uri) options) =
181214
%= Map.insertWith
182215
(\new old -> if shouldOverwrite then new else old)
183216
uri
184-
(VirtualFile 0 0 mempty Nothing)
217+
(Open (VirtualFile 0 0 mempty Nothing))
185218
where
186219
shouldOverwrite :: Bool
187220
shouldOverwrite = case options of
@@ -308,7 +341,8 @@ persistFileVFS :: (MonadIO m) => LogAction m (WithSeverity VfsLog) -> FilePath -
308341
persistFileVFS logger dir vfs uri =
309342
case vfs ^. vfsMap . at uri of
310343
Nothing -> Nothing
311-
Just vf ->
344+
(Just (Closed _)) -> Nothing
345+
(Just (Open vf)) ->
312346
let tfn = virtualFileName dir uri vf
313347
action = do
314348
exists <- liftIO $ doesFileExist tfn
@@ -329,7 +363,12 @@ closeVFS :: (MonadState VFS m) => LogAction m (WithSeverity VfsLog) -> J.TMessag
329363
closeVFS logger msg = do
330364
let J.DidCloseTextDocumentParams (J.TextDocumentIdentifier (J.toNormalizedUri -> uri)) = msg ^. J.params
331365
logger <& Closing uri `WithSeverity` Debug
332-
vfsMap . at uri .= Nothing
366+
vfsMap . at uri
367+
%= ( \mf ->
368+
case mf of
369+
Just (Open f) -> Just $ Closed $ ghostify f
370+
_ -> Nothing
371+
)
333372

334373
-- ---------------------------------------------------------------------
335374

0 commit comments

Comments
 (0)