Skip to content

Commit 6804c53

Browse files
authored
Fix for #374 (#376)
* Improve error message * Add test for #374 * Add fix * avoid double version bump * add a comment
1 parent 41b8f01 commit 6804c53

File tree

5 files changed

+72
-11
lines changed

5 files changed

+72
-11
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ decodeFromServerMsg reqMap bytes = unP $ parse p obj
8282
Just m -> Just $ (m, Pair m (Const newMap))
8383
unP (Success (FromServerMess m msg)) = (reqMap, FromServerMess m msg)
8484
unP (Success (FromServerRsp (Pair m (Const newMap)) msg)) = (newMap, FromServerRsp m msg)
85-
unP (Error e) = error e
85+
unP (Error e) = error $ "Error decoding " <> show obj <> " :" <> e
8686
{-
8787
WorkspaceWorkspaceFolders -> error "ReqWorkspaceFolders not supported yet"
8888
WorkspaceConfiguration -> error "ReqWorkspaceConfiguration not supported yet"

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

Lines changed: 10 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -354,7 +354,10 @@ updateState (FromServerMess SWorkspaceApplyEdit r) = do
354354
allChangeParams <- case r ^. params . edit . documentChanges of
355355
Just (List cs) -> do
356356
mapM_ (checkIfNeedsOpened . documentChangeUri) cs
357-
return $ mapMaybe getParamsFromDocumentChange cs
357+
-- replace the user provided version numbers with the VFS ones + 1
358+
-- (technically we should check that the user versions match the VFS ones)
359+
cs' <- traverseOf (traverse . _InL . textDocument) bumpNewestVersion cs
360+
return $ mapMaybe getParamsFromDocumentChange cs'
358361
-- Then fall back to the changes field
359362
Nothing -> case r ^. params . edit . changes of
360363
Just cs -> do
@@ -376,12 +379,11 @@ updateState (FromServerMess SWorkspaceApplyEdit r) = do
376379
-- Update VFS to new document versions
377380
let sortedVersions = map (sortBy (compare `on` (^. textDocument . version))) groupedParams
378381
latestVersions = map ((^. textDocument) . last) sortedVersions
379-
bumpedVersions = map (version . _Just +~ 1) latestVersions
380382

381-
forM_ bumpedVersions $ \(VersionedTextDocumentIdentifier uri v) ->
383+
forM_ latestVersions $ \(VersionedTextDocumentIdentifier uri v) ->
382384
modify $ \s ->
383385
let oldVFS = vfs s
384-
update (VirtualFile oldV file_ver t) = VirtualFile (fromMaybe oldV v) (file_ver + 1) t
386+
update (VirtualFile oldV file_ver t) = VirtualFile (fromMaybe oldV v) (file_ver +1) t
385387
newVFS = updateVFS (Map.adjust update (toNormalizedUri uri)) oldVFS
386388
in s { vfs = newVFS }
387389

@@ -401,7 +403,7 @@ updateState (FromServerMess SWorkspaceApplyEdit r) = do
401403
return $ s { vfs = newVFS }
402404

403405
getParamsFromTextDocumentEdit :: TextDocumentEdit -> DidChangeTextDocumentParams
404-
getParamsFromTextDocumentEdit (TextDocumentEdit docId (List edits)) =
406+
getParamsFromTextDocumentEdit (TextDocumentEdit docId (List edits)) = do
405407
DidChangeTextDocumentParams docId (List $ map editToChangeEvent edits)
406408

407409
editToChangeEvent :: TextEdit |? AnnotatedTextEdit -> TextDocumentContentChangeEvent
@@ -412,6 +414,8 @@ updateState (FromServerMess SWorkspaceApplyEdit r) = do
412414
getParamsFromDocumentChange (InL textDocumentEdit) = Just $ getParamsFromTextDocumentEdit textDocumentEdit
413415
getParamsFromDocumentChange _ = Nothing
414416

417+
bumpNewestVersion (VersionedTextDocumentIdentifier uri _) =
418+
head <$> textDocumentVersions uri
415419

416420
-- For a uri returns an infinite list of versions [n,n+1,n+2,...]
417421
-- where n is the current version
@@ -425,7 +429,7 @@ updateState (FromServerMess SWorkspaceApplyEdit r) = do
425429
vers <- textDocumentVersions uri
426430
pure $ map (\(v, e) -> TextDocumentEdit v (List [InL e])) $ zip vers edits
427431

428-
getChangeParams uri (List edits) = do
432+
getChangeParams uri (List edits) = do
429433
map <$> pure getParamsFromTextDocumentEdit <*> textDocumentEdits uri (reverse edits)
430434

431435
mergeParams :: [DidChangeTextDocumentParams] -> DidChangeTextDocumentParams

lsp-test/test/DummyServer.hs

Lines changed: 24 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -139,15 +139,36 @@ handlers =
139139
do
140140
Just token <- runInIO $ asks absRegToken >>= tryReadMVar
141141
runInIO $ unregisterCapability token
142+
143+
-- this handler is used by the
144+
-- "text document VFS / sends back didChange notifications (documentChanges)" test
145+
, notificationHandler STextDocumentDidChange $ \noti -> do
146+
let NotificationMessage _ _ params = noti
147+
void $ sendNotification (SCustomMethod "custom/textDocument/didChange") (toJSON params)
148+
142149
, requestHandler SWorkspaceExecuteCommand $ \req resp -> do
143-
let RequestMessage _ _ _ (ExecuteCommandParams Nothing "doAnEdit" (Just (List [val]))) = req
150+
case req of
151+
RequestMessage _ _ _ (ExecuteCommandParams Nothing "doAnEdit" (Just (List [val]))) -> do
152+
let
144153
Success docUri = fromJSON val
145154
edit = List [TextEdit (mkRange 0 0 0 5) "howdy"]
146155
params =
147156
ApplyWorkspaceEditParams (Just "Howdy edit") $
148157
WorkspaceEdit (Just (HM.singleton docUri edit)) Nothing Nothing
149-
resp $ Right Null
150-
void $ sendRequest SWorkspaceApplyEdit params (const (pure ()))
158+
resp $ Right Null
159+
void $ sendRequest SWorkspaceApplyEdit params (const (pure ()))
160+
RequestMessage _ _ _ (ExecuteCommandParams Nothing "doAVersionedEdit" (Just (List [val]))) -> do
161+
let
162+
Success versionedDocUri = fromJSON val
163+
edit = List [InL (TextEdit (mkRange 0 0 0 5) "howdy")]
164+
documentEdit = TextDocumentEdit versionedDocUri edit
165+
params =
166+
ApplyWorkspaceEditParams (Just "Howdy edit") $
167+
WorkspaceEdit Nothing (Just (List [InL documentEdit])) Nothing
168+
resp $ Right Null
169+
void $ sendRequest SWorkspaceApplyEdit params (const (pure ()))
170+
RequestMessage _ _ _ (ExecuteCommandParams _ name _) ->
171+
error $ "unsupported command: " <> show name
151172
, requestHandler STextDocumentCodeAction $ \req resp -> do
152173
let RequestMessage _ _ _ params = req
153174
CodeActionParams _ _ _ _ cactx = params

lsp-test/test/Test.hs

Lines changed: 32 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
{-# LANGUAGE GADTs #-}
33
{-# LANGUAGE DuplicateRecordFields #-}
44
{-# LANGUAGE OverloadedStrings #-}
5+
{-# LANGUAGE ScopedTypeVariables #-}
56
{-# LANGUAGE DeriveGeneric #-}
67
{-# LANGUAGE DeriveAnyClass #-}
78

@@ -132,7 +133,37 @@ main = hspec $ around withDummyServer $ do
132133
in runSessionWithHandles hin hout def fullCaps "." sesh
133134
`shouldThrow` selector
134135

135-
describe "text document VFS" $
136+
describe "text document VFS" $ do
137+
it "sends back didChange notifications (documentChanges)" $ \(hin, hout) ->
138+
runSessionWithHandles hin hout def fullCaps "." $ do
139+
doc <- openDoc "test/data/refactor/Main.hs" "haskell"
140+
VersionedTextDocumentIdentifier _ beforeVersion <- getVersionedDoc doc
141+
142+
let args = toJSON (VersionedTextDocumentIdentifier (doc ^. uri) beforeVersion)
143+
reqParams = ExecuteCommandParams Nothing "doAVersionedEdit" (Just (List [args]))
144+
145+
request_ SWorkspaceExecuteCommand reqParams
146+
147+
editReq <- message SWorkspaceApplyEdit
148+
liftIO $ do
149+
let Just (List [InL(TextDocumentEdit vdoc (List [InL edit_]))]) =
150+
editReq ^. params . edit . documentChanges
151+
vdoc `shouldBe` VersionedTextDocumentIdentifier (doc ^. uri) beforeVersion
152+
edit_ `shouldBe` TextEdit (Range (Position 0 0) (Position 0 5)) "howdy"
153+
154+
change <- customNotification "custom/textDocument/didChange"
155+
let NotMess (NotificationMessage _ _ (c::Value)) = change
156+
Success (DidChangeTextDocumentParams reportedVDoc _edit) = fromJSON c
157+
VersionedTextDocumentIdentifier _ reportedVersion = reportedVDoc
158+
159+
contents <- documentContents doc
160+
161+
liftIO $ contents `shouldBe` "howdy:: IO Int\nmain = return (42)\n"
162+
VersionedTextDocumentIdentifier _ afterVersion <- getVersionedDoc doc
163+
liftIO $ afterVersion `shouldNotBe` beforeVersion
164+
165+
liftIO $ reportedVersion `shouldNotBe` beforeVersion
166+
136167
it "sends back didChange notifications" $ \(hin, hout) ->
137168
runSessionWithHandles hin hout def fullCaps "." $ do
138169
doc <- openDoc "test/data/refactor/Main.hs" "haskell"

lsp-types/src/Language/LSP/Types/Lens.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@
99
{-# LANGUAGE FlexibleContexts #-}
1010
{-# LANGUAGE DataKinds #-}
1111
{-# LANGUAGE TypeInType #-}
12+
{-# LANGUAGE ExplicitNamespaces #-}
1213

1314
module Language.LSP.Types.Lens where
1415

@@ -19,6 +20,7 @@ import Language.LSP.Types.CodeAction
1920
import Language.LSP.Types.CodeLens
2021
import Language.LSP.Types.DocumentColor
2122
import Language.LSP.Types.Command
23+
import Language.LSP.Types.Common (type (|?))
2224
import Language.LSP.Types.Completion
2325
import Language.LSP.Types.Configuration
2426
import Language.LSP.Types.Declaration
@@ -391,3 +393,6 @@ makeFieldsNoPrefix ''SemanticTokensEdit
391393
makeFieldsNoPrefix ''SemanticTokensDelta
392394
makeFieldsNoPrefix ''SemanticTokensDeltaPartialResult
393395
makeFieldsNoPrefix ''SemanticTokensWorkspaceClientCapabilities
396+
397+
-- Unions
398+
makePrisms ''(|?)

0 commit comments

Comments
 (0)