Skip to content

Commit 81f8b94

Browse files
Track the languageId in Virtual File (#610)
The languageKind is received when a TextDocument is opened, we add this information to the VirtualFile to keep track of it. Note that the `_language_id` is defined as a Maybe to be compatible with lsp-test's use of the virtual file system. Co-authored-by: Michael Peyton Jones <[email protected]>
1 parent 696f256 commit 81f8b94

File tree

5 files changed

+23
-13
lines changed

5 files changed

+23
-13
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -445,7 +445,7 @@ updateState (FromServerMess SMethod_WorkspaceApplyEdit r) = do
445445
forM_ latestVersions $ \(VersionedTextDocumentIdentifier uri v) ->
446446
modify $ \s ->
447447
let oldVFS = vfs s
448-
update (VirtualFile _ file_ver t) = VirtualFile v (file_ver +1) t
448+
update (VirtualFile _ file_ver t _kind) = VirtualFile v (file_ver +1) t _kind
449449
newVFS = oldVFS & vfsMap . ix (toNormalizedUri uri) %~ update
450450
in s { vfs = newVFS }
451451

lsp/example/Reactor.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -246,7 +246,7 @@ handle logger =
246246
logger <& ("Processing DidChangeTextDocument for: " <> T.pack (show doc)) `WithSeverity` Info
247247
mdoc <- getVirtualFile doc
248248
case mdoc of
249-
Just (VirtualFile _version str _) -> do
249+
Just (VirtualFile _version str _ _) -> do
250250
logger <& ("Found the virtual file: " <> T.pack (show str)) `WithSeverity` Info
251251
Nothing -> do
252252
logger <& ("Didn't find anything in the VFS for: " <> T.pack (show doc)) `WithSeverity` Info

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -471,7 +471,7 @@ getVersionedTextDoc doc = do
471471
let uri = doc ^. L.uri
472472
mvf <- getVirtualFile (toNormalizedUri uri)
473473
let ver = case mvf of
474-
Just (VirtualFile lspver _ _) -> lspver
474+
Just (VirtualFile lspver _ _ _) -> lspver
475475
Nothing -> 0
476476
return (VersionedTextDocumentIdentifier uri ver)
477477
{-# INLINE getVersionedTextDoc #-}

lsp/src/Language/LSP/VFS.hs

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ module Language.LSP.VFS (
2323
file_text,
2424
virtualFileText,
2525
virtualFileVersion,
26+
virtualFileLanguageKind,
2627
VfsLog (..),
2728

2829
-- * Managing the VFS
@@ -92,6 +93,12 @@ data VirtualFile = VirtualFile
9293
-- remains in the map.
9394
, _file_text :: !Rope
9495
-- ^ The full contents of the document
96+
, _language_id :: !(Maybe J.LanguageKind)
97+
-- ^ The text document's language identifier
98+
-- This is a Maybe, since when we use the VFS as a client
99+
-- we don't have this information, since server sends WorkspaceEdit
100+
-- notifications without a language kind.
101+
-- When using the VFS in a server, this should always be Just.
95102
}
96103
deriving (Show)
97104

@@ -132,6 +139,9 @@ virtualFileText vf = Rope.toText (_file_text vf)
132139
virtualFileVersion :: VirtualFile -> Int32
133140
virtualFileVersion vf = _lsp_version vf
134141

142+
virtualFileLanguageKind :: VirtualFile -> Maybe J.LanguageKind
143+
virtualFileLanguageKind vf = _language_id vf
144+
135145
---
136146

137147
emptyVFS :: VFS
@@ -142,8 +152,8 @@ emptyVFS = VFS mempty
142152
-- | Applies the changes from a 'J.DidOpenTextDocument' to the 'VFS'
143153
openVFS :: (MonadState VFS m) => LogAction m (WithSeverity VfsLog) -> J.TMessage 'J.Method_TextDocumentDidOpen -> m ()
144154
openVFS logger msg = do
145-
let J.TextDocumentItem (J.toNormalizedUri -> uri) _ version text = msg ^. J.params . J.textDocument
146-
vfile = VirtualFile version 0 (Rope.fromText text)
155+
let J.TextDocumentItem (J.toNormalizedUri -> uri) languageId version text = msg ^. J.params . J.textDocument
156+
vfile = VirtualFile version 0 (Rope.fromText text) (Just languageId)
147157
logger <& Opening uri `WithSeverity` Debug
148158
vfsMap . at uri .= Just vfile
149159

@@ -158,9 +168,9 @@ changeFromClientVFS logger msg = do
158168
J.VersionedTextDocumentIdentifier (J.toNormalizedUri -> uri) version = vid
159169
vfs <- get
160170
case vfs ^. vfsMap . at uri of
161-
Just (VirtualFile _ file_ver contents) -> do
171+
Just (VirtualFile _ file_ver contents kind) -> do
162172
contents' <- applyChanges logger contents changes
163-
vfsMap . at uri .= Just (VirtualFile version (file_ver + 1) contents')
173+
vfsMap . at uri .= Just (VirtualFile version (file_ver + 1) contents' kind)
164174
Nothing -> logger <& URINotFound uri `WithSeverity` Warning
165175

166176
-- ---------------------------------------------------------------------
@@ -171,7 +181,7 @@ applyCreateFile (J.CreateFile _ann _kind (J.toNormalizedUri -> uri) options) =
171181
%= Map.insertWith
172182
(\new old -> if shouldOverwrite then new else old)
173183
uri
174-
(VirtualFile 0 0 mempty)
184+
(VirtualFile 0 0 mempty Nothing)
175185
where
176186
shouldOverwrite :: Bool
177187
shouldOverwrite = case options of
@@ -281,7 +291,7 @@ changeFromServerVFS logger msg = do
281291

282292
-- ---------------------------------------------------------------------
283293
virtualFileName :: FilePath -> J.NormalizedUri -> VirtualFile -> FilePath
284-
virtualFileName prefix uri (VirtualFile _ file_ver _) =
294+
virtualFileName prefix uri (VirtualFile _ file_ver _ _) =
285295
let uri_raw = J.fromNormalizedUri uri
286296
basename = maybe "" takeFileName (J.uriToFilePath uri_raw)
287297
-- Given a length and a version number, pad the version number to
@@ -463,7 +473,7 @@ rangeToCodePointRange vFile (J.Range b e) =
463473
CodePointRange <$> positionToCodePointPosition vFile b <*> positionToCodePointPosition vFile e
464474

465475
rangeLinesFromVfs :: VirtualFile -> J.Range -> T.Text
466-
rangeLinesFromVfs (VirtualFile _ _ ropetext) (J.Range (J.Position lf _cf) (J.Position lt _ct)) = r
476+
rangeLinesFromVfs (VirtualFile _ _ ropetext _) (J.Range (J.Position lf _cf) (J.Position lt _ct)) = r
467477
where
468478
(_, s1) = Rope.splitAtLine (fromIntegral lf) ropetext
469479
(s2, _) = Rope.splitAtLine (fromIntegral (lt - lf)) s1

lsp/test/VspSpec.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ spec = describe "VSP functions" vspSpec
2929
-- ---------------------------------------------------------------------
3030

3131
vfsFromText :: T.Text -> VirtualFile
32-
vfsFromText text = VirtualFile 0 0 (Rope.fromText text)
32+
vfsFromText text = VirtualFile 0 0 (Rope.fromText text) $ Just J.LanguageKind_Haskell
3333

3434
-- ---------------------------------------------------------------------
3535

@@ -243,7 +243,7 @@ vspSpec = do
243243
[ "a𐐀b"
244244
, "a𐐀b"
245245
]
246-
vfile = VirtualFile 0 0 (fromString orig)
246+
vfile = VirtualFile 0 0 (fromString orig) $ Just J.LanguageKind_Haskell
247247

248248
positionToCodePointPosition vfile (J.Position 1 0) `shouldBe` Just (CodePointPosition 1 0)
249249
positionToCodePointPosition vfile (J.Position 1 1) `shouldBe` Just (CodePointPosition 1 1)
@@ -265,7 +265,7 @@ vspSpec = do
265265
[ "a𐐀b"
266266
, "a𐐀b"
267267
]
268-
vfile = VirtualFile 0 0 (fromString orig)
268+
vfile = VirtualFile 0 0 (fromString orig) $ Just J.LanguageKind_Haskell
269269

270270
codePointPositionToPosition vfile (CodePointPosition 1 0) `shouldBe` Just (J.Position 1 0)
271271
codePointPositionToPosition vfile (CodePointPosition 1 1) `shouldBe` Just (J.Position 1 1)

0 commit comments

Comments
 (0)