Skip to content

Commit 9c40dcf

Browse files
authored
Reenable auto extend imports and drop snippets for infix completions (#1266)
* extendImport - catch duplicates * Use a command to extend imports * Reenable auto extend imports * Refactor: rid off ProduceCompletions * Remove snippets for infix forms * Fix indexing error in isUsedAsInfix * Strip qualifiers properly * Ignore hiding and qualified import decls * Compat with 8.6 * Follow changes in rewriteToEdit * Handle qualified imports * Fix merge issue
1 parent c7cd09e commit 9c40dcf

File tree

10 files changed

+410
-189
lines changed

10 files changed

+410
-189
lines changed

ghcide/ghcide.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -173,6 +173,7 @@ library
173173
Development.IDE.Types.Shake
174174
Development.IDE.Plugin
175175
Development.IDE.Plugin.Completions
176+
Development.IDE.Plugin.Completions.Types
176177
Development.IDE.Plugin.CodeAction
177178
Development.IDE.Plugin.CodeAction.ExactPrint
178179
Development.IDE.Plugin.HLS
@@ -204,7 +205,6 @@ library
204205
Development.IDE.Plugin.CodeAction.Rules
205206
Development.IDE.Plugin.CodeAction.RuleTypes
206207
Development.IDE.Plugin.Completions.Logic
207-
Development.IDE.Plugin.Completions.Types
208208
Development.IDE.Plugin.HLS.Formatter
209209
Development.IDE.Types.Action
210210
ghc-options: -Wall -Wno-name-shadowing -Wincomplete-uni-patterns

ghcide/src/Development/IDE/GHC/Compat.hs

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ module Development.IDE.GHC.Compat(
6060
module Compat.HieTypes,
6161
module Compat.HieUtils,
6262
dropForAll
63-
) where
63+
,isQualifiedImport) where
6464

6565
#if MIN_GHC_API_VERSION(8,10,0)
6666
import LinkerTypes
@@ -300,3 +300,12 @@ pattern FunTy arg res <- TyCoRep.FunTy {ft_arg = arg, ft_res = res}
300300
#else
301301
pattern FunTy arg res <- TyCoRep.FunTy arg res
302302
#endif
303+
304+
isQualifiedImport :: ImportDecl a -> Bool
305+
#if MIN_GHC_API_VERSION(8,10,0)
306+
isQualifiedImport ImportDecl{ideclQualified = NotQualified} = False
307+
isQualifiedImport ImportDecl{} = True
308+
#else
309+
isQualifiedImport ImportDecl{ideclQualified} = ideclQualified
310+
#endif
311+
isQualifiedImport _ = False

ghcide/src/Development/IDE/Plugin/CodeAction/ExactPrint.hs

Lines changed: 38 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
module Development.IDE.Plugin.CodeAction.ExactPrint
77
( Rewrite (..),
88
rewriteToEdit,
9+
rewriteToWEdit,
910
transferAnn,
1011

1112
-- * Utilities
@@ -40,6 +41,8 @@ import Retrie.GHC (rdrNameOcc, unpackFS, mkRealSrcSpan, realSrcSpanEnd)
4041
import Development.IDE.Spans.Common
4142
import Development.IDE.GHC.Error
4243
import Safe (lastMay)
44+
import Data.Generics (listify)
45+
import GHC.Exts (IsList (fromList))
4346

4447
------------------------------------------------------------------------------
4548

@@ -56,7 +59,7 @@ data Rewrite where
5659

5760
------------------------------------------------------------------------------
5861

59-
-- | Convert a 'Rewrite' into a 'WorkspaceEdit'.
62+
-- | Convert a 'Rewrite' into a list of '[TextEdit]'.
6063
rewriteToEdit ::
6164
DynFlags ->
6265
Anns ->
@@ -71,6 +74,16 @@ rewriteToEdit dflags anns (Rewrite dst f) = do
7174
]
7275
pure editMap
7376

77+
-- | Convert a 'Rewrite' into a 'WorkspaceEdit'
78+
rewriteToWEdit :: DynFlags -> Uri -> Anns -> Rewrite -> Either String WorkspaceEdit
79+
rewriteToWEdit dflags uri anns r = do
80+
edits <- rewriteToEdit dflags anns r
81+
return $
82+
WorkspaceEdit
83+
{ _changes = Just (fromList [(uri, List edits)])
84+
, _documentChanges = Nothing
85+
}
86+
7487
------------------------------------------------------------------------------
7588

