Skip to content

Commit 6d1f1a5

Browse files
authored
Update to lsp-1.2 (#1631)
* Update to lsp-1.2 * fix stack * fix splice plugin tests * fix tactic plugin tests * fix some tests * fix some tests * fix outline tests * hlint * fix func-test
1 parent d60dee0 commit 6d1f1a5

File tree

49 files changed

+212
-191
lines changed

Some content is hidden

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

49 files changed

+212
-191
lines changed

cabal.project

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ package ghcide
2727

2828
write-ghc-environment-files: never
2929

30-
index-state: 2021-03-02T21:23:14Z
30+
index-state: 2021-03-29T21:23:14Z
3131

3232
allow-newer:
3333
active:base,

ghcide/exe/Main.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,6 @@ import Control.Monad.Extra (unless, when, whenJust)
1212
import qualified Data.Aeson.Encode.Pretty as A
1313
import Data.Default (Default (def))
1414
import Data.List.Extra (upper)
15-
import Data.Maybe (fromMaybe)
1615
import qualified Data.Text as T
1716
import qualified Data.Text.IO as T
1817
import Data.Text.Lazy.Encoding (decodeUtf8)
@@ -122,7 +121,7 @@ main = do
122121
then Test.plugin
123122
else mempty
124123

125-
,Main.argsIdeOptions = \(fromMaybe def -> config) sessionLoader ->
124+
,Main.argsIdeOptions = \config sessionLoader ->
126125
let defOptions = defaultIdeOptions sessionLoader
127126
in defOptions
128127
{ optShakeProfiling = argsShakeProfiling

ghcide/ghcide.cabal

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -59,8 +59,8 @@ library
5959
hls-plugin-api ^>= 1.1.0.0,
6060
lens,
6161
hiedb == 0.3.0.1,
62-
lsp-types == 1.1.*,
63-
lsp == 1.1.1.0,
62+
lsp-types == 1.2.*,
63+
lsp == 1.2.*,
6464
mtl,
6565
network-uri,
6666
parallel,
@@ -339,7 +339,7 @@ test-suite ghcide-tests
339339
hls-plugin-api,
340340
network-uri,
341341
lens,
342-
lsp-test == 0.13.0.0,
342+
lsp-test == 0.14.0.0,
343343
optparse-applicative,
344344
process,
345345
QuickCheck,
@@ -396,7 +396,7 @@ executable ghcide-bench
396396
extra,
397397
filepath,
398398
ghcide,
399-
lsp-test == 0.13.0.0,
399+
lsp-test == 0.14.0.0,
400400
optparse-applicative,
401401
process,
402402
safe-exceptions,

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 4 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ module Development.IDE.Core.Shake(
5050
getIdeOptions,
5151
getIdeOptionsIO,
5252
GlobalIdeOptions(..),
53-
getClientConfig,
53+
HLS.getClientConfig,
5454
getPluginConfig,
5555
garbageCollect,
5656
knownTargets,
@@ -230,14 +230,10 @@ getShakeExtrasRules = do
230230
Just x <- getShakeExtraRules @ShakeExtras
231231
return x
232232

233-
getClientConfig :: LSP.MonadLsp Config m => ShakeExtras -> m Config
234-
getClientConfig ShakeExtras { defaultConfig } =
235-
fromMaybe defaultConfig <$> HLS.getClientConfig
236-
237233
getPluginConfig
238-
:: LSP.MonadLsp Config m => ShakeExtras -> PluginId -> m PluginConfig
239-
getPluginConfig extras plugin = do
240-
config <- getClientConfig extras
234+
:: LSP.MonadLsp Config m => PluginId -> m PluginConfig
235+
getPluginConfig plugin = do
236+
config <- HLS.getClientConfig
241237
return $ HLS.configForPlugin config plugin
242238

243239
-- | Register a function that will be called to get the "stale" result of a rule, possibly from disk

ghcide/src/Development/IDE/LSP/LanguageServer.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,6 @@ import Data.Aeson (Value)
2323
import Data.Maybe
2424
import qualified Data.Set as Set
2525
import qualified Data.Text as T
26-
import qualified Development.IDE.GHC.Util as Ghcide
2726
import Development.IDE.LSP.Server
2827
import Development.IDE.Session (runWithDb)
2928
import Ide.Types (traceWithSpan)
@@ -50,11 +49,12 @@ runLanguageServer
5049
-> Handle -- input
5150
-> Handle -- output
5251
-> (FilePath -> IO FilePath) -- ^ Map root paths to the location of the hiedb for the project
53-
-> (IdeState -> Value -> IO (Either T.Text config))
52+
-> config
53+
-> (config -> Value -> Either T.Text config)
5454
-> LSP.Handlers (ServerM config)
5555
-> (LSP.LanguageContextEnv config -> VFSHandle -> Maybe FilePath -> HieDb -> IndexQueue -> IO IdeState)
5656
-> IO ()
57-
runLanguageServer options inH outH getHieDbLoc onConfigurationChange userHandlers getIdeState = do
57+
runLanguageServer options inH outH getHieDbLoc defaultConfig onConfigurationChange userHandlers getIdeState = do
5858

5959
-- These barriers are signaled when the threads reading from these chans exit.
6060
-- This should not happen but if it does, we will make sure that the whole server
@@ -103,9 +103,8 @@ runLanguageServer options inH outH getHieDbLoc onConfigurationChange userHandler
103103

104104

105105
let serverDefinition = LSP.ServerDefinition
106-
{ LSP.onConfigurationChange = \v -> do
107-
(_chan, ide) <- ask
108-
liftIO $ onConfigurationChange ide v
106+
{ LSP.onConfigurationChange = onConfigurationChange
107+
, LSP.defaultConfig = defaultConfig
109108
, LSP.doInitialize = handleInit exit clearReqId waitForCancel clientMsgChan
110109
, LSP.staticHandlers = asyncHandlers
111110
, LSP.interpretHandler = \(env, st) -> LSP.Iso (LSP.runLspT env . flip runReaderT (clientMsgChan,st)) liftIO

ghcide/src/Development/IDE/LSP/Notifications.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,6 @@ import qualified Language.LSP.Types.Capabilities as LSP
1919
import Development.IDE.Core.IdeConfiguration
2020
import Development.IDE.Core.Service
2121
import Development.IDE.Core.Shake
22-
import Development.IDE.LSP.Server
2322
import Development.IDE.Types.Location
2423
import Development.IDE.Types.Logger
2524
import Development.IDE.Types.Options

ghcide/src/Development/IDE/LSP/Outline.hs

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ import qualified Data.Text as T
1919
import Development.IDE.Core.Rules
2020
import Development.IDE.Core.Shake
2121
import Development.IDE.GHC.Compat
22-
import Development.IDE.GHC.Error (realSrcSpanToRange)
22+
import Development.IDE.GHC.Error (realSrcSpanToRange, rangeToRealSrcSpan)
2323
import Development.IDE.Types.Location
2424
import Language.LSP.Server (LspM)
2525
import Language.LSP.Types
@@ -183,12 +183,10 @@ documentSymbolForImportSummary importSymbols =
183183
mergeRanges xs = Range (minimum $ map _start xs) (maximum $ map _end xs)
184184
importRange = mergeRanges $ map (_range :: DocumentSymbol -> Range) importSymbols
185185
in
186-
Just (defDocumentSymbol empty :: DocumentSymbol)
186+
Just (defDocumentSymbol (rangeToRealSrcSpan "" importRange))
187187
{ _name = "imports"
188188
, _kind = SkModule
189189
, _children = Just (List importSymbols)
190-
, _range = importRange
191-
, _selectionRange = importRange
192190
}
193191

194192
documentSymbolForImport :: Located (ImportDecl GhcPs) -> Maybe DocumentSymbol
@@ -213,6 +211,7 @@ defDocumentSymbol l = DocumentSymbol { .. } where
213211
_range = realSrcSpanToRange l
214212
_selectionRange = realSrcSpanToRange l
215213
_children = Nothing
214+
_tags = Nothing
216215

217216
showRdrName :: RdrName -> Text
218217
showRdrName = pprText

ghcide/src/Development/IDE/Main.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -88,7 +88,7 @@ data Arguments = Arguments
8888
, argsHlsPlugins :: IdePlugins IdeState
8989
, argsGhcidePlugin :: Plugin Config -- ^ Deprecated
9090
, argsSessionLoadingOptions :: SessionLoadingOptions
91-
, argsIdeOptions :: Maybe Config -> Action IdeGhcSession -> IdeOptions
91+
, argsIdeOptions :: Config -> Action IdeGhcSession -> IdeOptions
9292
, argsLspOptions :: LSP.Options
9393
, argsDefaultHlsConfig :: Config
9494
, argsGetHieDbLoc :: FilePath -> IO FilePath -- ^ Map project roots to the location of the hiedb for the project
@@ -142,11 +142,11 @@ defaultMain Arguments{..} = do
142142
logger <- argsLogger
143143
hSetBuffering stderr LineBuffering
144144

145-
let hlsPlugin = asGhcIdePlugin argsDefaultHlsConfig argsHlsPlugins
145+
let hlsPlugin = asGhcIdePlugin argsHlsPlugins
146146
hlsCommands = allLspCmdIds' pid argsHlsPlugins
147147
plugins = hlsPlugin <> argsGhcidePlugin
148148
options = argsLspOptions { LSP.executeCommandCommands = Just hlsCommands }
149-
argsOnConfigChange _ide = pure . getConfigFromNotification argsDefaultHlsConfig
149+
argsOnConfigChange = getConfigFromNotification
150150
rules = argsRules >> pluginRules plugins
151151

152152
debouncer <- argsDebouncer
@@ -158,7 +158,7 @@ defaultMain Arguments{..} = do
158158
t <- offsetTime
159159
hPutStrLn stderr "Starting LSP server..."
160160
hPutStrLn stderr "If you are seeing this in a terminal, you probably should have run ghcide WITHOUT the --lsp option!"
161-
runLanguageServer options inH outH argsGetHieDbLoc argsOnConfigChange (pluginHandlers plugins) $ \env vfs rootPath hiedb hieChan -> do
161+
runLanguageServer options inH outH argsGetHieDbLoc argsDefaultHlsConfig argsOnConfigChange (pluginHandlers plugins) $ \env vfs rootPath hiedb hieChan -> do
162162
t <- t
163163
hPutStrLn stderr $ "Started LSP server in " ++ showDuration t
164164

@@ -214,7 +214,7 @@ defaultMain Arguments{..} = do
214214
putStrLn "\nStep 3/4: Initializing the IDE"
215215
vfs <- makeVFSHandle
216216
sessionLoader <- loadSessionWithOptions argsSessionLoadingOptions dir
217-
let options = (argsIdeOptions Nothing sessionLoader)
217+
let options = (argsIdeOptions argsDefaultHlsConfig sessionLoader)
218218
{ optCheckParents = pure NeverCheck
219219
, optCheckProject = pure False
220220
}

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -117,7 +117,7 @@ codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range Cod
117117
actions =
118118
[ mkCA title kind isPreferred [x] edit
119119
| x <- xs, (title, kind, isPreferred, tedit) <- suggestAction $ CodeActionArgs exportsMap ideOptions parsedModule text df annotatedPS tcM har bindings gblSigs x
120-
, let edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing
120+
, let edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing Nothing
121121
]
122122
actions' = caRemoveRedundantImports parsedModule text diag xs uri
123123
<> actions
@@ -126,7 +126,7 @@ codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range Cod
126126

127127
mkCA :: T.Text -> Maybe CodeActionKind -> Maybe Bool -> [Diagnostic] -> WorkspaceEdit -> (Command |? CodeAction)
128128
mkCA title kind isPreferred diags edit =
129-
InR $ CodeAction title kind (Just $ List diags) isPreferred Nothing (Just edit) Nothing
129+
InR $ CodeAction title kind (Just $ List diags) isPreferred Nothing (Just edit) Nothing Nothing
130130

131131
suggestAction :: CodeActionArgs -> GhcideCodeActions
132132
suggestAction caa =
@@ -282,6 +282,7 @@ caRemoveRedundantImports m contents digs ctxDigs uri
282282
removeSingle title tedit diagnostic = mkCA title (Just CodeActionQuickFix) Nothing [diagnostic] WorkspaceEdit{..} where
283283
_changes = Just $ Map.singleton uri $ List tedit
284284
_documentChanges = Nothing
285+
_changeAnnotations = Nothing
285286
removeAll tedit = InR $ CodeAction{..} where
286287
_changes = Just $ Map.singleton uri $ List tedit
287288
_title = "Remove all redundant imports"
@@ -292,6 +293,8 @@ caRemoveRedundantImports m contents digs ctxDigs uri
292293
_isPreferred = Nothing
293294
_command = Nothing
294295
_disabled = Nothing
296+
_xdata = Nothing
297+
_changeAnnotations = Nothing
295298

296299
caRemoveInvalidExports :: Maybe ParsedModule -> Maybe T.Text -> [Diagnostic] -> [Diagnostic] -> Uri -> [Command |? CodeAction]
297300
caRemoveInvalidExports m contents digs ctxDigs uri
@@ -328,6 +331,8 @@ caRemoveInvalidExports m contents digs ctxDigs uri
328331
_command = Nothing
329332
_isPreferred = Nothing
330333
_disabled = Nothing
334+
_xdata = Nothing
335+
_changeAnnotations = Nothing
331336
removeAll [] = Nothing
332337
removeAll ranges = Just $ InR $ CodeAction{..} where
333338
tedit = concatMap (\r -> [TextEdit r ""]) ranges
@@ -340,6 +345,8 @@ caRemoveInvalidExports m contents digs ctxDigs uri
340345
_command = Nothing
341346
_isPreferred = Nothing
342347
_disabled = Nothing
348+
_xdata = Nothing
349+
_changeAnnotations = Nothing
343350

344351
suggestRemoveRedundantExport :: ParsedModule -> Diagnostic -> Maybe (T.Text, [Range])
345352
suggestRemoveRedundantExport ParsedModule{pm_parsed_source = L _ HsModule{..}} Diagnostic{..}

ghcide/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -83,6 +83,7 @@ rewriteToWEdit dflags uri anns r = do
8383
WorkspaceEdit
8484
{ _changes = Just (fromList [(uri, List edits)])
8585
, _documentChanges = Nothing
86+
, _changeAnnotations = Nothing
8687
}
8788

8889
------------------------------------------------------------------------------

ghcide/src/Development/IDE/Plugin/Completions/Logic.hs

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -186,6 +186,7 @@ mkCompl
186186
_filterText = Nothing,
187187
_insertText = Just insertText,
188188
_insertTextFormat = Just Snippet,
189+
_insertTextMode = Nothing,
189190
_textEdit = Nothing,
190191
_additionalTextEdits = Nothing,
191192
_commitCharacters = Nothing,
@@ -272,27 +273,27 @@ mkModCompl :: T.Text -> CompletionItem
272273
mkModCompl label =
273274
CompletionItem label (Just CiModule) Nothing Nothing
274275
Nothing Nothing Nothing Nothing Nothing Nothing Nothing
275-
Nothing Nothing Nothing Nothing Nothing
276+
Nothing Nothing Nothing Nothing Nothing Nothing
276277

277278
mkImportCompl :: T.Text -> T.Text -> CompletionItem
278279
mkImportCompl enteredQual label =
279280
CompletionItem m (Just CiModule) Nothing (Just label)
280281
Nothing Nothing Nothing Nothing Nothing Nothing Nothing
281-
Nothing Nothing Nothing Nothing Nothing
282+
Nothing Nothing Nothing Nothing Nothing Nothing
282283
where
283284
m = fromMaybe "" (T.stripPrefix enteredQual label)
284285

285286
mkExtCompl :: T.Text -> CompletionItem
286287
mkExtCompl label =
287288
CompletionItem label (Just CiKeyword) Nothing Nothing
288289
Nothing Nothing Nothing Nothing Nothing Nothing Nothing
289-
Nothing Nothing Nothing Nothing Nothing
290+
Nothing Nothing Nothing Nothing Nothing Nothing
290291

291292
mkPragmaCompl :: T.Text -> T.Text -> CompletionItem
292293
mkPragmaCompl label insertText =
293294
CompletionItem label (Just CiKeyword) Nothing Nothing
294295
Nothing Nothing Nothing Nothing Nothing (Just insertText) (Just Snippet)
295-
Nothing Nothing Nothing Nothing Nothing
296+
Nothing Nothing Nothing Nothing Nothing Nothing
296297

297298

298299
cacheDataProducer :: Uri -> HscEnvEq -> Module -> GlobalRdrEnv-> GlobalRdrEnv -> [LImportDecl GhcPs] -> IO CachedCompletions

ghcide/src/Development/IDE/Plugin/HLS.hs

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,6 @@ import Data.Either
2020
import qualified Data.List as List
2121
import Data.List.NonEmpty (NonEmpty, nonEmpty, toList)
2222
import qualified Data.Map as Map
23-
import Data.Maybe (fromMaybe)
2423
import Data.String
2524
import qualified Data.Text as T
2625
import Development.IDE.Core.Shake
@@ -44,12 +43,12 @@ import UnliftIO.Exception (catchAny)
4443
--
4544

4645
-- | Map a set of plugins to the underlying ghcide engine.
47-
asGhcIdePlugin :: Config -> IdePlugins IdeState -> Plugin Config
48-
asGhcIdePlugin defaultConfig mp =
46+
asGhcIdePlugin :: IdePlugins IdeState -> Plugin Config
47+
asGhcIdePlugin mp =
4948
mkPlugin rulesPlugins HLS.pluginRules <>
5049
mkPlugin executeCommandPlugins HLS.pluginCommands <>
51-
mkPlugin (extensiblePlugins defaultConfig) HLS.pluginHandlers <>
52-
mkPlugin (extensibleNotificationPlugins defaultConfig) HLS.pluginNotificationHandlers
50+
mkPlugin extensiblePlugins HLS.pluginHandlers <>
51+
mkPlugin extensibleNotificationPlugins HLS.pluginNotificationHandlers
5352
where
5453
ls = Map.toList (ipMap mp)
5554

@@ -133,8 +132,8 @@ executeCommandHandlers ecs = requestHandler SWorkspaceExecuteCommand execCmd
133132

134133
-- ---------------------------------------------------------------------
135134

136-
extensiblePlugins :: Config -> [(PluginId, PluginHandlers IdeState)] -> Plugin Config
137-
extensiblePlugins defaultConfig xs = Plugin mempty handlers
135+
extensiblePlugins :: [(PluginId, PluginHandlers IdeState)] -> Plugin Config
136+
extensiblePlugins xs = Plugin mempty handlers
138137
where
139138
IdeHandlers handlers' = foldMap bakePluginId xs
140139
bakePluginId :: (PluginId, PluginHandlers IdeState) -> IdeHandlers
@@ -144,7 +143,7 @@ extensiblePlugins defaultConfig xs = Plugin mempty handlers
144143
handlers = mconcat $ do
145144
(IdeMethod m :=> IdeHandler fs') <- DMap.assocs handlers'
146145
pure $ requestHandler m $ \ide params -> do
147-
config <- fromMaybe defaultConfig <$> Ide.PluginUtils.getClientConfig
146+
config <- Ide.PluginUtils.getClientConfig
148147
let fs = filter (\(pid,_) -> pluginEnabled m pid config) fs'
149148
case nonEmpty fs of
150149
Nothing -> pure $ Left $ ResponseError InvalidRequest
@@ -161,8 +160,8 @@ extensiblePlugins defaultConfig xs = Plugin mempty handlers
161160
pure $ Right $ combineResponses m config caps params xs
162161
-- ---------------------------------------------------------------------
163162

164-
extensibleNotificationPlugins :: Config -> [(PluginId, PluginNotificationHandlers IdeState)] -> Plugin Config
165-
extensibleNotificationPlugins defaultConfig xs = Plugin mempty handlers
163+
extensibleNotificationPlugins :: [(PluginId, PluginNotificationHandlers IdeState)] -> Plugin Config
164+
extensibleNotificationPlugins xs = Plugin mempty handlers
166165
where
167166
IdeNotificationHandlers handlers' = foldMap bakePluginId xs
168167
bakePluginId :: (PluginId, PluginNotificationHandlers IdeState) -> IdeNotificationHandlers
@@ -172,7 +171,7 @@ extensibleNotificationPlugins defaultConfig xs = Plugin mempty handlers
172171
handlers = mconcat $ do
173172
(IdeNotification m :=> IdeNotificationHandler fs') <- DMap.assocs handlers'
174173
pure $ notificationHandler m $ \ide params -> do
175-
config <- fromMaybe defaultConfig <$> Ide.PluginUtils.getClientConfig
174+
config <- Ide.PluginUtils.getClientConfig
176175
let fs = filter (\(pid,_) -> plcGlobalOn $ configForPlugin config pid) fs'
177176
case nonEmpty fs of
178177
Nothing -> do

ghcide/src/Development/IDE/Plugin/TypeLenses.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -117,7 +117,7 @@ codeLensProvider ideState pId CodeLensParams{_textDocument = TextDocumentIdentif
117117
diag <- getDiagnostics ideState
118118
hDiag <- getHiddenDiagnostics ideState
119119

120-
let toWorkSpaceEdit tedit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing
120+
let toWorkSpaceEdit tedit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing Nothing
121121
generateLensForGlobal sig@GlobalBindingTypeSig{..} = do
122122
range <- srcSpanToRange $ gbSrcSpan sig
123123
tedit <- gblBindingTypeSigToEdit sig

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -344,7 +344,7 @@ toUri = fromNormalizedUri . filePathToUri' . toNormalizedFilePath'
344344

345345
defRowToSymbolInfo :: Res DefRow -> Maybe SymbolInformation
346346
defRowToSymbolInfo (DefRow{..}:.(modInfoSrcFile -> Just srcFile))
347-
= Just $ SymbolInformation (showGhc defNameOcc) kind Nothing loc Nothing
347+
= Just $ SymbolInformation (showGhc defNameOcc) kind Nothing Nothing loc Nothing
348348
where
349349
kind
350350
| isVarOcc defNameOcc = SkVariable

0 commit comments

Comments
 (0)