@@ -10,6 +10,7 @@ module Development.IDE.Plugin.Completions.Logic (
10
10
, localCompletionsForParsedModule
11
11
, getCompletions
12
12
, fromIdentInfo
13
+ , getCompletionPrefix
13
14
) where
14
15
15
16
import Control.Applicative
@@ -20,7 +21,7 @@ import Data.List.Extra as List hiding
20
21
import qualified Data.Map as Map
21
22
22
23
import Data.Maybe (fromMaybe , isJust ,
23
- mapMaybe )
24
+ mapMaybe , catMaybes )
24
25
import qualified Data.Text as T
25
26
import qualified Text.Fuzzy.Parallel as Fuzzy
26
27
@@ -30,6 +31,8 @@ import Data.Either (fromRight)
30
31
import Data.Function (on )
31
32
import Data.Functor
32
33
import qualified Data.HashMap.Strict as HM
34
+ import qualified Data.Map.Strict as M
35
+
33
36
import qualified Data.HashSet as HashSet
34
37
import Data.Monoid (First (.. ))
35
38
import Data.Ord (Down (Down ))
@@ -66,6 +69,12 @@ import qualified Language.LSP.VFS as VFS
66
69
import Text.Fuzzy.Parallel (Scored (score ),
67
70
original )
68
71
72
+ import Development.IDE
73
+ import Data.Coerce (coerce )
74
+
75
+ import Data.Char (isAlphaNum )
76
+ import qualified Data.Rope.UTF16 as Rope
77
+
69
78
-- Chunk size used for parallelizing fuzzy matching
70
79
chunkSize :: Int
71
80
chunkSize = 1000
@@ -557,28 +566,29 @@ getCompletions
557
566
-> IdeOptions
558
567
-> CachedCompletions
559
568
-> Maybe (ParsedModule , PositionMapping )
569
+ -> Maybe (HieAstResult , PositionMapping )
560
570
-> (Bindings , PositionMapping )
561
- -> VFS. PosPrefixInfo
571
+ -> PosPrefixInfo
562
572
-> ClientCapabilities
563
573
-> CompletionsConfig
564
574
-> HM. HashMap T. Text (HashSet. HashSet IdentInfo )
565
575
-> IO [Scored CompletionItem ]
566
576
getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qualCompls, importableModules}
567
- maybe_parsed (localBindings, bmapping) prefixInfo caps config moduleExportsMap = do
568
- let VFS. PosPrefixInfo { fullLine, prefixModule , prefixText } = prefixInfo
569
- enteredQual = if T. null prefixModule then " " else prefixModule <> " ."
577
+ maybe_parsed maybe_ast_res (localBindings, bmapping) prefixInfo caps config moduleExportsMap = do
578
+ let PosPrefixInfo { fullLine, prefixScope , prefixText } = prefixInfo
579
+ enteredQual = if T. null prefixScope then " " else prefixScope <> " ."
570
580
fullPrefix = enteredQual <> prefixText
571
581
572
582
-- Boolean labels to tag suggestions as qualified (or not)
573
- qual = not (T. null prefixModule )
583
+ qual = not (T. null prefixScope )
574
584
notQual = False
575
585
576
586
{- correct the position by moving 'foo :: Int -> String -> '
577
587
^
578
588
to 'foo :: Int -> String -> '
579
589
^
580
590
-}
581
- pos = VFS. cursorPos prefixInfo
591
+ pos = cursorPos prefixInfo
582
592
583
593
maxC = maxCompletions config
584
594
@@ -600,6 +610,53 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
600
610
lpos = lowerRange position'
601
611
hpos = upperRange position'
602
612
in getCContext lpos pm <|> getCContext hpos pm
613
+
614
+ dotFieldSelectorToCompl :: T. Text -> (Bool , CompItem )
615
+ dotFieldSelectorToCompl label = (True , CI CiVariable label (ImportedFrom T. empty) Nothing label Nothing emptySpanDoc False Nothing )
616
+
617
+ -- we need the hieast to be fresh
618
+ -- not fresh, hasfield won't have a chance. it would to another larger change to ghc IfaceTyCon to contain record fields
619
+ tst :: [(Bool , CompItem )]
620
+ tst = case maybe_ast_res of
621
+ Just (HAR {hieAst = hieast, hieKind = HieFresh },_) -> concat $ pointCommand hieast (completionPrefixPos prefixInfo) (theFunc HieFresh )
622
+ _ -> []
623
+
624
+ getSels :: GHC. TyCon -> [T. Text ]
625
+ getSels tycon = let f fieldLabel = printOutputable fieldLabel
626
+ in map f $ tyConFieldLabels tycon
627
+
628
+ theFunc :: HieKind Type -> HieAST Type -> [(Bool , CompItem )]
629
+ theFunc kind node = concatMap g (nodeType $ nodeInfoH kind node)
630
+ where
631
+ g :: Type -> [(Bool , CompItem )]
632
+ g (TyConApp theTyCon _) = map dotFieldSelectorToCompl $ getSels theTyCon
633
+ g _ = []
634
+
635
+ nodeInfoH :: HieKind a -> HieAST a -> NodeInfo a
636
+ nodeInfoH (HieFromDisk _) = nodeInfo'
637
+ nodeInfoH HieFresh = nodeInfo
638
+
639
+ pointCommand :: HieASTs t -> Position -> (HieAST t -> a ) -> [a ]
640
+ pointCommand hf pos k =
641
+ catMaybes $ M. elems $ flip M. mapWithKey (getAsts hf) $ \ fs ast ->
642
+ -- Since GHC 9.2:
643
+ -- getAsts :: Map HiePath (HieAst a)
644
+ -- type HiePath = LexialFastString
645
+ --
646
+ -- but before:
647
+ -- getAsts :: Map HiePath (HieAst a)
648
+ -- type HiePath = FastString
649
+ --
650
+ -- 'coerce' here to avoid an additional function for maintaining
651
+ -- backwards compatibility.
652
+ case selectSmallestContaining (sp $ coerce fs) ast of
653
+ Nothing -> Nothing
654
+ Just ast' -> Just $ k ast'
655
+ where
656
+ sloc fs = mkRealSrcLoc fs (fromIntegral $ line+ 1 ) (fromIntegral $ cha+ 1 )
657
+ sp fs = mkRealSrcSpan (sloc fs) (sloc fs)
658
+ line = _line pos
659
+ cha = _character pos
603
660
604
661
-- completions specific to the current context
605
662
ctxCompls' = case mcc of
@@ -611,10 +668,10 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
611
668
ctxCompls = (fmap . fmap ) (\ comp -> toggleAutoExtend config $ comp { isInfix = infixCompls }) ctxCompls'
612
669
613
670
infixCompls :: Maybe Backtick
614
- infixCompls = isUsedAsInfix fullLine prefixModule prefixText pos
671
+ infixCompls = isUsedAsInfix fullLine prefixScope prefixText pos
615
672
616
673
PositionMapping bDelta = bmapping
617
- oldPos = fromDelta bDelta $ VFS. cursorPos prefixInfo
674
+ oldPos = fromDelta bDelta $ cursorPos prefixInfo
618
675
startLoc = lowerRange oldPos
619
676
endLoc = upperRange oldPos
620
677
localCompls = map (uncurry localBindsToCompItem) $ getFuzzyScope localBindings startLoc endLoc
@@ -627,10 +684,11 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
627
684
ty = showForSnippet <$> typ
628
685
thisModName = Local $ nameSrcSpan name
629
686
630
- compls = if T. null prefixModule
631
- then map (notQual,) localCompls ++ map (qual,) unqualCompls ++ ((notQual,) . ($ Nothing ) <$> anyQualCompls)
632
- else ((qual,) <$> Map. findWithDefault [] prefixModule (getQualCompls qualCompls))
633
- ++ ((notQual,) . ($ Just prefixModule) <$> anyQualCompls)
687
+ compls
688
+ | T. null prefixScope = map (notQual,) localCompls ++ map (qual,) unqualCompls ++ ((notQual,) . ($ Nothing ) <$> anyQualCompls)
689
+ | not $ null tst = tst
690
+ | otherwise = ((qual,) <$> Map. findWithDefault [] prefixScope (getQualCompls qualCompls))
691
+ ++ ((notQual,) . ($ Just prefixScope) <$> anyQualCompls)
634
692
635
693
filtListWith f list =
636
694
[ fmap f label
@@ -641,7 +699,7 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
641
699
filtImportCompls = filtListWith (mkImportCompl enteredQual) importableModules
642
700
filterModuleExports moduleName = filtListWith $ mkModuleFunctionImport moduleName
643
701
filtKeywordCompls
644
- | T. null prefixModule = filtListWith mkExtCompl (optKeywords ideOpts)
702
+ | T. null prefixScope = filtListWith mkExtCompl (optKeywords ideOpts)
645
703
| otherwise = []
646
704
647
705
if
@@ -884,3 +942,33 @@ mergeListsBy cmp all_lists = merge_lists all_lists
884
942
[] -> []
885
943
[xs] -> xs
886
944
lists' -> merge_lists lists'
945
+
946
+
947
+ getCompletionPrefix :: (Monad m ) => Position -> VFS. VirtualFile -> m (Maybe PosPrefixInfo )
948
+ getCompletionPrefix pos@ (Position l c) (VFS. VirtualFile _ _ ropetext) =
949
+ return $ Just $ fromMaybe (PosPrefixInfo " " " " " " pos) $ do -- Maybe monad
950
+ let headMaybe [] = Nothing
951
+ headMaybe (x: _) = Just x
952
+ lastMaybe [] = Nothing
953
+ lastMaybe xs = Just $ last xs
954
+
955
+ curLine <- headMaybe $ T. lines $ Rope. toText
956
+ $ fst $ Rope. splitAtLine 1 $ snd $ Rope. splitAtLine (fromIntegral l) ropetext
957
+ let beforePos = T. take (fromIntegral c) curLine
958
+ curWord <-
959
+ if | T. null beforePos -> Just " "
960
+ | T. last beforePos == ' ' -> Just " " -- don't count abc as the curword in 'abc '
961
+ | otherwise -> lastMaybe (T. words beforePos)
962
+
963
+ let parts = T. split (== ' .' )
964
+ $ T. takeWhileEnd (\ x -> isAlphaNum x || x `elem` (" ._'" :: String )) curWord
965
+ case reverse parts of
966
+ [] -> Nothing
967
+ (x: xs) -> do
968
+ let modParts = dropWhile (\ _ -> False )
969
+ $ reverse $ filter (not . T. null ) xs
970
+ modName = T. intercalate " ." modParts
971
+ return $ PosPrefixInfo { fullLine = curLine, prefixScope = modName, prefixText = x, cursorPos = pos }
972
+
973
+ completionPrefixPos :: PosPrefixInfo -> Position
974
+ completionPrefixPos PosPrefixInfo { cursorPos = Position ln co, prefixText = str} = Position ln (co - (fromInteger . toInteger . T. length $ str) - 1 )
0 commit comments