@@ -21,7 +21,7 @@ import Data.List.Extra as List hiding
2121import qualified Data.Map as Map
2222
2323import Data.Maybe (catMaybes , fromMaybe ,
24- isJust , mapMaybe )
24+ isJust , mapMaybe , listToMaybe )
2525import qualified Data.Text as T
2626import 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
937946getCompletionPrefix 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 '
0 commit comments