Skip to content

Commit 0bc2cfe

Browse files
committed
comments, fixes
1 parent 6dab681 commit 0bc2cfe

File tree

5 files changed

+42
-26
lines changed

5 files changed

+42
-26
lines changed

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

Lines changed: 7 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -151,24 +151,23 @@ getCompletionsLSP ide plId
151151
#endif
152152
ms <- fmap fst <$> useWithStaleFast GetModSummaryWithoutTimestamps npath
153153
astres <- case ms of
154-
Just ms' -> if uses_overloaded_record_dot ms'
155-
then useWithStaleFast GetHieAst npath
156-
else return Nothing
157-
Nothing -> return Nothing
154+
Just ms' | uses_overloaded_record_dot ms'
155+
-> useWithStaleFast GetHieAst npath
156+
_ -> return Nothing
158157

159158
pure (opts, fmap (,pm,binds) compls, moduleExports, astres)
160159
case compls of
161160
Just (cci', parsedMod, bindMap) -> do
162-
pfix <- getCompletionPrefix position cnts
161+
let pfix = getCompletionPrefix position cnts
163162
case (pfix, completionContext) of
164-
(Just (PosPrefixInfo _ "" _ _), Just CompletionContext { _triggerCharacter = Just "."})
163+
((PosPrefixInfo _ "" _ _), Just CompletionContext { _triggerCharacter = Just "."})
165164
-> return (InL $ List [])
166-
(Just pfix', _) -> do
165+
(_, _) -> do
167166
let clientCaps = clientCapabilities $ shakeExtras ide
168167
plugins = idePlugins $ shakeExtras ide
169168
config <- getCompletionsConfig plId
170169

171-
allCompletions <- liftIO $ getCompletions plugins ideOpts cci' parsedMod astres bindMap pfix' clientCaps config moduleExports
170+
allCompletions <- liftIO $ getCompletions plugins ideOpts cci' parsedMod astres bindMap pfix clientCaps config moduleExports
172171
pure $ InL (List $ orderedCompletions allCompletions)
173172
_ -> return (InL $ List [])
174173
_ -> return (InL $ List [])

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

Lines changed: 22 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ import Data.List.Extra as List hiding
2121
import qualified Data.Map as Map
2222

2323
import Data.Maybe (catMaybes, fromMaybe,
24-
isJust, mapMaybe)
24+
isJust, mapMaybe, listToMaybe)
2525
import qualified Data.Text as T
2626
import qualified Text.Fuzzy.Parallel as Fuzzy
2727

@@ -617,8 +617,10 @@ getCompletions plugins ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls,
617617
in getCContext lpos pm <|> getCContext hpos pm
618618

619619

620-
-- we need the hieast to be fresh
621-
-- not fresh, hasfield won't have a chance. it would to another larger change to ghc IfaceTyCon to contain record fields
620+
-- We need the hieast to be "fresh". We can't get types from "stale" hie files, so hasfield won't work,
621+
-- since it gets the record fields from the types.
622+
-- Perhaps this could be fixed with a refactor to GHC's IfaceTyCon, to have it also contain record fields.
623+
-- Requiring fresh hieast is fine for normal workflows, because it is generated while the user edits.
622624
recordDotSyntaxCompls :: [(Bool, CompItem)]
623625
recordDotSyntaxCompls = case maybe_ast_res of
624626
Just (HAR {hieAst = hieast, hieKind = HieFresh},_) -> concat $ pointCommand hieast (completionPrefixPos prefixInfo) nodeCompletions
@@ -632,8 +634,12 @@ getCompletions plugins ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls,
632634
getSels :: GHC.TyCon -> [T.Text]
633635
getSels tycon = let f fieldLabel = printOutputable fieldLabel
634636
in map f $ tyConFieldLabels tycon
637+
-- Completions can return more information that just the completion itself, but it will
638+
-- require more than what GHC currently gives us in the HieAST, since it only gives the Type
639+
-- of the fields, not where they are defined, etc. So for now the extra fields remain empty.
640+
-- Also: additionalTextEdits is a todo, since we may want to import the record. It requires a way
641+
-- to get the record's module, which isn't included in the type information used to get the fields.
635642
dotFieldSelectorToCompl :: T.Text -> T.Text -> (Bool, CompItem)
636-
--dotFieldSelectorToCompl label = (True, CI CiVariable label (ImportedFrom T.empty) Nothing label Nothing emptySpanDoc False Nothing)
637643
dotFieldSelectorToCompl recname label = (True, CI
638644
{ compKind = CiField
639645
, insertText = label
@@ -672,11 +678,14 @@ getCompletions plugins ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls,
672678
ty = showForSnippet <$> typ
673679
thisModName = Local $ nameSrcSpan name
674680

681+
-- When record-dot-syntax completions are available, we return them exclusively.
682+
-- They are only available when we write i.e. `myrecord.` with OverloadedRecordDot enabled.
683+
-- Anything that isn't a field is invalid, so those completion don't make sense.
675684
compls
676-
| T.null prefixScope = map (notQual,) localCompls ++ map (qual,) unqualCompls ++ ((notQual,) . ($ Nothing) <$> anyQualCompls)
685+
| T.null prefixScope = map (notQual,) localCompls ++ map (qual,) unqualCompls ++ map (\compl -> (notQual, compl Nothing)) anyQualCompls
677686
| not $ null recordDotSyntaxCompls = recordDotSyntaxCompls
678687
| otherwise = ((qual,) <$> Map.findWithDefault [] prefixScope (getQualCompls qualCompls))
679-
++ ((notQual,) . ($ Just prefixScope) <$> anyQualCompls)
688+
++ map (\compl -> (notQual, compl (Just prefixScope))) anyQualCompls
680689

681690
filtListWith f list =
682691
[ fmap f label
@@ -932,19 +941,18 @@ mergeListsBy cmp all_lists = merge_lists all_lists
932941
[xs] -> xs
933942
lists' -> merge_lists lists'
934943

935-
936-
getCompletionPrefix :: (Monad m) => Position -> VFS.VirtualFile -> m (Maybe PosPrefixInfo)
944+
-- |From the given cursor position, gets the prefix module or record for autocompletion
945+
getCompletionPrefix :: Position -> VFS.VirtualFile -> PosPrefixInfo
937946
getCompletionPrefix pos@(Position l c) (VFS.VirtualFile _ _ ropetext) =
938-
return $ Just $ fromMaybe (PosPrefixInfo "" "" "" pos) $ do -- Maybe monad
939-
let headMaybe [] = Nothing
940-
headMaybe (x:_) = Just x
941-
lastMaybe [] = Nothing
942-
lastMaybe [x] = Just x
943-
lastMaybe (_:xs) = lastMaybe xs
947+
fromMaybe (PosPrefixInfo "" "" "" pos) $ do -- Maybe monad
948+
let headMaybe = listToMaybe
949+
lastMaybe = headMaybe . reverse
944950

951+
-- grab the entire line the cursor is at
945952
curLine <- headMaybe $ T.lines $ Rope.toText
946953
$ fst $ Rope.splitAtLine 1 $ snd $ Rope.splitAtLine (fromIntegral l) ropetext
947954
let beforePos = T.take (fromIntegral c) curLine
955+
-- the word getting typed, after previous space and before cursor
948956
curWord <-
949957
if | T.null beforePos -> Just ""
950958
| T.last beforePos == ' ' -> Just "" -- don't count abc as the curword in 'abc '

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

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -139,7 +139,6 @@ instance Semigroup CachedCompletions where
139139
CC (a<>a') (b<>b') (c<>c') (d<>d') (e<>e')
140140

141141

142-
-- moved here from Language.LSP.VFS
143142
-- | Describes the line at the current cursor position
144143
data PosPrefixInfo = PosPrefixInfo
145144
{ fullLine :: !T.Text

test/functional/Completion.hs

Lines changed: 12 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -94,11 +94,20 @@ tests = testGroup "completions" [
9494

9595
compls <- getCompletions doc (Position 25 6)
9696
item <- getCompletionByLabel "a" compls
97+
9798
liftIO $ do
9899
item ^. label @?= "a"
99-
--item ^. detail @?= Just "Data.List" TODO
100-
--item ^. kind @?= Just CiModule
101-
liftIO $ length compls @?= 6
100+
, testCase "shows field selectors for nested field" $ runSession hlsCommand fullCaps "test/testdata/completion" $ do
101+
doc <- openDoc "RecordDotSyntax.hs" "haskell"
102+
103+
let te = TextEdit (Range (Position 27 0) (Position 27 8)) "z2 = x.c.z"
104+
_ <- applyEdit doc te
105+
106+
compls <- getCompletions doc (Position 27 9)
107+
item <- getCompletionByLabel "z" compls
108+
109+
liftIO $ do
110+
item ^. label @?= "z"
102111
]
103112

104113
-- See https://github.com/haskell/haskell-ide-engine/issues/903

test/testdata/completion/RecordDotSyntax.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -24,4 +24,5 @@ x = MyRecord1 { a = "Hello", b = 12, c = MyChild { z = "there" } }
2424

2525
y = x.a ++ show x.b
2626

27+
y2 = x.c.z
2728

0 commit comments

Comments
 (0)