Skip to content

Commit 90f43a5

Browse files
committed
Include fuzzy scores in completions sort text
1 parent d89c97e commit 90f43a5

File tree

3 files changed

+101
-25
lines changed

3 files changed

+101
-25
lines changed

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

Lines changed: 27 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,8 @@ import Ide.Types
4747
import qualified Language.LSP.Server as LSP
4848
import Language.LSP.Types
4949
import qualified Language.LSP.VFS as VFS
50+
import Text.Fuzzy.Parallel (Scored (..))
51+
5052

5153
descriptor :: PluginId -> PluginDescriptor IdeState
5254
descriptor plId = (defaultPluginDescriptor plId)
@@ -174,7 +176,7 @@ getCompletionsLSP ide plId
174176
of repeated occurrences we generate sortText values that include both the label and
175177
an index denoting the relative order
176178
177-
EXAMPLE
179+
EXAMPLE OF DESIRED BEHAVIOUR
178180
We produce completions:
179181
x -- local
180182
y -- local
@@ -188,15 +190,33 @@ getCompletionsLSP ide plId
188190
x -- global
189191
190192
This is fine if the LSP client thinks that 'y' is more relevant than 'x'.
191-
We are OK with that choice since the local options are presented before the global ones
193+
Importantly, the local options are presented before the global ones
192194
195+
We provide the LSP client with 3 sorting measures encoded in _sortText:
196+
1. The distance to the best fuzzy score
197+
2. The label
198+
3. The index in our original sorted list
193199
-}
194-
orderedCompletions :: [CompletionItem] -> [CompletionItem]
195-
orderedCompletions = zipWith addOrder [0..]
200+
201+
orderedCompletions :: [Scored CompletionItem] -> [CompletionItem]
202+
orderedCompletions [] = []
203+
orderedCompletions xx@(h:_) = zipWith addOrder [0..] xx
196204
where
197-
addOrder :: Int -> CompletionItem -> CompletionItem
198-
addOrder n it@CompletionItem{_label} =
199-
it{_sortText = Just $ _label <> T.pack(show n)}
205+
lxx = digits $ Prelude.length xx
206+
lm = digits maxScore
207+
maxScore = score_ h
208+
209+
digits = Prelude.length . show
210+
211+
addOrder :: Int -> Scored CompletionItem -> CompletionItem
212+
addOrder n Scored{score_, original = it@CompletionItem{_label,_sortText}} =
213+
it{_sortText = Just $
214+
(T.pack(pad lm (maxScore - score_))) <>
215+
_label <>
216+
T.pack(pad lxx n)
217+
}
218+
219+
pad n x = let sx = show x in replicate (n - Prelude.length sx) '0' <> sx
200220

201221
----------------------------------------------------------------------------------------------------
202222

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

Lines changed: 61 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ import qualified Text.Fuzzy.Parallel as Fuzzy
2929
import Control.Monad
3030
import Data.Aeson (ToJSON (toJSON))
3131
import Data.Either (fromRight)
32+
import Data.Function (on)
3233
import Data.Functor
3334
import qualified Data.HashMap.Strict as HM
3435
import qualified Data.HashSet as HashSet
@@ -52,6 +53,8 @@ import Ide.Types (CommandId (..),
5253
import Language.LSP.Types
5354
import Language.LSP.Types.Capabilities
5455
import qualified Language.LSP.VFS as VFS
56+
import Text.Fuzzy.Parallel (Scored (score_),
57+
original)
5558

5659
-- Chunk size used for parallelizing fuzzy matching
5760
chunkSize :: Int
@@ -200,6 +203,7 @@ mkCompl
200203
MarkupContent MkMarkdown $
201204
T.intercalate sectionSeparator docs'
202205

206+
203207
mkAdditionalEditsCommand :: PluginId -> ExtendImport -> Command
204208
mkAdditionalEditsCommand pId edits =
205209
mkLspCommand pId (CommandId extendImportCommandId) "extend import" (Just [toJSON edits])
@@ -525,7 +529,7 @@ getCompletions
525529
-> ClientCapabilities
526530
-> CompletionsConfig
527531
-> HM.HashMap T.Text (HashSet.HashSet IdentInfo)
528-
-> IO [CompletionItem]
532+
-> IO [Scored CompletionItem]
529533
getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qualCompls, importableModules}
530534
maybe_parsed (localBindings, bmapping) prefixInfo caps config moduleExportsMap = do
531535
let VFS.PosPrefixInfo { fullLine, prefixModule, prefixText } = prefixInfo
@@ -541,12 +545,14 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
541545

542546
maxC = maxCompletions config
543547

548+
filtModNameCompls :: [Scored CompletionItem]
544549
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
548554