7689
-- | Fix the parentheses around a type context
@@ -200,17 +213,25 @@ extendImportTopLevel df idnetifier (L l it@ImportDecl {..})
200213
src <- uniqueSrcSpanT
201214
top <- uniqueSrcSpanT
202215
rdr <- liftParseAST df idnetifier
216+
217+
let alreadyImported =
218+
showNameWithoutUniques (occName (unLoc rdr)) `elem`
219+
map (showNameWithoutUniques @OccName) (listify (const True) lies)
220+
when alreadyImported $
221+
lift (Left $ idnetifier <> " already imported")
222+
203223
let lie = L src $ IEName rdr
204224
x = L top $ IEVar noExtField lie
205-
when hasSibling $
206-
addTrailingCommaT (last lies)
207-
addSimpleAnnT x (DP (0, if hasSibling then 1 else 0)) []
208-
addSimpleAnnT rdr dp00 $ unqalDP $ hasParen idnetifier
209-
-- Parens are attachted to `lies`, so if `lies` was empty previously,
210-
-- we need change the ann key from `[]` to `:` to keep parens and other anns.
211-
unless hasSibling $
212-
transferAnn (L l' lies) (L l' [x]) id
213-
return $ L l it {ideclHiding = Just (hide, L l' $ lies ++ [x])}
225+
if x `elem` lies then lift (Left $ idnetifier <> " already imported") else do
226+
when hasSibling $
227+
addTrailingCommaT (last lies)
228+
addSimpleAnnT x (DP (0, if hasSibling then 1 else 0)) []
229+
addSimpleAnnT rdr dp00 $ unqalDP $ hasParen idnetifier
230+
-- Parens are attachted to `lies`, so if `lies` was empty previously,
231+
-- we need change the ann key from `[]` to `:` to keep parens and other anns.
232+
unless hasSibling $
233+
transferAnn (L l' lies) (L l' [x]) id
234+
return $ L l it {ideclHiding = Just (hide, L l' $ lies ++ [x])}
214235
extendImportTopLevel _ _ _ = lift $ Left "Unable to extend the import list"
215236

216237
-- | Add an identifier with its parent to import list
@@ -244,6 +265,13 @@ extendImportViaParent df parent child (L l it@ImportDecl {..})
244265
do
245266
srcChild <- uniqueSrcSpanT
246267
childRdr <- liftParseAST df child
268+
269+
let alreadyImported =
270+
showNameWithoutUniques(occName (unLoc childRdr)) `elem`
271+
map (showNameWithoutUniques @OccName) (listify (const True) lies')
272+
when alreadyImported $
273+
lift (Left $ child <> " already included in " <> parent <> " imports")
274+
247275
when hasSibling $
248276
addTrailingCommaT (last lies')
249277
let childLIE = L srcChild $ IEName childRdr

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

Lines changed: 76 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -4,14 +4,19 @@
44

55
module Development.IDE.Plugin.Completions
66
( descriptor
7-
, ProduceCompletions(..)
87
, LocalCompletions(..)
98
, NonLocalCompletions(..)
109
) where
1110
import Language.Haskell.LSP.Types
1211
import qualified Language.Haskell.LSP.Core as LSP
1312
import qualified Language.Haskell.LSP.VFS as VFS
1413

14+
import Control.Monad
15+
import Control.Monad.Trans.Maybe
16+
import Data.Aeson
17+
import Data.List (find)
18+
import Data.Maybe
19+
import qualified Data.Text as T
1520
import Development.Shake.Classes
1621
import Development.Shake
1722
import GHC.Generics
@@ -22,36 +27,33 @@ import Development.IDE.Types.Location
2227
import Development.IDE.Core.RuleTypes
2328
import Development.IDE.Core.Shake
2429
import Development.IDE.GHC.Compat
25-
30+
import Development.IDE.GHC.ExactPrint (Annotated (annsA), GetAnnotatedParsedSource (GetAnnotatedParsedSource))
2631
import Development.IDE.GHC.Util
27-
import TcRnDriver (tcRnImportDecls)
28-
import Data.Maybe
32+
import Development.IDE.Plugin.CodeAction.ExactPrint
33+
import Development.IDE.Plugin.Completions.Types
2934
import Ide.Plugin.Config (Config (completionSnippetsOn))
3035
import Ide.PluginUtils (getClientConfig)
3136
import Ide.Types
32-
37+
import TcRnDriver (tcRnImportDecls)
3338
#if defined(GHC_LIB)
3439
import Development.IDE.Import.DependencyInformation
3540
#endif
3641

3742
descriptor :: PluginId -> PluginDescriptor IdeState
3843
descriptor plId = (defaultPluginDescriptor plId)
39-
{ pluginRules = produceCompletions
40-
, pluginCompletionProvider = Just getCompletionsLSP
41-
}
44+
{ pluginRules = produceCompletions,
45+
pluginCompletionProvider = Just (getCompletionsLSP plId),
46+
pluginCommands = [extendImportCommand]
47+
}
4248

4349
produceCompletions :: Rules ()
4450
produceCompletions = do
45-
define $ \ProduceCompletions file -> do
46-
local <- useWithStale LocalCompletions file
47-
nonLocal <- useWithStale NonLocalCompletions file
48-
let extract = fmap fst
49-
return ([], extract local <> extract nonLocal)
5051
define $ \LocalCompletions file -> do
52+
let uri = fromNormalizedUri $ normalizedFilePathToUri file
5153
pm <- useWithStale GetParsedModule file
5254
case pm of
5355
Just (pm, _) -> do
54-
let cdata = localCompletionsForParsedModule pm
56+
let cdata = localCompletionsForParsedModule uri pm
5557
return ([], Just cdata)
5658
_ -> return ([], Nothing)
5759
define $ \NonLocalCompletions file -> do
@@ -77,7 +79,8 @@ produceCompletions = do
7779
res <- liftIO $ tcRnImportDecls env (dropListFromImportDecl <$> imps)
7880
case res of
7981
(_, Just rdrEnv) -> do
80-
cdata <- liftIO $ cacheDataProducer env (ms_mod ms) rdrEnv imps parsedDeps
82+
let uri = fromNormalizedUri $ normalizedFilePathToUri file
83+
cdata <- liftIO $ cacheDataProducer uri env (ms_mod ms) rdrEnv imps parsedDeps
8184
return ([], Just cdata)
8285
(_diag, _) ->
8386
return ([], Nothing)
@@ -94,16 +97,9 @@ dropListFromImportDecl iDecl = let
9497
in f <$> iDecl
9598

9699
-- | Produce completions info for a file
97-
type instance RuleResult ProduceCompletions = CachedCompletions
98100
type instance RuleResult LocalCompletions = CachedCompletions
99101
type instance RuleResult NonLocalCompletions = CachedCompletions
100102

101-
data ProduceCompletions = ProduceCompletions
102-
deriving (Eq, Show, Typeable, Generic)
103-
instance Hashable ProduceCompletions
104-
instance NFData ProduceCompletions
105-
instance Binary ProduceCompletions
106-
107103
data LocalCompletions = LocalCompletions
108104
deriving (Eq, Show, Typeable, Generic)
109105
instance Hashable LocalCompletions
@@ -115,13 +111,15 @@ data NonLocalCompletions = NonLocalCompletions
115111
instance Hashable NonLocalCompletions
116112
instance NFData NonLocalCompletions
117113
instance Binary NonLocalCompletions
114+
118115
-- | Generate code actions.
119116
getCompletionsLSP
120-
:: LSP.LspFuncs Config
117+
:: PluginId
118+
-> LSP.LspFuncs Config
121119
-> IdeState
122120
-> CompletionParams
123121
-> IO (Either ResponseError CompletionResponseResult)
124-
getCompletionsLSP lsp ide
122+
getCompletionsLSP plId lsp ide
125123
CompletionParams{_textDocument=TextDocumentIdentifier uri
126124
,_position=position
127125
,_context=completionContext} = do
@@ -131,12 +129,13 @@ getCompletionsLSP lsp ide
131129
let npath = toNormalizedFilePath' path
132130
(ideOpts, compls) <- runIdeAction "Completion" (shakeExtras ide) $ do
133131
opts <- liftIO $ getIdeOptionsIO $ shakeExtras ide
134-
compls <- useWithStaleFast ProduceCompletions npath
132+
localCompls <- useWithStaleFast LocalCompletions npath
133+
nonLocalCompls <- useWithStaleFast NonLocalCompletions npath
135134
pm <- useWithStaleFast GetParsedModule npath
136135
binds <- fromMaybe (mempty, zeroMapping) <$> useWithStaleFast GetBindings npath
137-
pure (opts, fmap (,pm,binds) compls )
136+
pure (opts, fmap (,pm,binds) ((fst <$> localCompls) <> (fst <$> nonLocalCompls)))
138137
case compls of
139-
Just ((cci', _), parsedMod, bindMap) -> do
138+
Just (cci', parsedMod, bindMap) -> do
140139
pfix <- VFS.getCompletionPrefix position cnts
141140
case (pfix, completionContext) of
142141
(Just (VFS.PosPrefixInfo _ "" _ _), Just CompletionContext { _triggerCharacter = Just "."})
@@ -145,8 +144,57 @@ getCompletionsLSP lsp ide
145144
let clientCaps = clientCapabilities $ shakeExtras ide
146145
config <- getClientConfig lsp
147146
let snippets = WithSnippets . completionSnippetsOn $ config
148-
allCompletions <- getCompletions ideOpts cci' parsedMod bindMap pfix' clientCaps snippets
147+
allCompletions <- getCompletions plId ideOpts cci' parsedMod bindMap pfix' clientCaps snippets
149148
pure $ Completions (List allCompletions)
150149
_ -> return (Completions $ List [])
151150
_ -> return (Completions $ List [])
152151
_ -> return (Completions $ List [])
152+
153+
----------------------------------------------------------------------------------------------------
154+
155+
extendImportCommand :: PluginCommand IdeState
156+
extendImportCommand =
157+
PluginCommand (CommandId extendImportCommandId) "additional edits for a completion" extendImportHandler
158+
159+
extendImportHandler :: CommandFunction IdeState ExtendImport
160+
extendImportHandler _lsp ideState edit = do
161+
res <- runMaybeT $ extendImportHandler' ideState edit
162+
return (Right Null, res)
163+
164+
extendImportHandler' :: IdeState -> ExtendImport -> MaybeT IO (ServerMethod, ApplyWorkspaceEditParams)
165+
extendImportHandler' ideState ExtendImport {..}
166+
| Just fp <- uriToFilePath doc,
167+
nfp <- toNormalizedFilePath' fp =
168+
do
169+
(ms, ps, imps) <- MaybeT $
170+
runAction "extend import" ideState $
171+
runMaybeT $ do
172+
-- We want accurate edits, so do not use stale data here
173+
(ms, imps) <- MaybeT $ use GetModSummaryWithoutTimestamps nfp
174+
ps <- MaybeT $ use GetAnnotatedParsedSource nfp
175+
return (ms, ps, imps)
176+
let df = ms_hspp_opts ms
177+
wantedModule = mkModuleName (T.unpack importName)
178+
wantedQual = mkModuleName . T.unpack <$> importQual
179+
imp <- liftMaybe $ find (isWantedModule wantedModule wantedQual) imps
180+
wedit <-
181+
liftEither $
182+
rewriteToWEdit df doc (annsA ps) $
183+
extendImport (T.unpack <$> thingParent) (T.unpack newThing) imp
184+
return (WorkspaceApplyEdit, ApplyWorkspaceEditParams wedit)
185+
| otherwise =
186+
mzero
187+
188+
isWantedModule :: ModuleName -> Maybe ModuleName -> GenLocated l (ImportDecl pass) -> Bool
189+
isWantedModule wantedModule Nothing (L _ it@ImportDecl{ideclName, ideclHiding = Just (False, _)}) =
190+
not (isQualifiedImport it) && unLoc ideclName == wantedModule
191+
isWantedModule wantedModule (Just qual) (L _ ImportDecl{ideclAs, ideclName, ideclHiding = Just (False, _)}) =
192+
unLoc ideclName == wantedModule && (wantedModule == qual || (unLoc <$> ideclAs) == Just qual)
193+
isWantedModule _ _ _ = False
194+
195+
liftMaybe :: Monad m => Maybe a -> MaybeT m a
196+
liftMaybe a = MaybeT $ pure a
197+
198+
liftEither :: Monad m => Either e a -> MaybeT m a
199+
liftEither (Left _) = mzero
200+
liftEither (Right x) = return x

0 commit comments

Comments
 (0)