Skip to content

Commit 26668f7

Browse files
pepeiborraalexnaspojneira
authored
Include sortText in completions and improve suggestions (#2332)
* sort completions * add an example * Include fuzzy scores in completions sort text * hlints * Extend completion documentation to inform whether an identifier is alreaady imported * Ditch alphabetical ordering - it's incompatible with qualified completions * Fix bugs in completion help text This fixes the ugly "Imported from 'Just B'" and other inconsistencies * added tests for qualified completions * Fix redundant import * Inline Fuzzy.match to apply [1] and to be case-sensitive on first match [1] - joom/fuzzy#4 * fixup! Fix bugs in completion help text * Sort qualified completions first * Filter out global suggestions that overlap with local For example, don't suggest GHC.Exts.fromList when Data.Map.fromList is in scope alraedy * Sort completions alphabetically * Show provenance in detail text * Sort local/in-scope completions first * Fix build with GHC 9 * Ignore func symbol tests Co-authored-by: Alex Naspo <[email protected]> Co-authored-by: Javier Neira <[email protected]>
1 parent 7011d5e commit 26668f7

File tree

7 files changed

+322
-98
lines changed

7 files changed

+322
-98
lines changed

Diff for: ghcide/src/Development/IDE/GHC/Compat/Core.hs

+16-4
Original file line numberDiff line numberDiff line change
@@ -190,7 +190,8 @@ module Development.IDE.GHC.Compat.Core (
190190
SrcLoc.RealSrcSpan,
191191
pattern RealSrcSpan,
192192
SrcLoc.RealSrcLoc,
193-
SrcLoc.SrcLoc(..),
193+
pattern RealSrcLoc,
194+
SrcLoc.SrcLoc(SrcLoc.UnhelpfulLoc),
194195
BufSpan,
195196
SrcLoc.leftmost_smallest,
196197
SrcLoc.containsSpan,
@@ -511,7 +512,7 @@ import GHC.Types.TyThing.Ppr
511512
#else
512513
import GHC.Types.Name.Set
513514
#endif
514-
import GHC.Types.SrcLoc (BufSpan, SrcSpan (UnhelpfulSpan))
515+
import GHC.Types.SrcLoc (BufPos, BufSpan, SrcSpan (UnhelpfulSpan), SrcLoc(UnhelpfulLoc))
515516
import qualified GHC.Types.SrcLoc as SrcLoc
516517
import GHC.Types.Unique.Supply
517518
import GHC.Types.Var (Var (varName), setTyVarUnique,
@@ -637,10 +638,11 @@ import Var (Var (varName), setTyVarUnique,
637638
#if MIN_VERSION_ghc(8,10,0)
638639
import Coercion (coercionKind)
639640
import Predicate
640-
import SrcLoc (SrcSpan (UnhelpfulSpan))
641+
import SrcLoc (SrcSpan (UnhelpfulSpan), SrcLoc (UnhelpfulLoc))
641642
#else
642643
import SrcLoc (RealLocated,
643-
SrcSpan (UnhelpfulSpan))
644+
SrcSpan (UnhelpfulSpan),
645+
SrcLoc (UnhelpfulLoc))
644646
#endif
645647
#endif
646648

@@ -651,6 +653,7 @@ import System.FilePath
651653

652654
#if !MIN_VERSION_ghc(9,0,0)
653655
type BufSpan = ()
656+
type BufPos = ()
654657
#endif
655658

656659
pattern RealSrcSpan :: SrcLoc.RealSrcSpan -> Maybe BufSpan -> SrcLoc.SrcSpan
@@ -662,6 +665,15 @@ pattern RealSrcSpan x y <- ((,Nothing) -> (SrcLoc.RealSrcSpan x, y)) where
662665
#endif
663666
{-# COMPLETE RealSrcSpan, UnhelpfulSpan #-}
664667

668+
pattern RealSrcLoc :: SrcLoc.RealSrcLoc -> Maybe BufPos-> SrcLoc.SrcLoc
669+
#if MIN_VERSION_ghc(9,0,0)
670+
pattern RealSrcLoc x y = SrcLoc.RealSrcLoc x y
671+
#else
672+
pattern RealSrcLoc x y <- ((,Nothing) -> (SrcLoc.RealSrcLoc x, y)) where
673+
RealSrcLoc x _ = SrcLoc.RealSrcLoc x
674+
#endif
675+
{-# COMPLETE RealSrcLoc, UnhelpfulLoc #-}
676+
665677

666678
pattern AvailTC :: Name -> [Name] -> [FieldLabel] -> Avail.AvailInfo
667679
#if __GLASGOW_HASKELL__ >= 902

Diff for: ghcide/src/Development/IDE/Plugin/Completions.hs

+38-4
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,6 @@ import Development.IDE.GHC.ExactPrint (Annotated (annsA)
3030
import Development.IDE.GHC.Util (prettyPrint)
3131
import Development.IDE.Graph
3232
import Development.IDE.Graph.Classes
33-
import qualified Development.IDE.Types.KnownTargets as KT
3433
import Development.IDE.Plugin.CodeAction (newImport,
3534
newImportToEdit)
3635
import Development.IDE.Plugin.CodeAction.ExactPrint
@@ -39,6 +38,7 @@ import Development.IDE.Plugin.Completions.Types
3938
import Development.IDE.Types.Exports
4039
import Development.IDE.Types.HscEnvEq (HscEnvEq (envPackageExports),
4140
hscEnv)
41+
import qualified Development.IDE.Types.KnownTargets as KT
4242
import Development.IDE.Types.Location
4343
import GHC.Exts (fromList, toList)
4444
import GHC.Generics
@@ -47,6 +47,7 @@ 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 (..))
5051

5152
descriptor :: PluginId -> PluginDescriptor IdeState
5253
descriptor plId = (defaultPluginDescriptor plId)
@@ -156,17 +157,50 @@ getCompletionsLSP ide plId
156157
let clientCaps = clientCapabilities $ shakeExtras ide
157158
config <- getCompletionsConfig plId
158159
allCompletions <- liftIO $ getCompletions plId ideOpts cci' parsedMod bindMap pfix' clientCaps config moduleExports
159-
pure $ InL (List allCompletions)
160+
pure $ InL (List $ orderedCompletions allCompletions)
160161
_ -> return (InL $ List [])
161162
_ -> return (InL $ List [])
162163
_ -> return (InL $ List [])
163164

165+
{- COMPLETION SORTING
166+
We return an ordered set of completions (local -> nonlocal -> global).
167+
Ordering is important because local/nonlocal are import aware, whereas
168+
global are not and will always insert import statements, potentially redundant.
169+
170+
Moreover, the order prioritizes qualifiers, for instance, given:
171+
172+
import qualified MyModule
173+
foo = MyModule.<complete>
174+
175+
The identifiers defined in MyModule will be listed first, followed by other
176+
identifiers in importable modules.
177+
178+
According to the LSP specification, if no sortText is provided, the label is used
179+
to sort alphabetically. Alphabetical ordering is almost never what we want,
180+
so we force the LSP client to respect our ordering by using a numbered sequence.
181+
-}
182+
183+
orderedCompletions :: [Scored CompletionItem] -> [CompletionItem]
184+
orderedCompletions [] = []
185+
orderedCompletions xx = zipWith addOrder [0..] xx
186+
where
187+
lxx = digits $ Prelude.length xx
188+
digits = Prelude.length . show
189+
190+
addOrder :: Int -> Scored CompletionItem -> CompletionItem
191+
addOrder n Scored{original = it@CompletionItem{_label,_sortText}} =
192+
it{_sortText = Just $
193+
T.pack(pad lxx n)
194+
}
195+
196+
pad n x = let sx = show x in replicate (n - Prelude.length sx) '0' <> sx
197+
164198
----------------------------------------------------------------------------------------------------
165199

166200
toModueNameText :: KT.Target -> T.Text
167201
toModueNameText target = case target of
168-
KT.TargetModule m -> T.pack $ moduleNameString m
169-
_ -> T.empty
202+
KT.TargetModule m -> T.pack $ moduleNameString m
203+
_ -> T.empty
170204

171205
extendImportCommand :: PluginCommand IdeState
172206
extendImportCommand =

0 commit comments

Comments
 (0)