549-
filtCompls = map Fuzzy.original $ Fuzzy.filter chunkSize maxC prefixText ctxCompls "" "" label False
555+
filtCompls = Fuzzy.filter chunkSize maxC prefixText ctxCompls "" "" label False
550556
where
551557

552558
mcc = case maybe_parsed of
@@ -592,9 +598,9 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
592598
++ (($ Just prefixModule) <$> anyQualCompls)
593599

594600
filtListWith f list =
595-
[ f label
601+
[ fmap f label
596602
| label <- Fuzzy.simpleFilter chunkSize maxC fullPrefix list
597-
, enteredQual `T.isPrefixOf` label
603+
, enteredQual `T.isPrefixOf` original label
598604
]
599605

600606
filtImportCompls = filtListWith (mkImportCompl enteredQual) importableModules
@@ -621,11 +627,13 @@ getCompletions plId ideOpts CC {allModNamesAsNS, anyQualCompls, unqualCompls, qu
621627
-> return []
622628
| otherwise -> do
623629
-- 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+
]
629637

630638
uniqueCompl :: CompItem -> CompItem -> Ordering
631639
uniqueCompl x y =
@@ -777,3 +785,44 @@ getImportQual :: LImportDecl GhcPs -> Maybe T.Text
777785
getImportQual (L _ imp)
778786
| isQualifiedImport imp = Just $ T.pack $ moduleNameString $ maybe (unLoc $ ideclName imp) unLoc (ideclAs imp)
779787
| 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'

ghcide/src/Text/Fuzzy/Parallel.hs

Lines changed: 13 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,9 @@
22
module Text.Fuzzy.Parallel
33
( filter,
44
simpleFilter,
5+
Scored(..),
56
-- reexports
6-
Fuzzy(..),
7+
Fuzzy,
78
match
89
) where
910

@@ -19,6 +20,9 @@ import Data.Maybe (fromJust)
1920
import Prelude hiding (filter)
2021
import Text.Fuzzy (Fuzzy (..), match)
2122

23+
data Scored a = Scored {score_ :: !Int, original:: !a}
24+
deriving Functor
25+
2226
-- | The function to filter a list of values by fuzzy search on the text extracted from them.
2327
filter :: (TextualMonoid s)
2428
=> Int -- ^ Chunk size. 1000 works well.
@@ -29,7 +33,7 @@ filter :: (TextualMonoid s)
2933
-> s -- ^ The text to add after each match.
3034
-> (t -> s) -- ^ The function to extract the text from the container.
3135
-> Bool -- ^ Case sensitivity.
32-
-> [Fuzzy t s] -- ^ The list of results, sorted, highest score first.
36+
-> [Scored t] -- ^ The list of results, sorted, highest score first.
3337
filter chunkSize maxRes pattern ts pre post extract caseSen = runST $ do
3438
let v = V.mapMaybe id
3539
(V.map (\t -> match pattern t pre post extract caseSen) (V.fromList ts)
@@ -50,9 +54,9 @@ simpleFilter :: (TextualMonoid s)
5054
-> Int -- ^ Max. number of results wanted
5155
-> s -- ^ Pattern to look for.
5256
-> [s] -- ^ List of texts to check.
53-
-> [s] -- ^ The ones that match.
57+
-> [Scored s] -- ^ The ones that match.
5458
simpleFilter chunk maxRes pattern xs =
55-
map original $ filter chunk maxRes pattern xs mempty mempty id False
59+
filter chunk maxRes pattern xs mempty mempty id False
5660

5761
--------------------------------------------------------------------------------
5862

@@ -102,7 +106,7 @@ partialSortByAscScore :: TextualMonoid s
102106
=> Int -- ^ Number of items needed
103107
-> Int -- ^ Value of a perfect score
104108
-> Vector (Fuzzy t s)
105-
-> [Fuzzy t s]
109+
-> [Scored t]
106110
partialSortByAscScore wantedCount perfectScore v = loop 0 (SortState minBound perfectScore 0) [] where
107111
l = V.length v
108112
loop index st@SortState{..} acc
@@ -115,12 +119,15 @@ partialSortByAscScore wantedCount perfectScore v = loop 0 (SortState minBound pe
115119
| otherwise =
116120
case v!index of
117121
x | score x == scoreWanted
118-
-> loop (index+1) st{foundCount = foundCount+1} (x:acc)
122+
-> loop (index+1) st{foundCount = foundCount+1} (toScored x:acc)
119123
| score x < scoreWanted && score x > bestScoreSeen
120124
-> loop (index+1) st{bestScoreSeen = score x} acc
121125
| otherwise
122126
-> loop (index+1) st acc
123127

128+
toScored :: TextualMonoid s => Fuzzy t s -> Scored t
129+
toScored Fuzzy{..} = Scored score original
130+
124131
data SortState a = SortState
125132
{ bestScoreSeen :: !Int
126133
, scoreWanted :: !Int

0 commit comments

Comments
 (0)