Skip to content

Commit e06469f

Browse files
authored
Enforce max completions over all plugins (#1256)
* Enforce max completions across HLS plugins * Fix pragma completions to prefilter * Fix a completion test * Add a test * Fix another inaccurate test * rename n to limit * Evaluate completion providers in parallel * Evaluate all HLS providers concurrently
1 parent 15c070c commit e06469f

File tree

5 files changed

+52
-32
lines changed

5 files changed

+52
-32
lines changed

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

+2-3
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ import Development.IDE.GHC.Util
3030
import Development.IDE.LSP.Server
3131
import TcRnDriver (tcRnImportDecls)
3232
import Data.Maybe
33-
import Ide.Plugin.Config (Config (completionSnippetsOn, maxCompletions))
33+
import Ide.Plugin.Config (Config (completionSnippetsOn))
3434
import Ide.PluginUtils (getClientConfig)
3535

3636
#if defined(GHC_LIB)
@@ -146,8 +146,7 @@ getCompletionsLSP lsp ide
146146
config <- getClientConfig lsp
147147
let snippets = WithSnippets . completionSnippetsOn $ config
148148
allCompletions <- getCompletions ideOpts cci' parsedMod bindMap pfix' clientCaps snippets
149-
let (topCompletions, rest) = splitAt (maxCompletions config) allCompletions
150-
pure $ CompletionList (CompletionListType (null rest) (List topCompletions))
149+
pure $ Completions (List allCompletions)
151150
_ -> return (Completions $ List [])
152151
_ -> return (Completions $ List [])
153152
_ -> return (Completions $ List [])

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

+33-21
Original file line numberDiff line numberDiff line change
@@ -6,9 +6,10 @@ module Development.IDE.Plugin.HLS
66
) where
77

88
import Control.Exception(SomeException, catch)
9-
import Control.Lens ( (^.) )
9+
import Control.Lens ((^.))
1010
import Control.Monad
1111
import qualified Data.Aeson as J
12+
import qualified Data.DList as DList
1213
import Data.Either
1314
import qualified Data.List as List
1415
import qualified Data.Map as Map
@@ -33,6 +34,7 @@ import Development.Shake (Rules)
3334
import Ide.PluginUtils (getClientConfig, pluginEnabled, getPluginConfig, responseError, getProcessID)
3435
import Development.IDE.Types.Logger (logInfo)
3536
import Development.IDE.Core.Tracing
37+
import Control.Concurrent.Async (mapConcurrently)
3638

3739
-- ---------------------------------------------------------------------
3840

@@ -97,7 +99,7 @@ makeCodeAction cas lf ideState (CodeActionParams docId range context _) = do
9799
if pluginEnabled pluginConfig plcCodeActionsOn
98100
then otTracedProvider pid "codeAction" $ provider lf ideState pid docId range context
99101
else return $ Right (List [])
100-
r <- mapM makeAction cas
102+
r <- mapConcurrently makeAction cas
101103
let actions = filter wasRequested . foldMap unL $ rights r
102104
res <- send caps actions
103105
return $ Right res
@@ -171,7 +173,7 @@ makeCodeLens cas lf ideState params = do
171173
doOneRight (pid, Right a) = [(pid,a)]
172174
doOneRight (_, Left _) = []
173175

