Skip to content

Commit 0b0eee3

Browse files
authored
Bump lsp versions (#4052)
* Bump lsp versions Broadly: - A few places where we need to pipe `ProgressToken`s around. - I also just removed the progress reporting from resolve commands, since it's going to often be costly to do progress reporting on something that short. Possibly we could revisit after haskell/lsp#549 - Some changes to the registration options we infer - A few places where we need to adapt to ignoring registrations or not - Adapting to use the ghcide verison of `getCompletionPrefix` everywhere - Adapting to use the new mixed rope format * stack * More fixes
1 parent 9021c39 commit 0b0eee3

File tree

45 files changed

+159
-157
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

45 files changed

+159
-157
lines changed

Diff for: cabal.project

+1-1
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ packages:
99
./hls-plugin-api
1010
./hls-test-utils
1111

12-
index-state: 2024-01-21T00:00:00Z
12+
index-state: 2024-02-25T00:00:00Z
1313

1414
tests: True
1515
test-show-details: direct

Diff for: ghcide-bench/ghcide-bench.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -99,7 +99,7 @@ test-suite test
9999
base,
100100
extra,
101101
ghcide-bench,
102-
lsp-test ^>= 0.16,
102+
lsp-test ^>= 0.17,
103103
tasty,
104104
tasty-hunit >= 0.10,
105105
tasty-rerun,

Diff for: ghcide/ghcide.cabal

+3-3
Original file line numberDiff line numberDiff line change
@@ -93,7 +93,7 @@ library
9393
, implicit-hie >= 0.1.4.0 && < 0.1.5
9494
, lens
9595
, list-t
96-
, lsp ^>=2.3.0.0
96+
, lsp ^>=2.4.0.0
9797
, lsp-types ^>=2.1.0.0
9898
, mtl
9999
, opentelemetry >=0.6.1
@@ -183,6 +183,7 @@ library
183183
Development.IDE.Plugin
184184
Development.IDE.Plugin.Completions
185185
Development.IDE.Plugin.Completions.Types
186+
Development.IDE.Plugin.Completions.Logic
186187
Development.IDE.Plugin.HLS
187188
Development.IDE.Plugin.HLS.GhcIde
188189
Development.IDE.Plugin.Test
@@ -210,7 +211,6 @@ library
210211
Development.IDE.Core.FileExists
211212
Development.IDE.GHC.CPP
212213
Development.IDE.GHC.Warnings
213-
Development.IDE.Plugin.Completions.Logic
214214
Development.IDE.Session.VersionCheck
215215
Development.IDE.Types.Action
216216

@@ -305,7 +305,7 @@ test-suite ghcide-tests
305305
, lens
306306
, list-t
307307
, lsp
308-
, lsp-test ^>=0.16.0.0
308+
, lsp-test ^>=0.17.0.0
309309
, lsp-types
310310
, monoid-subclasses
311311
, mtl

Diff for: ghcide/session-loader/Development/IDE/Session.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -635,7 +635,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
635635
-- Display a user friendly progress message here: They probably don't know what a cradle is
636636
let progMsg = "Setting up " <> T.pack (takeBaseName (cradleRootDir cradle))
637637
<> " (for " <> T.pack lfp <> ")"
638-
eopts <- mRunLspTCallback lspEnv (withIndefiniteProgress progMsg NotCancellable) $
638+
eopts <- mRunLspTCallback lspEnv (\act -> withIndefiniteProgress progMsg Nothing NotCancellable (const act)) $
639639
withTrace "Load cradle" $ \addTag -> do
640640
addTag "file" lfp
641641
old_files <- readIORef cradle_files

Diff for: ghcide/src/Development/IDE/Core/FileStore.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -183,7 +183,7 @@ getFileContentsImpl file = do
183183
time <- use_ GetModificationTime file
184184
res <- do
185185
mbVirtual <- getVirtualFile file
186-
pure $ Rope.toText . _file_text <$> mbVirtual
186+
pure $ virtualFileText <$> mbVirtual
187187
pure ([], Just (time, res))
188188

189189
-- | Returns the modification time and the contents.

Diff for: ghcide/src/Development/IDE/Core/Rules.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -575,7 +575,7 @@ persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybe
575575
vfsData <- liftIO $ _vfsMap <$> readTVarIO vfsRef
576576
(currentSource, ver) <- liftIO $ case M.lookup (filePathToUri' file) vfsData of
577577
Nothing -> (,Nothing) . T.decodeUtf8 <$> BS.readFile (fromNormalizedFilePath file)
578-
Just vf -> pure (Rope.toText $ _file_text vf, Just $ _lsp_version vf)
578+
Just vf -> pure (virtualFileText vf, Just $ virtualFileVersion vf)
579579
let refmap = Compat.generateReferencesMap . Compat.getAsts . Compat.hie_asts $ res
580580
del = deltaFromDiff (T.decodeUtf8 $ Compat.hie_hs_src res) currentSource
581581
pure (HAR (Compat.hie_module res) (Compat.hie_asts res) refmap mempty (HieFromDisk res),del,ver)

Diff for: ghcide/src/Development/IDE/Plugin/Completions/Logic.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ import qualified Language.LSP.VFS as VFS
6262
import Text.Fuzzy.Parallel (Scored (score),
6363
original)
6464

65-
import qualified Data.Text.Utf16.Rope as Rope
65+
import qualified Data.Text.Utf16.Rope.Mixed as Rope
6666
import Development.IDE hiding (line)
6767

6868
import Development.IDE.Spans.AtPoint (pointCommand)

Diff for: ghcide/src/Development/IDE/Plugin/HLS.hs

+5-5
Original file line numberDiff line numberDiff line change
@@ -177,7 +177,7 @@ executeCommandHandlers recorder ecs = requestHandler SMethod_WorkspaceExecuteCom
177177

178178
-- The parameters to the HLS command are always the first element
179179
execCmd :: IdeState -> ExecuteCommandParams -> LSP.LspT Config IO (Either ResponseError (A.Value |? Null))
180-
execCmd ide (ExecuteCommandParams _ cmdId args) = do
180+
execCmd ide (ExecuteCommandParams mtoken cmdId args) = do
181181
let cmdParams :: A.Value
182182
cmdParams = case args of
183183
Just ((x:_)) -> x
@@ -201,23 +201,23 @@ executeCommandHandlers recorder ecs = requestHandler SMethod_WorkspaceExecuteCom
201201
A.Error _str -> return $ Right $ InR Null
202202

203203
-- Just an ordinary HIE command
204-
Just (plugin, cmd) -> runPluginCommand ide plugin cmd cmdParams
204+
Just (plugin, cmd) -> runPluginCommand ide plugin cmd mtoken cmdParams
205205

206206
-- Couldn't parse the command identifier
207207
_ -> do
208208
logWith recorder Warning LogInvalidCommandIdentifier
209209
return $ Left $ ResponseError (InR ErrorCodes_InvalidParams) "Invalid command identifier" Nothing
210210

211-
runPluginCommand :: IdeState -> PluginId -> CommandId -> A.Value -> LSP.LspT Config IO (Either ResponseError (A.Value |? Null))
212-
runPluginCommand ide p com arg =
211+
runPluginCommand :: IdeState -> PluginId -> CommandId -> Maybe ProgressToken -> A.Value -> LSP.LspT Config IO (Either ResponseError (A.Value |? Null))
212+
runPluginCommand ide p com mtoken arg =
213213
case Map.lookup p pluginMap of
214214
Nothing -> logAndReturnError recorder p (InR ErrorCodes_InvalidRequest) (pluginDoesntExist p)
215215
Just xs -> case List.find ((com ==) . commandId) xs of
216216
Nothing -> logAndReturnError recorder p (InR ErrorCodes_InvalidRequest) (commandDoesntExist com p xs)
217217
Just (PluginCommand _ _ f) -> case A.fromJSON arg of
218218
A.Error err -> logAndReturnError recorder p (InR ErrorCodes_InvalidParams) (failedToParseArgs com p err arg)
219219
A.Success a -> do
220-
res <- runExceptT (f ide a) `catchAny` -- See Note [Exception handling in plugins]
220+
res <- runExceptT (f ide mtoken a) `catchAny` -- See Note [Exception handling in plugins]
221221
(\e -> pure $ Left $ PluginInternalError (exceptionInPlugin p SMethod_WorkspaceExecuteCommand e))
222222
case res of
223223
(Left (PluginRequestRefused r)) ->

Diff for: ghcide/src/Development/IDE/Plugin/Test.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -170,7 +170,7 @@ blockCommandDescriptor plId = (defaultPluginDescriptor plId "") {
170170
}
171171

172172
blockCommandHandler :: CommandFunction state ExecuteCommandParams
173-
blockCommandHandler _ideState _params = do
173+
blockCommandHandler _ideState _ _params = do
174174
lift $ LSP.sendNotification (SMethod_CustomMethod (Proxy @"ghcide/blocking/command")) A.Null
175175
liftIO $ threadDelay maxBound
176176
pure $ InR Null

Diff for: ghcide/src/Development/IDE/Plugin/TypeLenses.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -192,7 +192,7 @@ generateLensCommand pId uri title edit =
192192
-- recompute the edit upon command. Hence the command here just takes a edit
193193
-- and applies it.
194194
commandHandler :: CommandFunction IdeState WorkspaceEdit
195-
commandHandler _ideState wedit = do
195+
commandHandler _ideState _ wedit = do
196196
_ <- lift $ LSP.sendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wedit) (\_ -> pure ())
197197
pure $ InR Null
198198

Diff for: ghcide/test/exe/ClientSettingsTests.hs

-1
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,6 @@ tests :: TestTree
2121
tests = testGroup "client settings handling"
2222
[ testSession "ghcide restarts shake session on config changes" $ do
2323
setIgnoringLogNotifications False
24-
void $ skipManyTill anyMessage $ message SMethod_ClientRegisterCapability
2524
void $ createDoc "A.hs" "haskell" "module A where"
2625
waitForProgressDone
2726
setConfigSection "haskell" $ toJSON (def :: Config)

Diff for: ghcide/test/exe/ExceptionTests.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -65,7 +65,7 @@ tests recorder logger = do
6565
plugins = pluginDescToIdePlugins $
6666
[ (defaultPluginDescriptor pluginId "")
6767
{ pluginCommands =
68-
[ PluginCommand commandId "Causes an exception" $ \_ (_::Int) -> do
68+
[ PluginCommand commandId "Causes an exception" $ \_ _ (_::Int) -> do
6969
_ <- liftIO $ throwIO DivideByZero
7070
pure (InR Null)
7171
]

Diff for: ghcide/test/exe/InitializeResponseTests.hs

+15-15
Original file line numberDiff line numberDiff line change
@@ -36,29 +36,29 @@ tests = withResource acquire release tests where
3636
tests getInitializeResponse =
3737
testGroup "initialize response capabilities"
3838
[ chk " text doc sync" _textDocumentSync tds
39-
, chk " hover" _hoverProvider (Just $ InL True)
40-
, chk " completion" _completionProvider (Just $ CompletionOptions Nothing (Just ["."]) Nothing (Just True) Nothing)
39+
, chk " hover" _hoverProvider (Just $ InR (HoverOptions (Just False)))
40+
, chk " completion" _completionProvider (Just $ CompletionOptions (Just False) (Just ["."]) Nothing (Just True) Nothing)
4141
, chk "NO signature help" _signatureHelpProvider Nothing
42-
, chk " goto definition" _definitionProvider (Just $ InL True)
43-
, chk " goto type definition" _typeDefinitionProvider (Just $ InL True)
42+
, chk " goto definition" _definitionProvider (Just $ InR (DefinitionOptions (Just False)))
43+
, chk " goto type definition" _typeDefinitionProvider (Just $ InR (InL (TypeDefinitionOptions (Just False))))
4444
-- BUG in lsp-test, this test fails, just change the accepted response
4545
-- for now
46-
, chk "NO goto implementation" _implementationProvider (Just $ InL False)
47-
, chk " find references" _referencesProvider (Just $ InL True)
48-
, chk " doc highlight" _documentHighlightProvider (Just $ InL True)
49-
, chk " doc symbol" _documentSymbolProvider (Just $ InL True)
50-
, chk " workspace symbol" _workspaceSymbolProvider (Just $ InL True)
51-
, chk " code action" _codeActionProvider (Just $ InL False)
46+
, chk "NO goto implementation" _implementationProvider Nothing
47+
, chk " find references" _referencesProvider (Just $ InR (ReferenceOptions (Just False)))
48+
, chk " doc highlight" _documentHighlightProvider (Just $ InR (DocumentHighlightOptions (Just False)))
49+
, chk " doc symbol" _documentSymbolProvider (Just $ InR (DocumentSymbolOptions (Just False) Nothing))
50+
, chk " workspace symbol" _workspaceSymbolProvider (Just $ InR (WorkspaceSymbolOptions (Just False) (Just False)))
51+
, chk "NO code action" _codeActionProvider Nothing
5252
, chk " code lens" _codeLensProvider (Just $ CodeLensOptions (Just False) (Just True))
53-
, chk "NO doc formatting" _documentFormattingProvider (Just $ InL False)
53+
, chk "NO doc formatting" _documentFormattingProvider Nothing
5454
, chk "NO doc range formatting"
55-
_documentRangeFormattingProvider (Just $ InL False)
55+
_documentRangeFormattingProvider Nothing
5656
, chk "NO doc formatting on typing"
5757
_documentOnTypeFormattingProvider Nothing
58-
, chk "NO renaming" _renameProvider (Just $ InL False)
58+
, chk "NO renaming" _renameProvider Nothing
5959
, chk "NO doc link" _documentLinkProvider Nothing
60-
, chk "NO color" (^. L.colorProvider) (Just $ InL False)
61-
, chk "NO folding range" _foldingRangeProvider (Just $ InL False)
60+
, chk "NO color" (^. L.colorProvider) Nothing
61+
, chk "NO folding range" _foldingRangeProvider Nothing
6262
, che " execute command" _executeCommandProvider [typeLensCommandId, blockCommandId]
6363
, chk " workspace" (^. L.workspace) (Just $ #workspaceFolders .== Just WorkspaceFoldersServerCapabilities{_supported = Just True, _changeNotifications = Just ( InR True )}
6464
.+ #fileOperations .== Nothing)

Diff for: ghcide/test/exe/PositionMappingTests.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -6,8 +6,8 @@ module PositionMappingTests (tests) where
66
import qualified Data.EnumMap.Strict as EM
77
import Data.Row
88
import qualified Data.Text as T
9-
import Data.Text.Utf16.Rope (Rope)
10-
import qualified Data.Text.Utf16.Rope as Rope
9+
import Data.Text.Utf16.Rope.Mixed (Rope)
10+
import qualified Data.Text.Utf16.Rope.Mixed as Rope
1111
import Development.IDE.Core.PositionMapping (PositionResult (..),
1212
fromCurrent,
1313
positionResultToMaybe,

Diff for: ghcide/test/exe/WatchedFileTests.hs

+2
Original file line numberDiff line numberDiff line change
@@ -28,6 +28,7 @@ tests = testGroup "watched files"
2828
[ testSession' "workspace files" $ \sessionDir -> do
2929
liftIO $ writeFile (sessionDir </> "hie.yaml") "cradle: {direct: {arguments: [\"-isrc\", \"A\", \"WatchedFilesMissingModule\"]}}"
3030
_doc <- createDoc "A.hs" "haskell" "{-#LANGUAGE NoImplicitPrelude #-}\nmodule A where\nimport WatchedFilesMissingModule"
31+
setIgnoringRegistrationRequests False
3132
watchedFileRegs <- getWatchedFilesSubscriptionsUntil SMethod_TextDocumentPublishDiagnostics
3233

3334
-- Expect 2 subscriptions: one for all .hs files and one for the hie.yaml cradle
@@ -38,6 +39,7 @@ tests = testGroup "watched files"
3839
let yaml = "cradle: {direct: {arguments: [\"-i" <> tail(init(show tmpDir)) <> "\", \"A\", \"WatchedFilesMissingModule\"]}}"
3940
liftIO $ writeFile (sessionDir </> "hie.yaml") yaml
4041
_doc <- createDoc "A.hs" "haskell" "{-# LANGUAGE NoImplicitPrelude#-}\nmodule A where\nimport WatchedFilesMissingModule"
42+
setIgnoringRegistrationRequests False
4143
watchedFileRegs <- getWatchedFilesSubscriptionsUntil SMethod_TextDocumentPublishDiagnostics
4244

4345
-- Expect 2 subscriptions: one for all .hs files and one for the hie.yaml cradle

Diff for: ghcide/test/ghcide-test-utils.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ library
3535
lsp-types,
3636
hls-plugin-api,
3737
lens,
38-
lsp-test ^>= 0.16,
38+
lsp-test ^>= 0.17,
3939
tasty-hunit >= 0.10,
4040
text,
4141
row-types,

Diff for: haskell-language-server.cabal

+7-6
Original file line numberDiff line numberDiff line change
@@ -181,7 +181,7 @@ library hls-cabal-plugin
181181
, hls-plugin-api == 2.6.0.0
182182
, hls-graph == 2.6.0.0
183183
, lens
184-
, lsp ^>=2.3
184+
, lsp ^>=2.4
185185
, lsp-types ^>=2.1
186186
, regex-tdfa ^>=1.3.1
187187
, stm
@@ -206,6 +206,7 @@ test-suite hls-cabal-plugin-tests
206206
, bytestring
207207
, Cabal-syntax >= 3.7
208208
, filepath
209+
, ghcide
209210
, haskell-language-server:hls-cabal-plugin
210211
, hls-test-utils == 2.6.0.0
211212
, lens
@@ -309,7 +310,7 @@ library hls-call-hierarchy-plugin
309310
, hiedb
310311
, hls-plugin-api == 2.6.0.0
311312
, lens
312-
, lsp >=2.3
313+
, lsp >=2.4
313314
, sqlite-simple
314315
, text
315316

@@ -876,7 +877,7 @@ library hls-alternate-number-format-plugin
876877
, hls-graph
877878
, hls-plugin-api == 2.6.0.0
878879
, lens
879-
, lsp ^>=2.3.0.0
880+
, lsp ^>=2.4
880881
, mtl
881882
, regex-tdfa
882883
, syb
@@ -1091,7 +1092,7 @@ library hls-gadt-plugin
10911092
, hls-plugin-api == 2.6.0.0
10921093
, haskell-language-server:hls-refactor-plugin
10931094
, lens
1094-
, lsp >=2.3
1095+
, lsp >=2.4
10951096
, mtl
10961097
, text
10971098
, transformers
@@ -1137,7 +1138,7 @@ library hls-explicit-fixity-plugin
11371138
, ghcide == 2.6.0.0
11381139
, hashable
11391140
, hls-plugin-api == 2.6.0.0
1140-
, lsp >=2.3
1141+
, lsp >=2.4
11411142
, text
11421143

11431144
default-extensions: DataKinds
@@ -1566,7 +1567,7 @@ library hls-semantic-tokens-plugin
15661567
, ghcide == 2.6.0.0
15671568
, hls-plugin-api == 2.6.0.0
15681569
, lens
1569-
, lsp >=2.3
1570+
, lsp >=2.4
15701571
, text
15711572
, transformers
15721573
, bytestring

Diff for: hls-plugin-api/hls-plugin-api.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -69,7 +69,7 @@ library
6969
, hls-graph == 2.6.0.0
7070
, lens
7171
, lens-aeson
72-
, lsp ^>=2.3
72+
, lsp ^>=2.4
7373
, megaparsec >=9.0
7474
, mtl
7575
, opentelemetry >=0.4

0 commit comments

Comments
 (0)