Skip to content

Commit

Permalink
enable completions of local imports
Browse files Browse the repository at this point in the history
  • Loading branch information
alexnaspo committed Sep 13, 2021
1 parent 8d7e8f1 commit a52894f
Show file tree
Hide file tree
Showing 2 changed files with 6 additions and 12 deletions.
11 changes: 3 additions & 8 deletions ghcide/src/Development/IDE/Plugin/Completions/Logic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiWayIf #-}


-- Mostly taken from "haskell-ide-engine"
module Development.IDE.Plugin.Completions.Logic (
CachedCompletions
Expand Down Expand Up @@ -66,6 +65,7 @@ import qualified Language.LSP.VFS as VFS
import Outputable (Outputable)
import TyCoRep


-- From haskell-ide-engine/hie-plugin-api/Haskell/Ide/Engine/Context.hs

-- | A context of a declaration in the program
Expand Down Expand Up @@ -403,15 +403,12 @@ cacheDataProducer uri env curMod globalEnv inScopeEnv limports = do

(unquals,quals) <- getCompls rdrElts

-- The list of all importable Modules from all packages
moduleNames <- maybe [] (map showModName) <$> envVisibleModuleNames env

return $ CC
{ allModNamesAsNS = allModNamesAsNS
, unqualCompls = unquals
, qualCompls = quals
, anyQualCompls = []
, importableModules = moduleNames
}

-- | Produces completions from the top level declarations of a module.
Expand All @@ -421,7 +418,6 @@ localCompletionsForParsedModule uri pm@ParsedModule{pm_parsed_source = L _ HsMod
, unqualCompls = compls
, qualCompls = mempty
, anyQualCompls = []
, importableModules = mempty
}
where
typeSigIds = Set.fromList
Expand Down Expand Up @@ -535,7 +531,7 @@ getCompletions
-> CompletionsConfig
-> HM.HashMap T.Text (HashSet.HashSet IdentInfo)
-> IO [CompletionItem]
getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qualCompls, importableModules}
getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qualCompls}
maybe_parsed (localBindings, bmapping) prefixInfo caps config moduleExportsMap = do
let VFS.PosPrefixInfo { fullLine, prefixModule, prefixText } = prefixInfo
enteredQual = if T.null prefixModule then "" else prefixModule <> "."
Expand Down Expand Up @@ -604,12 +600,11 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
, enteredQual `T.isPrefixOf` label
]

filtImportCompls = filtListWith (mkImportCompl enteredQual) importableModules
filtImportCompls = filtListWith (mkImportCompl enteredQual) $ map fst $ HM.toList moduleExportsMap
filterModuleExports moduleName = filtListWith $ mkModuleFunctionImport moduleName
filtKeywordCompls
| T.null prefixModule = filtListWith mkExtCompl (optKeywords ideOpts)
| otherwise = []

if
-- TODO: handle multiline imports
| "import " `T.isPrefixOf` fullLine
Expand Down
7 changes: 3 additions & 4 deletions ghcide/src/Development/IDE/Plugin/Completions/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,7 +95,6 @@ data CachedCompletions = CC
, qualCompls :: QualCompls -- ^ Completion items associated to
-- to a specific module name.
, anyQualCompls :: [Maybe T.Text -> CompItem] -- ^ Items associated to any qualifier
, importableModules :: [T.Text] -- ^ All modules that may be imported.
}

instance Show CachedCompletions where show _ = "<cached completions>"
Expand All @@ -104,8 +103,8 @@ instance NFData CachedCompletions where
rnf = rwhnf

instance Monoid CachedCompletions where
mempty = CC mempty mempty mempty mempty mempty
mempty = CC mempty mempty mempty mempty

instance Semigroup CachedCompletions where
CC a b c d e <> CC a' b' c' d' e' =
CC (a<>a') (b<>b') (c<>c') (d<>d') (e<>e')
CC a b c d <> CC a' b' c' d' =
CC (a<>a') (b<>b') (c<>c') (d<>d')

0 comments on commit a52894f

Please sign in to comment.