Skip to content

Commit

Permalink
Bump lsp versions
Browse files Browse the repository at this point in the history
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
  • Loading branch information
michaelpj committed Feb 5, 2024
1 parent b91c907 commit 0cb5bf9
Show file tree
Hide file tree
Showing 42 changed files with 153 additions and 151 deletions.
2 changes: 1 addition & 1 deletion cabal.project
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ packages:
./hls-plugin-api
./hls-test-utils

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

tests: True
test-show-details: direct
Expand Down
2 changes: 1 addition & 1 deletion ghcide-bench/ghcide-bench.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,7 @@ test-suite test
base,
extra,
ghcide-bench,
lsp-test ^>= 0.16,
lsp-test ^>= 0.17,
tasty,
tasty-hunit >= 0.10,
tasty-rerun,
Expand Down
6 changes: 3 additions & 3 deletions ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,7 @@ library
, implicit-hie >= 0.1.4.0 && < 0.1.5
, lens
, list-t
, lsp ^>=2.3.0.0
, lsp ^>=2.4.0.0
, lsp-types ^>=2.1.0.0
, mtl
, opentelemetry >=0.6.1
Expand Down Expand Up @@ -180,6 +180,7 @@ library
Development.IDE.Plugin
Development.IDE.Plugin.Completions
Development.IDE.Plugin.Completions.Types
Development.IDE.Plugin.Completions.Logic
Development.IDE.Plugin.HLS
Development.IDE.Plugin.HLS.GhcIde
Development.IDE.Plugin.Test
Expand Down Expand Up @@ -207,7 +208,6 @@ library
Development.IDE.Core.FileExists
Development.IDE.GHC.CPP
Development.IDE.GHC.Warnings
Development.IDE.Plugin.Completions.Logic
Development.IDE.Session.VersionCheck
Development.IDE.Types.Action

Expand Down Expand Up @@ -326,7 +326,7 @@ test-suite ghcide-tests
, lens
, list-t
, lsp
, lsp-test ^>=0.16.0.0
, lsp-test ^>=0.17.0.0
, lsp-types
, monoid-subclasses
, mtl
Expand Down
2 changes: 1 addition & 1 deletion ghcide/session-loader/Development/IDE/Session.hs
Original file line number Diff line number Diff line change
Expand Up @@ -635,7 +635,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} dir = do
-- Display a user friendly progress message here: They probably don't know what a cradle is
let progMsg = "Setting up " <> T.pack (takeBaseName (cradleRootDir cradle))
<> " (for " <> T.pack lfp <> ")"
eopts <- mRunLspTCallback lspEnv (withIndefiniteProgress progMsg NotCancellable) $
eopts <- mRunLspTCallback lspEnv (\act -> withIndefiniteProgress progMsg Nothing NotCancellable (const act)) $
withTrace "Load cradle" $ \addTag -> do
addTag "file" lfp
old_files <- readIORef cradle_files
Expand Down
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/Core/FileStore.hs
Original file line number Diff line number Diff line change
Expand Up @@ -183,7 +183,7 @@ getFileContentsImpl file = do
time <- use_ GetModificationTime file
res <- do
mbVirtual <- getVirtualFile file
pure $ Rope.toText . _file_text <$> mbVirtual
pure $ virtualFileText <$> mbVirtual
pure ([], Just (time, res))

