Skip to content

Commit a03013c

Browse files
pepeiborrajneira
andauthored
More completions fixes (#2354)
* Clean up previous entries in the exports map when updating it * Add typeText for local completions of type/class declarations helps with #2270 * add typeText for all local completions * fix test Co-authored-by: Javier Neira <atreyu.bbb@gmail.com>
1 parent 9a575e0 commit a03013c

File tree

4 files changed

+55
-19
lines changed

4 files changed

+55
-19
lines changed

ghcide/src/Development/IDE/Core/OfInterest.hs

+1-2
Original file line numberDiff line numberDiff line change
@@ -113,8 +113,7 @@ kick = do
113113
-- Update the exports map
114114
results <- uses GenerateCore files <* uses GetHieAst files
115115
let mguts = catMaybes results
116-
!exportsMap' = createExportsMapMg mguts
117-
void $ liftIO $ modifyVar' exportsMap (exportsMap' <>)
116+
void $ liftIO $ modifyVar' exportsMap (updateExportsMapMg mguts)
118117

119118
liftIO $ progressUpdate progress KickCompleted
120119

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

+11-14
Original file line numberDiff line numberDiff line change
@@ -151,13 +151,6 @@ occNameToComKind ty oc
151151
showModName :: ModuleName -> T.Text
152152
showModName = T.pack . moduleNameString
153153

