Skip to content
New issue

Have a question about this project? # for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “#”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? # to your account

enable completions of local imports #2190

Merged
merged 16 commits into from
Sep 17, 2021
Merged
18 changes: 14 additions & 4 deletions ghcide/src/Development/IDE/Plugin/Completions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,10 +48,13 @@ import Ide.Types
import qualified Language.LSP.Server as LSP
import Language.LSP.Types
import qualified Language.LSP.VFS as VFS

import Development.IDE.Types.KnownTargets (Target(..))
#if MIN_VERSION_ghc(9,0,0)
import GHC.Tc.Module (tcRnImportDecls)
#else
import TcRnDriver (tcRnImportDecls)
import qualified Data.HashMap.Strict as HM
#endif

descriptor :: PluginId -> PluginDescriptor IdeState
Expand Down Expand Up @@ -133,13 +136,15 @@ getCompletionsLSP ide plId
fmap Right $ case (contents, uriToFilePath' uri) of
(Just cnts, Just path) -> do
let npath = toNormalizedFilePath' path
(ideOpts, compls, moduleExports) <- liftIO $ runIdeAction "Completion" (shakeExtras ide) $ do
(ideOpts, compls, moduleExports, lModules) <- liftIO $ runIdeAction "Completion" (shakeExtras ide) $ do
opts <- liftIO $ getIdeOptionsIO $ shakeExtras ide
localCompls <- useWithStaleFast LocalCompletions npath
nonLocalCompls <- useWithStaleFast NonLocalCompletions npath
pm <- useWithStaleFast GetParsedModule npath
binds <- fromMaybe (mempty, zeroMapping) <$> useWithStaleFast GetBindings npath

knownTargets <- liftIO $ runAction "Completion" ide $ useNoFile GetKnownTargets
let localModules = maybe [] Map.keys knownTargets
let lModules = map toModueNameText localModules
-- set up the exports map including both package and project-level identifiers
packageExportsMapIO <- fmap(envPackageExports . fst) <$> useWithStaleFast GhcSession npath
packageExportsMap <- mapM liftIO packageExportsMapIO
Expand All @@ -151,7 +156,7 @@ getCompletionsLSP ide plId
exportsCompls = mempty{anyQualCompls = exportsCompItems}
let compls = (fst <$> localCompls) <> (fst <$> nonLocalCompls) <> Just exportsCompls

pure (opts, fmap (,pm,binds) compls, moduleExports)
pure (opts, fmap (,pm,binds) compls, moduleExports, lModules)
case compls of
Just (cci', parsedMod, bindMap) -> do
pfix <- VFS.getCompletionPrefix position cnts
Expand All @@ -161,14 +166,19 @@ getCompletionsLSP ide plId
(Just pfix', _) -> do
let clientCaps = clientCapabilities $ shakeExtras ide
config <- getCompletionsConfig plId
allCompletions <- liftIO $ getCompletions plId ideOpts cci' parsedMod bindMap pfix' clientCaps config moduleExports
allCompletions <- liftIO $ getCompletions plId ideOpts cci' parsedMod bindMap pfix' clientCaps config moduleExports lModules
pure $ InL (List allCompletions)
_ -> return (InL $ List [])
_ -> return (InL $ List [])
_ -> return (InL $ List [])

----------------------------------------------------------------------------------------------------

toModueNameText :: Development.IDE.Types.KnownTargets.Target -> T.Text
toModueNameText target = case target of
Development.IDE.Types.KnownTargets.TargetModule m -> T.pack $ moduleNameString m
_ -> T.empty

extendImportCommand :: PluginCommand IdeState
extendImportCommand =
PluginCommand (CommandId extendImportCommandId) "additional edits for a completion" extendImportHandler
Expand Down
7 changes: 4 additions & 3 deletions ghcide/src/Development/IDE/Plugin/Completions/Logic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -534,9 +534,10 @@ getCompletions
-> ClientCapabilities
-> CompletionsConfig
-> HM.HashMap T.Text (HashSet.HashSet IdentInfo)
-> [T.Text]
-> IO [CompletionItem]
getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qualCompls, importableModules}
maybe_parsed (localBindings, bmapping) prefixInfo caps config moduleExportsMap = do
maybe_parsed (localBindings, bmapping) prefixInfo caps config moduleExportsMap localImportableModues = do
let VFS.PosPrefixInfo { fullLine, prefixModule, prefixText } = prefixInfo
enteredQual = if T.null prefixModule then "" else prefixModule <> "."
fullPrefix = enteredQual <> prefixText
Expand Down Expand Up @@ -604,7 +605,7 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
, enteredQual `T.isPrefixOf` label
]

filtImportCompls = filtListWith (mkImportCompl enteredQual) importableModules
filtImportCompls localModules = filtListWith (mkImportCompl enteredQual) (importableModules <> localModules)
filterModuleExports moduleName = filtListWith $ mkModuleFunctionImport moduleName
filtKeywordCompls
| T.null prefixModule = filtListWith mkExtCompl (optKeywords ideOpts)
Expand All @@ -621,7 +622,7 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
funs = map (show . name) $ HashSet.toList funcs
return $ filterModuleExports moduleName $ map T.pack funs
| "import " `T.isPrefixOf` fullLine
-> return filtImportCompls
-> return $ filtImportCompls localImportableModues
-- we leave this condition here to avoid duplications and return empty list
-- since HLS implements these completions (#haskell-language-server/pull/662)
| "{-# " `T.isPrefixOf` fullLine
Expand Down
20 changes: 19 additions & 1 deletion ghcide/test/exe/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ import Development.IDE.Test (Cursor,
import Development.IDE.Test.Runfiles
import qualified Development.IDE.Types.Diagnostics as Diagnostics
import Development.IDE.Types.Location
import qualified Language.LSP.Types.Lens as Lens (label)
import Development.Shake (getDirectoryFilesIO)
import qualified Experiments as Bench
import Ide.Plugin.Config
Expand Down Expand Up @@ -4589,7 +4590,24 @@ projectCompletionTests =
<- compls
, _label == "anidentifier"
]
liftIO $ compls' @?= ["Defined in 'A"]
liftIO $ compls' @?= ["Defined in 'A"],
testSession' "auto complete project imports" $ \dir-> do
liftIO $ writeFile (dir </> "hie.yaml")
"cradle: {direct: {arguments: [\"-Wmissing-signatures\", \"ALocalModule\", \"B\"]}}"
_ <- createDoc "ALocalModule.hs" "haskell" $ T.unlines
[ "module ALocalModule (anidentifier) where",
"anidentifier = ()"
]
_ <- waitForDiagnostics
-- Note that B does not import A
doc <- createDoc "B.hs" "haskell" $ T.unlines
[ "module B where",
"import ALocal"
]
compls <- getCompletions doc (Position 1 13)
let item = head $ filter ((== "ALocalModule") . (^. Lens.label)) compls
liftIO $ do
item ^. Lens.label @?= "ALocalModule"
]

highlightTests :: TestTree
Expand Down