@@ -29,6 +29,7 @@ import qualified Text.Fuzzy.Parallel as Fuzzy
29
29
import Control.Monad
30
30
import Data.Aeson (ToJSON (toJSON ))
31
31
import Data.Either (fromRight )
32
+ import Data.Function (on )
32
33
import Data.Functor
33
34
import qualified Data.HashMap.Strict as HM
34
35
import qualified Data.HashSet as HashSet
@@ -52,6 +53,8 @@ import Ide.Types (CommandId (..),
52
53
import Language.LSP.Types
53
54
import Language.LSP.Types.Capabilities
54
55
import qualified Language.LSP.VFS as VFS
56
+ import Text.Fuzzy.Parallel (Scored (score_ ),
57
+ original )
55
58
56
59
-- Chunk size used for parallelizing fuzzy matching
57
60
chunkSize :: Int
@@ -200,6 +203,7 @@ mkCompl
200
203
MarkupContent MkMarkdown $
201
204
T. intercalate sectionSeparator docs'
202
205
206
+
203
207
mkAdditionalEditsCommand :: PluginId -> ExtendImport -> Command
204
208
mkAdditionalEditsCommand pId edits =
205
209
mkLspCommand pId (CommandId extendImportCommandId) " extend import" (Just [toJSON edits])
@@ -525,7 +529,7 @@ getCompletions
525
529
-> ClientCapabilities
526
530
-> CompletionsConfig
527
531
-> HM. HashMap T. Text (HashSet. HashSet IdentInfo )
528
- -> IO [CompletionItem ]
532
+ -> IO [Scored CompletionItem ]
529
533
getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qualCompls, importableModules}
530
534
maybe_parsed (localBindings, bmapping) prefixInfo caps config moduleExportsMap = do
531
535
let VFS. PosPrefixInfo { fullLine, prefixModule, prefixText } = prefixInfo
@@ -541,12 +545,14 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
541
545
542
546
maxC = maxCompletions config
543
547
548
+ filtModNameCompls :: [Scored CompletionItem ]
544
549
filtModNameCompls =
545
- map mkModCompl
546
- $ mapMaybe (T. stripPrefix enteredQual)
547
- $ Fuzzy. simpleFilter chunkSize maxC fullPrefix allModNamesAsNS
550
+ (fmap . fmap ) mkModCompl
551
+ $ Fuzzy. simpleFilter chunkSize maxC fullPrefix
552
+ $ (if T. null enteredQual then id else mapMaybe (T. stripPrefix enteredQual))
553
+ $ allModNamesAsNS
548
554
549
- filtCompls = map Fuzzy. original $ Fuzzy. filter chunkSize maxC prefixText ctxCompls " " " " label False
555
+ filtCompls = Fuzzy. filter chunkSize maxC prefixText ctxCompls " " " " label False
550
556
where
551
557
552
558
mcc = case maybe_parsed of
@@ -592,9 +598,9 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
592
598
++ (($ Just prefixModule) <$> anyQualCompls)
593
599
594
600
filtListWith f list =
595
- [ f label
601
+ [ fmap f label
596
602
| label <- Fuzzy. simpleFilter chunkSize maxC fullPrefix list
597
- , enteredQual `T.isPrefixOf` label
603
+ , enteredQual `T.isPrefixOf` original label
598
604
]
599
605
600
606
filtImportCompls = filtListWith (mkImportCompl enteredQual) importableModules
@@ -621,11 +627,13 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
621
627
-> return []
622
628
| otherwise -> do
623
629
-- assumes that nubOrdBy is stable
624
- let uniqueFiltCompls = nubOrdBy uniqueCompl filtCompls
625
- let compls = map (mkCompl plId ideOpts) uniqueFiltCompls
626
- return $ filtModNameCompls
627
- ++ filtKeywordCompls
628
- ++ map (toggleSnippets caps config) compls
630
+ let uniqueFiltCompls = nubOrdBy (uniqueCompl `on` Fuzzy. original) filtCompls
631
+ let compls = (fmap . fmap ) (mkCompl plId ideOpts) uniqueFiltCompls
632
+ return $ mergeListsBy (flip compare `on` score_)
633
+ [ filtModNameCompls
634
+ , filtKeywordCompls
635
+ , (fmap . fmap ) (toggleSnippets caps config) compls
636
+ ]
629
637
630
638
uniqueCompl :: CompItem -> CompItem -> Ordering
631
639
uniqueCompl x y =
@@ -777,3 +785,44 @@ getImportQual :: LImportDecl GhcPs -> Maybe T.Text
777
785
getImportQual (L _ imp)
778
786
| isQualifiedImport imp = Just $ T. pack $ moduleNameString $ maybe (unLoc $ ideclName imp) unLoc (ideclAs imp)
779
787
| otherwise = Nothing
788
+
789
+ --------------------------------------------------------------------------------
790
+
791
+ -- This comes from the GHC.Utils.Misc module (not exported)
792
+ -- | Merge an unsorted list of sorted lists, for example:
793
+ --
794
+ -- > mergeListsBy compare [ [2,5,15], [1,10,100] ] = [1,2,5,10,15,100]
795
+ --
796
+ -- \( O(n \log{} k) \)
797
+ mergeListsBy :: forall a . (a -> a -> Ordering ) -> [[a ]] -> [a ]
798
+ mergeListsBy cmp all_lists = merge_lists all_lists
799
+ where
800
+ -- Implements "Iterative 2-Way merge" described at
801
+ -- https://en.wikipedia.org/wiki/K-way_merge_algorithm
802
+
803
+ -- Merge two sorted lists into one in O(n).
804
+ merge2 :: [a ] -> [a ] -> [a ]
805
+ merge2 [] ys = ys
806
+ merge2 xs [] = xs
807
+ merge2 (x: xs) (y: ys) =
808
+ case cmp x y of
809
+ Prelude. GT -> y : merge2 (x: xs) ys
810
+ _ -> x : merge2 xs (y: ys)
811
+
812
+ -- Merge the first list with the second, the third with the fourth, and so
813
+ -- on. The output has half as much lists as the input.
814
+ merge_neighbours :: [[a ]] -> [[a ]]
815
+ merge_neighbours [] = []
816
+ merge_neighbours [xs] = [xs]
817
+ merge_neighbours (xs : ys : lists) =
818
+ merge2 xs ys : merge_neighbours lists
819
+
820
+ -- Since 'merge_neighbours' halves the amount of lists in each iteration,
821
+ -- we perform O(log k) iteration. Each iteration is O(n). The total running
822
+ -- time is therefore O(n log k).
823
+ merge_lists :: [[a ]] -> [a ]
824
+ merge_lists lists =
825
+ case merge_neighbours lists of
826
+ [] -> []
827
+ [xs] -> xs
828
+ lists' -> merge_lists lists'
0 commit comments