174-
r <- mapM makeLens cas
176+
r <- mapConcurrently makeLens cas
175177
case breakdown r of
176178
([],[]) -> return $ Right $ List []
177179
(es,[]) -> return $ Left $ ResponseError InternalError (T.pack $ "codeLens failed:" ++ show es) Nothing
@@ -306,7 +308,7 @@ makeHover hps lf ideState params
306308
if pluginEnabled pluginConfig plcHoverOn
307309
then otTracedProvider pid "hover" $ p ideState params
308310
else return $ Right Nothing
309-
mhs <- mapM makeHover hps
311+
mhs <- mapConcurrently makeHover hps
310312
-- TODO: We should support ServerCapabilities and declare that
311313
-- we don't support hover requests during initialization if we
312314
-- don't have any hover providers
@@ -361,7 +363,7 @@ makeSymbols sps lf ideState params
361363
if pluginEnabled pluginConfig plcSymbolsOn
362364
then otTracedProvider pid "symbols" $ p lf ideState params
363365
else return $ Right []
364-
mhs <- mapM makeSymbols sps
366+
mhs <- mapConcurrently makeSymbols sps
365367
case rights mhs of
366368
[] -> return $ Left $ responseError $ T.pack $ show $ lefts mhs
367369
hs -> return $ Right $ convertSymbols $ concat hs
@@ -391,7 +393,7 @@ renameWith providers lspFuncs state params = do
391393
then otTracedProvider pid "rename" $ p lspFuncs state params
392394
else return $ Right $ WorkspaceEdit Nothing Nothing
393395
-- TODO:AZ: we need to consider the right way to combine possible renamers
394-
results <- mapM makeAction providers
396+
results <- mapConcurrently makeAction providers
395397
case partitionEithers results of
396398
(errors, []) -> return $ Left $ responseError $ T.pack $ show errors
397399
(_, edits) -> return $ Right $ mconcat edits
@@ -436,22 +438,23 @@ makeCompletions :: [(PluginId, CompletionProvider IdeState)]
436438
makeCompletions sps lf ideState params@(CompletionParams (TextDocumentIdentifier doc) pos _context _mt)
437439
= do
438440
mprefix <- getPrefixAtPos lf doc pos
439-
_snippets <- WithSnippets . completionSnippetsOn <$> getClientConfig lf
441+
maxCompletions <- maxCompletions <$> getClientConfig lf
440442

