@@ -31,7 +31,6 @@ import Data.Either (fromRight)
3131import Data.Function (on )
3232import Data.Functor
3333import qualified Data.HashMap.Strict as HM
34- import qualified Data.Map.Strict as M
3534
3635import qualified Data.HashSet as HashSet
3736import Data.Monoid (First (.. ))
@@ -69,10 +68,10 @@ import qualified Language.LSP.VFS as VFS
6968import Text.Fuzzy.Parallel (Scored (score ),
7069 original )
7170
72- import Data.Coerce (coerce )
7371import Development.IDE
7472
7573import qualified Data.Rope.UTF16 as Rope
74+ import Development.IDE.Spans.AtPoint (pointCommand )
7675
7776-- Chunk size used for parallelizing fuzzy matching
7877chunkSize :: Int
@@ -610,52 +609,35 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
610609 hpos = upperRange position'
611610 in getCContext lpos pm <|> getCContext hpos pm
612611
613- dotFieldSelectorToCompl :: T. Text -> (Bool , CompItem )
614- dotFieldSelectorToCompl label = (True , CI CiVariable label (ImportedFrom T. empty) Nothing label Nothing emptySpanDoc False Nothing )
615612
616613 -- we need the hieast to be fresh
617614 -- not fresh, hasfield won't have a chance. it would to another larger change to ghc IfaceTyCon to contain record fields
618- tst :: [(Bool , CompItem )]
619- tst = case maybe_ast_res of
620- Just (HAR {hieAst = hieast, hieKind = HieFresh },_) -> concat $ pointCommand hieast (completionPrefixPos prefixInfo) (theFunc HieFresh )
615+ recordDotSyntaxCompls :: [(Bool , CompItem )]
616+ recordDotSyntaxCompls = case maybe_ast_res of
617+ Just (HAR {hieAst = hieast, hieKind = HieFresh },_) -> concat $ pointCommand hieast (completionPrefixPos prefixInfo) nodeCompletions
621618 _ -> []
622-
623- getSels :: GHC. TyCon -> [T. Text ]
624- getSels tycon = let f fieldLabel = printOutputable fieldLabel
625- in map f $ tyConFieldLabels tycon
626-
627- theFunc :: HieKind Type -> HieAST Type -> [(Bool , CompItem )]
628- theFunc kind node = concatMap g (nodeType $ nodeInfoH kind node)
629619 where
620+ nodeCompletions :: HieAST Type -> [(Bool , CompItem )]
621+ nodeCompletions node = concatMap g (nodeType $ nodeInfo node)
630622 g :: Type -> [(Bool , CompItem )]
631- g (TyConApp theTyCon _) = map dotFieldSelectorToCompl $ getSels theTyCon
623+ g (TyConApp theTyCon _) = map ( dotFieldSelectorToCompl (printOutputable $ GHC. tyConName theTyCon)) $ getSels theTyCon
632624 g _ = []
633-
634- nodeInfoH :: HieKind a -> HieAST a -> NodeInfo a
635- nodeInfoH (HieFromDisk _) = nodeInfo'
636- nodeInfoH HieFresh = nodeInfo
637-
638- pointCommand :: HieASTs t -> Position -> (HieAST t -> a ) -> [a ]
639- pointCommand hf pos k =
640- catMaybes $ M. elems $ flip M. mapWithKey (getAsts hf) $ \ fs ast ->
641- -- Since GHC 9.2:
642- -- getAsts :: Map HiePath (HieAst a)
643- -- type HiePath = LexialFastString
644- --
645- -- but before:
646- -- getAsts :: Map HiePath (HieAst a)
647- -- type HiePath = FastString
648- --
649- -- 'coerce' here to avoid an additional function for maintaining
650- -- backwards compatibility.
651- case selectSmallestContaining (sp $ coerce fs) ast of
652- Nothing -> Nothing
653- Just ast' -> Just $ k ast'
654- where
655- sloc fs = mkRealSrcLoc fs (fromIntegral $ line+ 1 ) (fromIntegral $ cha+ 1 )
656- sp fs = mkRealSrcSpan (sloc fs) (sloc fs)
657- line = _line pos
658- cha = _character pos
625+ getSels :: GHC. TyCon -> [T. Text ]
626+ getSels tycon = let f fieldLabel = printOutputable fieldLabel
627+ in map f $ tyConFieldLabels tycon
628+ dotFieldSelectorToCompl :: T. Text -> T. Text -> (Bool , CompItem )
629+ -- dotFieldSelectorToCompl label = (True, CI CiVariable label (ImportedFrom T.empty) Nothing label Nothing emptySpanDoc False Nothing)
630+ dotFieldSelectorToCompl recname label = (True , CI
631+ { compKind = CiField
632+ , insertText = label
633+ , provenance = DefinedIn recname
634+ , typeText = Nothing
635+ , label = label
636+ , isInfix = Nothing
637+ , docs = emptySpanDoc
638+ , isTypeCompl = False
639+ , additionalTextEdits = Nothing
640+ })
659641
660642 -- completions specific to the current context
661643 ctxCompls' = case mcc of
@@ -685,7 +667,7 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
685667
686668 compls
687669 | T. null prefixScope = map (notQual,) localCompls ++ map (qual,) unqualCompls ++ ((notQual,) . ($ Nothing ) <$> anyQualCompls)
688- | not $ null tst = tst
670+ | not $ null recordDotSyntaxCompls = recordDotSyntaxCompls
689671 | otherwise = ((qual,) <$> Map. findWithDefault [] prefixScope (getQualCompls qualCompls))
690672 ++ ((notQual,) . ($ Just prefixScope) <$> anyQualCompls)
691673
0 commit comments