154-
-- mkCompl :: IdeOptions -> CompItem -> CompletionItem
155-
-- mkCompl IdeOptions{..} CI{compKind,insertText, importedFrom,typeText,label,docs} =
156-
-- CompletionItem label kind (List []) ((colon <>) <$> typeText)
157-
-- (Just $ CompletionDocMarkup $ MarkupContent MkMarkdown $ T.intercalate sectionSeparator docs')
158-
-- Nothing Nothing Nothing Nothing (Just insertText) (Just Snippet)
159-
-- Nothing Nothing Nothing Nothing Nothing
160-
161154
mkCompl :: PluginId -> IdeOptions -> CompItem -> CompletionItem
162155
mkCompl
163156
pId
@@ -179,10 +172,10 @@ mkCompl
179172
_tags = Nothing,
180173
_detail =
181174
case (typeText, provenance) of
182-
(Just t,_) -> Just $ colon <> t
183-
(_, ImportedFrom mod) -> Just $ "from " <> mod
184-
(_, DefinedIn mod) -> Just $ "from " <> mod
185-
_ -> Nothing,
175+
(Just t,_) | not(T.null t) -> Just $ colon <> t
176+
(_, ImportedFrom mod) -> Just $ "from " <> mod
177+
(_, DefinedIn mod) -> Just $ "from " <> mod
178+
_ -> Nothing,
186179
_documentation = documentation,
187180
_deprecated = Nothing,
188181
_preselect = Nothing,
@@ -448,12 +441,12 @@ localCompletionsForParsedModule uri pm@ParsedModule{pm_parsed_source = L _ HsMod
448441
[mkComp id CiVariable Nothing
449442
| VarPat _ id <- listify (\(_ :: Pat GhcPs) -> True) pat_lhs]
450443
TyClD _ ClassDecl{tcdLName, tcdSigs} ->
451-
mkComp tcdLName CiInterface Nothing :
444+
mkComp tcdLName CiInterface (Just $ ppr tcdLName) :
452445
[ mkComp id CiFunction (Just $ ppr typ)
453446
| L _ (ClassOpSig _ _ ids typ) <- tcdSigs
454447
, id <- ids]
455448
TyClD _ x ->
456-
let generalCompls = [mkComp id cl Nothing
449+
let generalCompls = [mkComp id cl (Just $ ppr $ tcdLName x)
457450
| id <- listify (\(_ :: Located(IdP GhcPs)) -> True) x
458451
, let cl = occNameToComKind Nothing (rdrNameOcc $ unLoc id)]
459452
-- here we only have to look at the outermost type
@@ -471,8 +464,12 @@ localCompletionsForParsedModule uri pm@ParsedModule{pm_parsed_source = L _ HsMod
471464
]
472465

473466
mkLocalComp pos n ctyp ty =
474-
CI ctyp pn (Local pos) ty pn Nothing doc (ctyp `elem` [CiStruct, CiInterface]) Nothing
467+
CI ctyp pn (Local pos) ensureTypeText pn Nothing doc (ctyp `elem` [CiStruct, CiInterface]) Nothing
475468
where
469+
-- when sorting completions, we use the presence of typeText
470+
-- to tell local completions and global completions apart
471+
-- instead of using the empty string here, we should probably introduce a new field...
472+
ensureTypeText = Just $ fromMaybe "" ty
476473
pn = ppr n
477474
doc = SpanDocText (getDocumentation [pm] n) (SpanDocUris Nothing Nothing)
478475

ghcide/src/Development/IDE/Types/Exports.hs

+24-2
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Development.IDE.Types.Exports
1010
buildModuleExportMapFrom,
1111
createExportsMapHieDb,
1212
size,
13+
updateExportsMapMg
1314
) where
1415

1516
import Control.DeepSeq (NFData (..))
@@ -30,11 +31,23 @@ import HieDb
3031

3132

3233
data ExportsMap = ExportsMap
33-
{getExportsMap :: HashMap IdentifierText (HashSet IdentInfo)
34-
, getModuleExportsMap :: Map.HashMap ModuleNameText (HashSet IdentInfo)
34+
{ getExportsMap :: HashMap IdentifierText (HashSet IdentInfo)
35+
, getModuleExportsMap :: HashMap ModuleNameText (HashSet IdentInfo)
3536
}
3637
deriving (Show)
3738

39+
deleteEntriesForModule :: ModuleNameText -> ExportsMap -> ExportsMap
40+
deleteEntriesForModule m em = ExportsMap
41+
{ getExportsMap =
42+
let moduleIds = Map.lookupDefault mempty m (getModuleExportsMap em)
43+
in deleteAll
44+
(rendered <$> Set.toList moduleIds)
45+
(getExportsMap em)
46+
, getModuleExportsMap = Map.delete m (getModuleExportsMap em)
47+
}
48+
where
49+
deleteAll keys map = foldr Map.delete map keys
50+
3851
size :: ExportsMap -> Int
3952
size = sum . map length . elems . getExportsMap
4053

@@ -119,6 +132,15 @@ createExportsMapMg modGuts = do
119132
let getModuleName = moduleName $ mg_module mi
120133
concatMap (fmap (second Set.fromList) . unpackAvail getModuleName) (mg_exports mi)
121134

135+
updateExportsMapMg :: [ModGuts] -> ExportsMap -> ExportsMap
136+
updateExportsMapMg modGuts old =
137+
old' <> new
138+
where
139+
new = createExportsMapMg modGuts
140+
old' = deleteAll old (Map.keys $ getModuleExportsMap new)
141+
deleteAll = foldr deleteEntriesForModule
142+
143+
122144
createExportsMapTc :: [TcGblEnv] -> ExportsMap
123145
createExportsMapTc modIface = do
124146
let exportList = concatMap doOne modIface

ghcide/test/exe/Main.hs

+19-1
Original file line numberDiff line numberDiff line change
@@ -4319,7 +4319,25 @@ localCompletionTests = [
43194319
(Position 4 14)
43204320
[("abcd", CiFunction, "abcd", True, False, Nothing)
43214321
,("abcde", CiFunction, "abcde", True, False, Nothing)
4322-
]
4322+
],
4323+
testSessionWait "incomplete entries" $ do
4324+
let src a = "data Data = " <> a
4325+
doc <- createDoc "A.hs" "haskell" $ src "AAA"
4326+
void $ waitForTypecheck doc
4327+
let editA rhs =
4328+
changeDoc doc [TextDocumentContentChangeEvent
4329+
{ _range=Nothing
4330+
, _rangeLength=Nothing
4331+
, _text=src rhs}]
4332+
4333+
editA "AAAA"
4334+
void $ waitForTypecheck doc
4335+
editA "AAAAA"
4336+
void $ waitForTypecheck doc
4337+
4338+
compls <- getCompletions doc (Position 0 15)
4339+
liftIO $ filter ("AAA" `T.isPrefixOf`) (mapMaybe _insertText compls) @?= ["AAAAA"]
4340+
pure ()
43234341
]
43244342

43254343
nonLocalCompletionTests :: [TestTree]

0 commit comments

Comments
 (0)