Skip to content

Commit 09ee25e

Browse files
authored
Completions for project identifiers (#2187)
* completions for project identifiers * simplify import completions Since the projectExportsMap already indexes home modules, there is no need to handle them separately
1 parent 155023f commit 09ee25e

File tree

2 files changed

+44
-21
lines changed

2 files changed

+44
-21
lines changed

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

+14-17
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ module Development.IDE.Plugin.Completions
99
) where
1010

1111
import Control.Concurrent.Async (concurrently)
12+
import Control.Concurrent.Extra
1213
import Control.Monad.Extra
1314
import Control.Monad.IO.Class
1415
import Control.Monad.Trans.Maybe
@@ -30,7 +31,7 @@ import Development.IDE.GHC.ExactPrint (Annotated (annsA)
3031
import Development.IDE.GHC.Util (prettyPrint)
3132
import Development.IDE.Graph
3233
import Development.IDE.Graph.Classes
33-
import Development.IDE.Import.FindImports
34+
import Development.IDE.Import.FindImports
3435
import Development.IDE.Plugin.CodeAction (newImport,
3536
newImportToEdit)
3637
import Development.IDE.Plugin.CodeAction.ExactPrint
@@ -138,15 +139,19 @@ getCompletionsLSP ide plId
138139
nonLocalCompls <- useWithStaleFast NonLocalCompletions npath
139140
pm <- useWithStaleFast GetParsedModule npath
140141
binds <- fromMaybe (mempty, zeroMapping) <$> useWithStaleFast GetBindings npath
141-
exportsMapIO <- fmap(envPackageExports . fst) <$> useWithStaleFast GhcSession npath
142-
exportsMap <- mapM liftIO exportsMapIO
143-
locatedImports <- fromMaybe (mempty, zeroMapping) <$> useWithStaleFast GetLocatedImports npath
144-
localModuleExports <- liftIO $ buildLocalModuleExports ide locatedImports
145-
let moduleExports = maybe Map.empty getModuleExportsMap exportsMap
146-
exportsCompItems = foldMap (map (fromIdentInfo uri) . Set.toList) . Map.elems . getExportsMap <$> exportsMap
147-
exportsCompls = mempty{anyQualCompls = fromMaybe [] exportsCompItems}
142+
143+
-- set up the exports map including both package and project-level identifiers
144+
packageExportsMapIO <- fmap(envPackageExports . fst) <$> useWithStaleFast GhcSession npath
145+
packageExportsMap <- mapM liftIO packageExportsMapIO
146+
projectExportsMap <- liftIO $ readVar (exportsMap $ shakeExtras ide)
147+
let exportsMap = fromMaybe mempty packageExportsMap <> projectExportsMap
148+
149+
let moduleExports = getModuleExportsMap exportsMap
150+
exportsCompItems = foldMap (map (fromIdentInfo uri) . Set.toList) . Map.elems . getExportsMap $ exportsMap
151+
exportsCompls = mempty{anyQualCompls = exportsCompItems}
148152
let compls = (fst <$> localCompls) <> (fst <$> nonLocalCompls) <> Just exportsCompls
149-
pure (opts, fmap (,pm,binds) compls, Map.unionWith (<>) localModuleExports moduleExports)
153+
154+
pure (opts, fmap (,pm,binds) compls, moduleExports)
150155
case compls of
151156
Just (cci', parsedMod, bindMap) -> do
152157
pfix <- VFS.getCompletionPrefix position cnts
@@ -163,14 +168,6 @@ getCompletionsLSP ide plId
163168
_ -> return (InL $ List [])
164169

165170
----------------------------------------------------------------------------------------------------
166-
167-
buildLocalModuleExports:: IdeState -> ([(Located ModuleName, Maybe ArtifactsLocation)], PositionMapping) -> IO (Map.HashMap T.Text (Set.HashSet IdentInfo))
168-
buildLocalModuleExports ide inMap = do
169-
let artifactLoctions = mapMaybe snd (fst inMap)
170-
let afp = map artifactFilePath artifactLoctions
171-
let queries = map (useWithStaleFast GetModIface) afp
172-
files <- liftIO $ mapM (runIdeAction "Completion" (shakeExtras ide)) queries
173-
pure (buildModuleExportMapFrom $ map (hirModIface . fst) $ catMaybes files)
174171

175172
extendImportCommand :: PluginCommand IdeState
176173
extendImportCommand =

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

+30-4
Original file line numberDiff line numberDiff line change
@@ -4058,7 +4058,8 @@ completionTests
40584058
[ testGroup "non local" nonLocalCompletionTests
40594059
, testGroup "topLevel" topLevelCompletionTests
40604060
, testGroup "local" localCompletionTests
4061-
, testGroup "global" globalCompletionTests
4061+
, testGroup "package" packageCompletionTests
4062+
, testGroup "project" projectCompletionTests
40624063
, testGroup "other" otherCompletionTests
40634064
]
40644065

@@ -4467,8 +4468,8 @@ otherCompletionTests = [
44674468
liftIO $ length compls @?= maxCompletions def
44684469
]
44694470

4470-
globalCompletionTests :: [TestTree]
4471-
globalCompletionTests =
4471+
packageCompletionTests :: [TestTree]
4472+
packageCompletionTests =
44724473
[ testSessionWait "fromList" $ do
44734474
doc <- createDoc "A.hs" "haskell" $ T.unlines
44744475
[ "{-# OPTIONS_GHC -Wunused-binds #-}",
@@ -4566,6 +4567,31 @@ globalCompletionTests =
45664567
]
45674568
]
45684569

4570+
projectCompletionTests :: [TestTree]
4571+
projectCompletionTests =
4572+
[ testSession' "from hiedb" $ \dir-> do
4573+
liftIO $ writeFile (dir </> "hie.yaml")
4574+
"cradle: {direct: {arguments: [\"-Wmissing-signatures\", \"A\", \"B\"]}}"
4575+
_ <- createDoc "A.hs" "haskell" $ T.unlines
4576+
[ "module A (anidentifier) where",
4577+
"anidentifier = ()"
4578+
]
4579+
_ <- waitForDiagnostics
4580+
-- Note that B does not import A
4581+
doc <- createDoc "B.hs" "haskell" $ T.unlines
4582+
[ "module B where",
4583+
"b = anidenti"
4584+
]
4585+
compls <- getCompletions doc (Position 1 10)
4586+
let compls' =
4587+
[T.drop 1 $ T.dropEnd 10 d
4588+
| CompletionItem {_documentation = Just (CompletionDocMarkup (MarkupContent MkMarkdown d)), _label}
4589+
<- compls
4590+
, _label == "anidentifier"
4591+
]
4592+
liftIO $ compls' @?= ["Defined in 'A"]
4593+
]
4594+
45694595
highlightTests :: TestTree
45704596
highlightTests = testGroup "highlight"
45714597
[ testSessionWait "value" $ do
@@ -5995,4 +6021,4 @@ thDollarIdx | ghcVersion >= GHC90 = 1
59956021
-- | We don't have a uinteger type yet. So hardcode the maxBound of uinteger, 2 ^ 31 - 1
59966022
-- as a constant.
59976023
maxBoundUinteger :: Int
5998-
maxBoundUinteger = 2147483647
6024+
maxBoundUinteger = 2147483647

0 commit comments

Comments
 (0)