-- | Returns the modification time and the contents.
Expand Down
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/Core/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -575,7 +575,7 @@ persistentHieFileRule recorder = addPersistentRule GetHieAst $ \file -> runMaybe
vfsData <- liftIO $ _vfsMap <$> readTVarIO vfsRef
(currentSource, ver) <- liftIO $ case M.lookup (filePathToUri' file) vfsData of
Nothing -> (,Nothing) . T.decodeUtf8 <$> BS.readFile (fromNormalizedFilePath file)
Just vf -> pure (Rope.toText $ _file_text vf, Just $ _lsp_version vf)
Just vf -> pure (virtualFileText vf, Just $ virtualFileVersion vf)
let refmap = Compat.generateReferencesMap . Compat.getAsts . Compat.hie_asts $ res
del = deltaFromDiff (T.decodeUtf8 $ Compat.hie_hs_src res) currentSource
pure (HAR (Compat.hie_module res) (Compat.hie_asts res) refmap mempty (HieFromDisk res),del,ver)
Expand Down
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/Plugin/Completions/Logic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ import qualified Language.LSP.VFS as VFS
import Text.Fuzzy.Parallel (Scored (score),
original)

import qualified Data.Text.Utf16.Rope as Rope
import qualified Data.Text.Utf16.Rope.Mixed as Rope
import Development.IDE hiding (line)

import Development.IDE.Spans.AtPoint (pointCommand)
Expand Down
10 changes: 5 additions & 5 deletions ghcide/src/Development/IDE/Plugin/HLS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -177,7 +177,7 @@ executeCommandHandlers recorder ecs = requestHandler SMethod_WorkspaceExecuteCom

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

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

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

runPluginCommand :: IdeState -> PluginId -> CommandId -> A.Value -> LSP.LspT Config IO (Either ResponseError (A.Value |? Null))
runPluginCommand ide p com arg =
runPluginCommand :: IdeState -> PluginId -> CommandId -> Maybe ProgressToken -> A.Value -> LSP.LspT Config IO (Either ResponseError (A.Value |? Null))
runPluginCommand ide p com mtoken arg =
case Map.lookup p pluginMap of
Nothing -> logAndReturnError recorder p (InR ErrorCodes_InvalidRequest) (pluginDoesntExist p)
Just xs -> case List.find ((com ==) . commandId) xs of
Nothing -> logAndReturnError recorder p (InR ErrorCodes_InvalidRequest) (commandDoesntExist com p xs)
Just (PluginCommand _ _ f) -> case A.fromJSON arg of
A.Error err -> logAndReturnError recorder p (InR ErrorCodes_InvalidParams) (failedToParseArgs com p err arg)
A.Success a -> do
res <- runExceptT (f ide a) `catchAny` -- See Note [Exception handling in plugins]
res <- runExceptT (f ide mtoken a) `catchAny` -- See Note [Exception handling in plugins]
(\e -> pure $ Left $ PluginInternalError (exceptionInPlugin p SMethod_WorkspaceExecuteCommand e))
case res of
(Left (PluginRequestRefused r)) ->
Expand Down
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/Plugin/Test.hs
Original file line number Diff line number Diff line change
Expand Up @@ -170,7 +170,7 @@ blockCommandDescriptor plId = (defaultPluginDescriptor plId "") {
}

blockCommandHandler :: CommandFunction state ExecuteCommandParams
blockCommandHandler _ideState _params = do
blockCommandHandler _ideState _ _params = do
lift $ LSP.sendNotification (SMethod_CustomMethod (Proxy @"ghcide/blocking/command")) A.Null
liftIO $ threadDelay maxBound
pure $ InR Null
2 changes: 1 addition & 1 deletion ghcide/src/Development/IDE/Plugin/TypeLenses.hs
Original file line number Diff line number Diff line change
Expand Up @@ -192,7 +192,7 @@ generateLensCommand pId uri title edit =
-- recompute the edit upon command. Hence the command here just takes a edit
-- and applies it.
commandHandler :: CommandFunction IdeState WorkspaceEdit
commandHandler _ideState wedit = do
commandHandler _ideState _ wedit = do
_ <- lift $ LSP.sendRequest SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wedit) (\_ -> pure ())
pure $ InR Null

