Skip to content

Commit af6387c

Browse files
authored
Remove suggestion of stanzas inside of stanza context (#3761)
1 parent 3ffde0d commit af6387c

File tree

5 files changed

+52
-22
lines changed

5 files changed

+52
-22
lines changed

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Completion/Completions.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ contextToCompleter (TopLevel, KeyWord kw) =
4949
contextToCompleter (Stanza s _, None) =
5050
case Map.lookup s stanzaKeywordMap of
5151
Nothing -> errorNoopCompleter (LogUnknownStanzaNameInContextError s)
52-
Just l -> constantCompleter $ Map.keys l ++ Map.keys stanzaKeywordMap
52+
Just l -> constantCompleter $ Map.keys l
5353
-- if we are in a stanza's keyword's context we can complete possible values of that keyword
5454
contextToCompleter (Stanza s _, KeyWord kw) =
5555
case Map.lookup s stanzaKeywordMap of

plugins/hls-cabal-plugin/test/Completer.hs

+24-3
Original file line numberDiff line numberDiff line change
@@ -3,15 +3,18 @@
33

44
module Completer where
55

6-
import Control.Lens ((^.))
6+
import Control.Lens ((^.), (^?))
7+
import Control.Lens.Prism
78
import qualified Data.ByteString as ByteString
9+
import Data.Maybe (mapMaybe)
810
import qualified Data.Text as T
911
import Distribution.PackageDescription.Parsec (parseGenericPackageDescriptionMaybe)
1012
import Ide.Plugin.Cabal.Completion.Completer.FilePath
1113
import Ide.Plugin.Cabal.Completion.Completer.Module
1214
import Ide.Plugin.Cabal.Completion.Completer.Types (CompleterData (..))
1315
import Ide.Plugin.Cabal.Completion.Completions
14-
import Ide.Plugin.Cabal.Completion.Types
16+
import Ide.Plugin.Cabal.Completion.Types (CabalPrefixInfo (..),
17+
StanzaName)
1518
import Ide.Plugin.Cabal.Parse (GenericPackageDescription)
1619
import qualified Language.LSP.Protocol.Lens as L
1720
import qualified Language.LSP.VFS as VFS
@@ -23,14 +26,32 @@ completerTests :: TestTree
2326
completerTests =
2427
testGroup
2528
"Completer Tests"
26-
[ fileCompleterTests,
29+
[ basicCompleterTests,
30+
fileCompleterTests,
2731
filePathCompletionContextTests,
2832
directoryCompleterTests,
2933
completionHelperTests,
3034
filePathExposedModulesTests,
3135
exposedModuleCompleterTests
3236
]
3337

38+
basicCompleterTests :: TestTree
39+
basicCompleterTests =
40+
testGroup
41+
"Basic Completer Tests"
42+
[ runCabalTestCaseSession "In stanza context - stanza should not be suggested" "" $ do
43+
doc <- openDoc "completer.cabal" "cabal"
44+
compls <- getCompletions doc (Position 11 7)
45+
let complTexts = mapMaybe (^? L.textEdit . _Just . _L . L.newText) compls
46+
liftIO $ assertBool "does not suggest library" $ "library" `notElem` complTexts
47+
liftIO $ assertBool "suggests library keyword" $ "extra-libraries:" `elem` complTexts
48+
, runCabalTestCaseSession "In top level context - stanza should be suggested" "" $ do
49+
doc <- openDoc "completer.cabal" "cabal"
50+
compls <- getCompletions doc (Position 8 2)
51+
let complTexts = mapMaybe (^? L.textEdit . _Just . _L . L.newText) compls
52+
liftIO $ assertBool "suggests benchmark" $ "benchmark" `elem` complTexts
53+
]
54+
3455
fileCompleterTests :: TestTree
3556
fileCompleterTests =
3657
testGroup

plugins/hls-cabal-plugin/test/Main.hs

+1-18
Original file line numberDiff line numberDiff line change
@@ -17,15 +17,12 @@ import Data.Either (isRight)
1717
import Data.Row
1818
import qualified Data.Text as T
1919
import qualified Data.Text as Text
20-
import Ide.Plugin.Cabal
2120
import Ide.Plugin.Cabal.LicenseSuggest (licenseErrorSuggestion)
2221
import qualified Ide.Plugin.Cabal.Parse as Lib
2322
import qualified Language.LSP.Protocol.Lens as L
2423
import System.FilePath
2524
import Test.Hls
26-
27-
cabalPlugin :: PluginTestDescriptor Ide.Plugin.Cabal.Log
28-
cabalPlugin = mkPluginTestDescriptor descriptor "cabal"
25+
import Utils
2926

3027
main :: IO ()
3128
main = do
@@ -195,17 +192,3 @@ pluginTests =
195192
InR action@CodeAction{_title} <- codeActions
196193
guard (_title == "Replace with " <> license)
197194
pure action
198-
199-
-- ------------------------------------------------------------------------
200-
-- Runner utils
201-
-- ------------------------------------------------------------------------
202-
203-
runCabalTestCaseSession :: TestName -> FilePath -> Session () -> TestTree
204-
runCabalTestCaseSession title subdir = testCase title . runCabalSession subdir
205-
206-
runCabalSession :: FilePath -> Session a -> IO a
207-
runCabalSession subdir =
208-
failIfSessionTimeout . runSessionWithServer cabalPlugin (testDataDir </> subdir)
209-
210-
testDataDir :: FilePath
211-
testDataDir = "test" </> "testdata"

plugins/hls-cabal-plugin/test/Utils.hs

+14
Original file line numberDiff line numberDiff line change
@@ -5,11 +5,15 @@ module Utils where
55

66
import Data.List (sort)
77
import qualified Data.Text as T
8+
import Ide.Plugin.Cabal (descriptor)
9+
import qualified Ide.Plugin.Cabal
810
import Ide.Plugin.Cabal.Completion.Types
911
import System.Directory (getCurrentDirectory)
1012
import System.FilePath
1113
import Test.Hls
1214

15+
cabalPlugin :: PluginTestDescriptor Ide.Plugin.Cabal.Log
16+
cabalPlugin = mkPluginTestDescriptor descriptor "cabal"
1317

1418
simpleCabalPrefixInfoFromPos :: Position -> T.Text -> CabalPrefixInfo
1519
simpleCabalPrefixInfoFromPos pos prefix =
@@ -43,6 +47,16 @@ getFilePathComplTestDir = do
4347
testDir <- getTestDir
4448
pure $ addTrailingPathSeparator $ testDir </> "filepath-completions"
4549

50+
runCabalTestCaseSession :: TestName -> FilePath -> Session () -> TestTree
51+
runCabalTestCaseSession title subdir = testCase title . runCabalSession subdir
52+
53+
runCabalSession :: FilePath -> Session a -> IO a
54+
runCabalSession subdir =
55+
failIfSessionTimeout . runSessionWithServer cabalPlugin (testDataDir </> subdir)
56+
57+
testDataDir :: FilePath
58+
testDataDir = "test" </> "testdata"
59+
4660
-- | list comparison where the order in the list is irrelevant
4761
(@?==) :: (HasCallStack, Ord a, Show a) => [a] -> [a] -> Assertion
4862
(@?==) l1 l2 = sort l1 @?= sort l2
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
cabal-version: 3.4
2+
name: test-hls
3+
version: 0.1.0.0
4+
maintainer: milky
5+
synopsis: example cabal file :)
6+
license: Apache-2.0
7+
build-type: Simple
8+
9+
be
10+
11+
library
12+
lib

0 commit comments

Comments
 (0)