Skip to content

Commit a957773

Browse files
committed
refactor
1 parent 40c2a22 commit a957773

File tree

1 file changed

+24
-42
lines changed
  • ghcide/src/Development/IDE/Plugin/Completions

1 file changed

+24
-42
lines changed

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

Lines changed: 24 additions & 42 deletions
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ import Data.Either (fromRight)
3131
import Data.Function (on)
3232
import Data.Functor
3333
import qualified Data.HashMap.Strict as HM
34-
import qualified Data.Map.Strict as M
3534

3635
import qualified Data.HashSet as HashSet
3736
import Data.Monoid (First (..))
@@ -69,10 +68,10 @@ import qualified Language.LSP.VFS as VFS
6968
import Text.Fuzzy.Parallel (Scored (score),
7069
original)
7170

72-
import Data.Coerce (coerce)
7371
import Development.IDE
7472

7573
import qualified Data.Rope.UTF16 as Rope
74+
import Development.IDE.Spans.AtPoint (pointCommand)
7675

7776
-- Chunk size used for parallelizing fuzzy matching
7877
chunkSize :: Int
@@ -615,52 +614,35 @@ getCompletions plugins ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls,
615614
hpos = upperRange position'
616615
in getCContext lpos pm <|> getCContext hpos pm
617616

618-
dotFieldSelectorToCompl :: T.Text -> (Bool, CompItem)
619-
dotFieldSelectorToCompl label = (True, CI CiVariable label (ImportedFrom T.empty) Nothing label Nothing emptySpanDoc False Nothing)
620617

621618
-- we need the hieast to be fresh
622619
-- not fresh, hasfield won't have a chance. it would to another larger change to ghc IfaceTyCon to contain record fields
623-
tst :: [(Bool, CompItem)]
624-
tst = case maybe_ast_res of
625-
Just (HAR {hieAst = hieast, hieKind = HieFresh},_) -> concat $ pointCommand hieast (completionPrefixPos prefixInfo) (theFunc HieFresh)
620+
recordDotSyntaxCompls :: [(Bool, CompItem)]
621+
recordDotSyntaxCompls = case maybe_ast_res of
622+
Just (HAR {hieAst = hieast, hieKind = HieFresh},_) -> concat $ pointCommand hieast (completionPrefixPos prefixInfo) nodeCompletions
626623
_ -> []
627-
628-
getSels :: GHC.TyCon -> [T.Text]
629-
getSels tycon = let f fieldLabel = printOutputable fieldLabel
630-
in map f $ tyConFieldLabels tycon
631-
632-
theFunc :: HieKind Type -> HieAST Type -> [(Bool, CompItem)]
633-
theFunc kind node = concatMap g (nodeType $ nodeInfoH kind node)
634624
where
625+
nodeCompletions :: HieAST Type -> [(Bool, CompItem)]
626+
nodeCompletions node = concatMap g (nodeType $ nodeInfo node)
635627
g :: Type -> [(Bool, CompItem)]
636-
g (TyConApp theTyCon _) = map dotFieldSelectorToCompl $ getSels theTyCon
628+
g (TyConApp theTyCon _) = map (dotFieldSelectorToCompl (printOutputable $ GHC.tyConName theTyCon)) $ getSels theTyCon
637629
g _ = []
638-
639-
nodeInfoH :: HieKind a -> HieAST a -> NodeInfo a
640-
nodeInfoH (HieFromDisk _) = nodeInfo'
641-
nodeInfoH HieFresh = nodeInfo
642-
643-
pointCommand :: HieASTs t -> Position -> (HieAST t -> a) -> [a]
644-
pointCommand hf pos k =
645-
catMaybes $ M.elems $ flip M.mapWithKey (getAsts hf) $ \fs ast ->
646-
-- Since GHC 9.2:
647-
-- getAsts :: Map HiePath (HieAst a)
648-
-- type HiePath = LexialFastString
649-
--
650-
-- but before:
651-
-- getAsts :: Map HiePath (HieAst a)
652-
-- type HiePath = FastString
653-
--
654-
-- 'coerce' here to avoid an additional function for maintaining
655-
-- backwards compatibility.
656-
case selectSmallestContaining (sp $ coerce fs) ast of
657-
Nothing -> Nothing
658-
Just ast' -> Just $ k ast'
659-
where
660-
sloc fs = mkRealSrcLoc fs (fromIntegral $ line+1) (fromIntegral $ cha+1)
661-
sp fs = mkRealSrcSpan (sloc fs) (sloc fs)
662-
line = _line pos
663-
cha = _character pos
630+
getSels :: GHC.TyCon -> [T.Text]
631+
getSels tycon = let f fieldLabel = printOutputable fieldLabel
632+
in map f $ tyConFieldLabels tycon
633+
dotFieldSelectorToCompl :: T.Text -> T.Text -> (Bool, CompItem)
634+
--dotFieldSelectorToCompl label = (True, CI CiVariable label (ImportedFrom T.empty) Nothing label Nothing emptySpanDoc False Nothing)
635+
dotFieldSelectorToCompl recname label = (True, CI
636+
{ compKind = CiField
637+
, insertText = label
638+
, provenance = DefinedIn recname
639+
, typeText = Nothing
640+
, label = label
641+
, isInfix = Nothing
642+
, docs = emptySpanDoc
643+
, isTypeCompl = False
644+
, additionalTextEdits = Nothing
645+
})
664646

665647
-- completions specific to the current context
666648
ctxCompls' = case mcc of
@@ -690,7 +672,7 @@ getCompletions plugins ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls,
690672

691673
compls
692674
| T.null prefixScope = map (notQual,) localCompls ++ map (qual,) unqualCompls ++ ((notQual,) . ($ Nothing) <$> anyQualCompls)
693-
| not $ null tst = tst
675+
| not $ null recordDotSyntaxCompls = recordDotSyntaxCompls
694676
| otherwise = ((qual,) <$> Map.findWithDefault [] prefixScope (getQualCompls qualCompls))
695677
++ ((notQual,) . ($ Just prefixScope) <$> anyQualCompls)
696678

0 commit comments

Comments
 (0)