441443
let
442444
combine :: [CompletionResponseResult] -> CompletionResponseResult
443-
combine cs = go (Completions $ List []) cs
444-
where
445-
go acc [] = acc
446-
go (Completions (List ls)) (Completions (List ls2):rest)
447-
= go (Completions (List (ls <> ls2))) rest
448-
go (Completions (List ls)) (CompletionList (CompletionListType complete (List ls2)):rest)
449-
= go (CompletionList $ CompletionListType complete (List (ls <> ls2))) rest
450-
go (CompletionList (CompletionListType complete (List ls))) (CompletionList (CompletionListType complete2 (List ls2)):rest)
451-
= go (CompletionList $ CompletionListType (complete || complete2) (List (ls <> ls2))) rest
452-
go (CompletionList (CompletionListType complete (List ls))) (Completions (List ls2):rest)
453-
= go (CompletionList $ CompletionListType complete (List (ls <> ls2))) rest
454-
makeAction (pid,p) = do
445+
combine cs = go True mempty cs
446+
447+
go !comp acc [] =
448+
CompletionList (CompletionListType comp (List $ DList.toList acc))
449+
go comp acc (Completions (List ls) : rest) =
450+
go comp (acc <> DList.fromList ls) rest
451+
go comp acc (CompletionList (CompletionListType comp' (List ls)) : rest) =
452+
go (comp && comp') (acc <> DList.fromList ls) rest
453+
454+
makeAction ::
455+
(PluginId, CompletionProvider IdeState) ->
456+
IO (Either ResponseError CompletionResponseResult)
457+
makeAction (pid, p) = do
455458
pluginConfig <- getPluginConfig lf pid
456459
if pluginEnabled pluginConfig plcCompletionOn
457460
then otTracedProvider pid "completions" $ p lf ideState params
@@ -460,10 +463,19 @@ makeCompletions sps lf ideState params@(CompletionParams (TextDocumentIdentifier
460463
case mprefix of
461464
Nothing -> return $ Right $ Completions $ List []
462465
Just _prefix -> do
463-
mhs <- mapM makeAction sps
466+
mhs <- mapConcurrently makeAction sps
464467
case rights mhs of
465468
[] -> return $ Left $ responseError $ T.pack $ show $ lefts mhs
466-
hs -> return $ Right $ combine hs
469+
hs -> return $ Right $ snd $ consumeCompletionResponse maxCompletions $ combine hs
470+
471+
-- | Crops a completion response. Returns the final number of completions and the cropped response
472+
consumeCompletionResponse :: Int -> CompletionResponseResult -> (Int, CompletionResponseResult)
473+
consumeCompletionResponse limit it@(CompletionList (CompletionListType _ (List xx))) =
474+
case splitAt limit xx of
475+
(_, []) -> (limit - length xx, it)
476+
(xx', _) -> (0, CompletionList (CompletionListType False (List xx')))
477+
consumeCompletionResponse n (Completions (List xx)) =
478+
consumeCompletionResponse n (CompletionList (CompletionListType False (List xx)))
467479

468480
getPrefixAtPos :: LSP.LspFuncs Config -> Uri -> Position -> IO (Maybe VFS.PosPrefixInfo)
469481
getPrefixAtPos lf uri pos = do

haskell-language-server.cabal

+1
Original file line numberDiff line numberDiff line change
@@ -220,6 +220,7 @@ common moduleName
220220
common pragmas
221221
if flag(pragmas) || flag(all-plugins)
222222
hs-source-dirs: plugins/default/src
223+
build-depends: fuzzy
223224
other-modules: Ide.Plugin.Pragmas
224225
cpp-options: -Dpragmas
225226

plugins/default/src/Ide/Plugin/Pragmas.hs

+6-6
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,6 @@
88
module Ide.Plugin.Pragmas
99
(
1010
descriptor
11-
-- , commands -- TODO: get rid of this
1211
) where
1312

1413
import Control.Lens hiding (List)
@@ -25,7 +24,8 @@ import qualified Language.Haskell.LSP.Types.Lens as J
2524
import Control.Monad (join)
2625
import Development.IDE.GHC.Compat
2726
import qualified Language.Haskell.LSP.Core as LSP
28-
import qualified Language.Haskell.LSP.VFS as VFS
27+
import qualified Language.Haskell.LSP.VFS as VFS
28+
import qualified Text.Fuzzy as Fuzzy
2929

3030
-- ---------------------------------------------------------------------
3131

@@ -142,13 +142,13 @@ completion lspFuncs _ide complParams = do
142142
position = complParams ^. J.position
143143
contents <- LSP.getVirtualFileFunc lspFuncs $ toNormalizedUri uri
144144
fmap Right $ case (contents, uriToFilePath' uri) of
145-
(Just cnts, Just _path) -> do
146-
pfix <- VFS.getCompletionPrefix position cnts
147-
return $ result pfix
145+
(Just cnts, Just _path) ->
146+
result <$> VFS.getCompletionPrefix position cnts
148147
where
149148
result (Just pfix)
150149
| "{-# LANGUAGE" `T.isPrefixOf` VFS.fullLine pfix
151-
= Completions $ List $ map buildCompletion allPragmas
150+
= Completions $ List $ map buildCompletion
151+
(Fuzzy.simpleFilter (VFS.prefixText pfix) allPragmas)
152152
| otherwise
153153
= Completions $ List []
154154
result Nothing = Completions $ List []

test/functional/Completion.hs

+10-2
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,8 @@ import Test.Tasty
1313
import Test.Tasty.ExpectedFailure (ignoreTestBecause)
1414
import Test.Tasty.HUnit
1515
import qualified Data.Text as T
16+
import Data.Default (def)
17+
import Ide.Plugin.Config (Config (maxCompletions))
1618

1719
tests :: TestTree
1820
tests = testGroup "completions" [
@@ -102,7 +104,7 @@ tests = testGroup "completions" [
102104
let te = TextEdit (Range (Position 0 13) (Position 0 31)) "Str"
103105
_ <- applyEdit doc te
104106

105-
compls <- getCompletions doc (Position 0 24)
107+
compls <- getCompletions doc (Position 0 16)
106108
let item = head $ filter ((== "Strict") . (^. label)) compls
107109
liftIO $ do
108110
item ^. label @?= "Strict"
@@ -116,7 +118,7 @@ tests = testGroup "completions" [
116118
let te = TextEdit (Range (Position 0 13) (Position 0 31)) "NoOverload"
117119
_ <- applyEdit doc te
118120

119-
compls <- getCompletions doc (Position 0 24)
121+
compls <- getCompletions doc (Position 0 23)
120122
let item = head $ filter ((== "NoOverloadedStrings") . (^. label)) compls
121123
liftIO $ do
122124
item ^. label @?= "NoOverloadedStrings"
@@ -221,6 +223,12 @@ tests = testGroup "completions" [
221223
liftIO $
222224
item ^. detail @?= Just ":: (a -> b -> c) -> b -> a -> c"
223225

226+
, testCase "maxCompletions" $ runSession hlsCommand fullCaps "test/testdata/completion" $ do
227+
doc <- openDoc "Completion.hs" "haskell"
228+
229+
compls <- getCompletions doc (Position 5 7)
230+
liftIO $ length compls @?= maxCompletions def
231+
224232
, contextTests
225233
, snippetTests
226234
]

0 commit comments

Comments
 (0)