Expand Down
1 change: 0 additions & 1 deletion ghcide/test/exe/ClientSettingsTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ tests :: TestTree
tests = testGroup "client settings handling"
[ testSession "ghcide restarts shake session on config changes" $ do
setIgnoringLogNotifications False
void $ skipManyTill anyMessage $ message SMethod_ClientRegisterCapability
void $ createDoc "A.hs" "haskell" "module A where"
waitForProgressDone
setConfigSection "haskell" $ toJSON (def :: Config)
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/exe/ExceptionTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,7 @@ tests recorder logger = do
plugins = pluginDescToIdePlugins $
[ (defaultPluginDescriptor pluginId "")
{ pluginCommands =
[ PluginCommand commandId "Causes an exception" $ \_ (_::Int) -> do
[ PluginCommand commandId "Causes an exception" $ \_ _ (_::Int) -> do
_ <- liftIO $ throwIO DivideByZero
pure (InR Null)
]
Expand Down
30 changes: 15 additions & 15 deletions ghcide/test/exe/InitializeResponseTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,29 +36,29 @@ tests = withResource acquire release tests where
tests getInitializeResponse =
testGroup "initialize response capabilities"
[ chk " text doc sync" _textDocumentSync tds
, chk " hover" _hoverProvider (Just $ InL True)
, chk " completion" _completionProvider (Just $ CompletionOptions Nothing (Just ["."]) Nothing (Just True) Nothing)
, chk " hover" _hoverProvider (Just $ InR (HoverOptions (Just False)))
, chk " completion" _completionProvider (Just $ CompletionOptions (Just False) (Just ["."]) Nothing (Just True) Nothing)
, chk "NO signature help" _signatureHelpProvider Nothing
, chk " goto definition" _definitionProvider (Just $ InL True)
, chk " goto type definition" _typeDefinitionProvider (Just $ InL True)
, chk " goto definition" _definitionProvider (Just $ InR (DefinitionOptions (Just False)))
, chk " goto type definition" _typeDefinitionProvider (Just $ InR (InL (TypeDefinitionOptions (Just False))))
-- BUG in lsp-test, this test fails, just change the accepted response
-- for now
, chk "NO goto implementation" _implementationProvider (Just $ InL False)
, chk " find references" _referencesProvider (Just $ InL True)
, chk " doc highlight" _documentHighlightProvider (Just $ InL True)
, chk " doc symbol" _documentSymbolProvider (Just $ InL True)
, chk " workspace symbol" _workspaceSymbolProvider (Just $ InL True)
, chk " code action" _codeActionProvider (Just $ InL False)
, chk "NO goto implementation" _implementationProvider Nothing
, chk " find references" _referencesProvider (Just $ InR (ReferenceOptions (Just False)))
, chk " doc highlight" _documentHighlightProvider (Just $ InR (DocumentHighlightOptions (Just False)))
, chk " doc symbol" _documentSymbolProvider (Just $ InR (DocumentSymbolOptions (Just False) Nothing))
, chk " workspace symbol" _workspaceSymbolProvider (Just $ InR (WorkspaceSymbolOptions (Just False) (Just False)))
, chk "NO code action" _codeActionProvider Nothing
, chk " code lens" _codeLensProvider (Just $ CodeLensOptions (Just False) (Just True))
, chk "NO doc formatting" _documentFormattingProvider (Just $ InL False)
, chk "NO doc formatting" _documentFormattingProvider Nothing
, chk "NO doc range formatting"
_documentRangeFormattingProvider (Just $ InL False)
_documentRangeFormattingProvider Nothing
, chk "NO doc formatting on typing"
_documentOnTypeFormattingProvider Nothing
, chk "NO renaming" _renameProvider (Just $ InL False)
, chk "NO renaming" _renameProvider Nothing
, chk "NO doc link" _documentLinkProvider Nothing
, chk "NO color" (^. L.colorProvider) (Just $ InL False)
, chk "NO folding range" _foldingRangeProvider (Just $ InL False)
, chk "NO color" (^. L.colorProvider) Nothing
, chk "NO folding range" _foldingRangeProvider Nothing
, che " execute command" _executeCommandProvider [typeLensCommandId, blockCommandId]
, chk " workspace" (^. L.workspace) (Just $ #workspaceFolders .== Just WorkspaceFoldersServerCapabilities{_supported = Just True, _changeNotifications = Just ( InR True )}
.+ #fileOperations .== Nothing)
Expand Down
4 changes: 2 additions & 2 deletions ghcide/test/exe/PositionMappingTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,8 @@ module PositionMappingTests (tests) where
import qualified Data.EnumMap.Strict as EM
import Data.Row
import qualified Data.Text as T
import Data.Text.Utf16.Rope (Rope)
import qualified Data.Text.Utf16.Rope as Rope
import Data.Text.Utf16.Rope.Mixed (Rope)
import qualified Data.Text.Utf16.Rope.Mixed as Rope
import Development.IDE.Core.PositionMapping (PositionResult (..),
fromCurrent,
positionResultToMaybe,
Expand Down
2 changes: 2 additions & 0 deletions ghcide/test/exe/WatchedFileTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ tests = testGroup "watched files"
[ testSession' "workspace files" $ \sessionDir -> do
liftIO $ writeFile (sessionDir </> "hie.yaml") "cradle: {direct: {arguments: [\"-isrc\", \"A\", \"WatchedFilesMissingModule\"]}}"
_doc <- createDoc "A.hs" "haskell" "{-#LANGUAGE NoImplicitPrelude #-}\nmodule A where\nimport WatchedFilesMissingModule"
setIgnoringRegistrationRequests False
watchedFileRegs <- getWatchedFilesSubscriptionsUntil SMethod_TextDocumentPublishDiagnostics

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

-- Expect 2 subscriptions: one for all .hs files and one for the hie.yaml cradle
Expand Down
2 changes: 1 addition & 1 deletion ghcide/test/ghcide-test-utils.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ library
lsp-types,
hls-plugin-api,
lens,
lsp-test ^>= 0.16,
lsp-test ^>= 0.17,
tasty-hunit >= 0.10,
text,
row-types,
Expand Down
15 changes: 8 additions & 7 deletions haskell-language-server.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -179,7 +179,7 @@ library hls-cabal-plugin
, hls-plugin-api == 2.6.0.0
, hls-graph == 2.6.0.0
, lens
, lsp ^>=2.3
, lsp ^>=2.4
, lsp-types ^>=2.1
, regex-tdfa ^>=1.3.1
, stm
Expand All @@ -204,6 +204,7 @@ test-suite hls-cabal-plugin-tests
, bytestring
, Cabal-syntax >= 3.7
, filepath
, ghcide
, haskell-language-server:hls-cabal-plugin
, hls-test-utils == 2.6.0.0
, lens
Expand Down Expand Up @@ -307,7 +308,7 @@ library hls-call-hierarchy-plugin
, hiedb
, hls-plugin-api == 2.6.0.0
, lens
, lsp >=2.3
, lsp >=2.4
, sqlite-simple
, text

Expand Down Expand Up @@ -886,7 +887,7 @@ library hls-alternate-number-format-plugin
, hls-graph
, hls-plugin-api == 2.6.0.0
, lens
, lsp ^>=2.3.0.0
, lsp ^>=2.4
, mtl
, regex-tdfa
, syb
Expand Down Expand Up @@ -1106,7 +1107,7 @@ library hls-gadt-plugin
, hls-plugin-api == 2.6.0.0
, haskell-language-server:hls-refactor-plugin
, lens
, lsp >=2.3
, lsp >=2.4
, mtl
, text
, transformers
Expand Down Expand Up @@ -1152,7 +1153,7 @@ library hls-explicit-fixity-plugin
, ghcide == 2.6.0.0
, hashable
, hls-plugin-api == 2.6.0.0
, lsp >=2.3
, lsp >=2.4
, text

default-extensions: DataKinds
Expand Down Expand Up @@ -1583,7 +1584,7 @@ library hls-semantic-tokens-plugin
, ghcide == 2.6.0.0
, hls-plugin-api == 2.6.0.0
, lens
, lsp >=2.3
, lsp >=2.4
, sqlite-simple
, text
, unordered-containers
Expand Down Expand Up @@ -1684,7 +1685,7 @@ library
, ghc
, ghcide == 2.6.0.0
, githash >=0.1.6.1
, lsp >= 2.3.0.0
, lsp >= 2.4.0.0
, hie-bios
, hiedb
, hls-plugin-api == 2.6.0.0
Expand Down
2 changes: 1 addition & 1 deletion hls-plugin-api/hls-plugin-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@ library
, hls-graph == 2.6.0.0
, lens
, lens-aeson
, lsp ^>=2.3
, lsp ^>=2.4
, megaparsec >=9.0
, mtl
, opentelemetry >=0.4
Expand Down
Loading

0 comments on commit 0cb5bf9

Please sign in to comment.