@@ -79,14 +79,14 @@ import GHC.Exts (fromList)
7979import qualified GHC.LanguageExtensions as Lang
8080import Ide.Logger hiding
8181 (group )
82- import Ide.PluginUtils (extractTextInRange ,
82+ import Ide.PluginUtils (extendToFullLines ,
83+ extractTextInRange ,
8384 subRange )
8485import Ide.Types
8586import Language.LSP.Protocol.Message (Method (.. ),
8687 SMethod (.. ))
8788import Language.LSP.Protocol.Types (ApplyWorkspaceEditParams (.. ),
8889 CodeAction (.. ),
89- CodeActionContext (CodeActionContext , _diagnostics ),
9090 CodeActionKind (CodeActionKind_QuickFix ),
9191 CodeActionParams (CodeActionParams ),
9292 Command ,
@@ -110,16 +110,16 @@ import Text.Regex.TDFA ((=~), (=~~))
110110
111111-- | Generate code actions.
112112codeAction :: PluginMethodHandler IdeState 'Method_TextDocumentCodeAction
113- codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range CodeActionContext {_diagnostics = xs} ) = do
113+ codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) range _ ) = do
114114 contents <- lift $ LSP. getVirtualFile $ toNormalizedUri uri
115115 liftIO $ do
116116 let text = virtualFileText <$> contents
117117 mbFile = toNormalizedFilePath' <$> uriToFilePath uri
118- diag <- atomically $ fmap (\ (_, _, d) -> d) . filter (\ (p, _, _) -> mbFile == Just p) <$> getDiagnostics state
118+ allDiags <- atomically $ fmap (\ (_, _, d) -> d) . filter (\ (p, _, _) -> mbFile == Just p) <$> getDiagnostics state
119119 (join -> parsedModule) <- runAction " GhcideCodeActions.getParsedModule" state $ getParsedModule `traverse` mbFile
120120 let
121- actions = caRemoveRedundantImports parsedModule text diag xs uri
122- <> caRemoveInvalidExports parsedModule text diag xs uri
121+ actions = caRemoveRedundantImports parsedModule text allDiags range uri
122+ <> caRemoveInvalidExports parsedModule text allDiags range uri
123123 pure $ InL actions
124124
125125-------------------------------------------------------------------------------------------------
@@ -438,19 +438,25 @@ suggestRemoveRedundantImport ParsedModule{pm_parsed_source = L _ HsModule{hsmod
438438 = [(" Remove import" , [TextEdit (extendToWholeLineIfPossible contents _range) " " ])]
439439 | otherwise = []
440440
441+ diagInRange :: Diagnostic -> Range -> Bool
442+ diagInRange Diagnostic {_range = dr} r = dr `subRange` extendedRange
443+ where
444+ -- Ensures the range captures full lines. Makes it easier to trigger the correct
445+ -- "remove redundant" code actions from anywhere on the offending line.
446+ extendedRange = extendToFullLines r
441447
442448-- Note [Removing imports is preferred]
443449-- It's good to prefer the remove imports code action because an unused import
444450-- is likely to be removed and less likely the warning will be disabled.
445451-- Therefore actions to remove a single or all redundant imports should be
446452-- preferred, so that the client can prioritize them higher.
447- caRemoveRedundantImports :: Maybe ParsedModule -> Maybe T. Text -> [Diagnostic ] -> [ Diagnostic ] -> Uri -> [Command |? CodeAction ]
448- caRemoveRedundantImports m contents digs ctxDigs uri
453+ caRemoveRedundantImports :: Maybe ParsedModule -> Maybe T. Text -> [Diagnostic ] -> Range -> Uri -> [Command |? CodeAction ]
454+ caRemoveRedundantImports m contents allDiags contextRange uri
449455 | Just pm <- m,
450- r <- join $ map (\ d -> repeat d `zip` suggestRemoveRedundantImport pm contents d) digs ,
456+ r <- join $ map (\ d -> repeat d `zip` suggestRemoveRedundantImport pm contents d) allDiags ,
451457 allEdits <- [ e | (_, (_, edits)) <- r, e <- edits],
452458 caRemoveAll <- removeAll allEdits,
453- ctxEdits <- [ x | x@ (d, _) <- r, d `elem` ctxDigs ],
459+ ctxEdits <- [ x | x@ (d, _) <- r, d `diagInRange` contextRange ],
454460 not $ null ctxEdits,
455461 caRemoveCtx <- map (\ (d, (title, tedit)) -> removeSingle title tedit d) ctxEdits
456462 = caRemoveCtx ++ [caRemoveAll]
@@ -474,18 +480,18 @@ caRemoveRedundantImports m contents digs ctxDigs uri
474480 _data_ = Nothing
475481 _changeAnnotations = Nothing
476482
477- caRemoveInvalidExports :: Maybe ParsedModule -> Maybe T. Text -> [Diagnostic ] -> [ Diagnostic ] -> Uri -> [Command |? CodeAction ]
478- caRemoveInvalidExports m contents digs ctxDigs uri
483+ caRemoveInvalidExports :: Maybe ParsedModule -> Maybe T. Text -> [Diagnostic ] -> Range -> Uri -> [Command |? CodeAction ]
484+ caRemoveInvalidExports m contents allDiags contextRange uri
479485 | Just pm <- m,
480486 Just txt <- contents,
481487 txt' <- indexedByPosition $ T. unpack txt,
482- r <- mapMaybe (groupDiag pm) digs ,
488+ r <- mapMaybe (groupDiag pm) allDiags ,
483489 r' <- map (\ (t,d,rs) -> (t,d,extend txt' rs)) r,
484490 caRemoveCtx <- mapMaybe removeSingle r',
485491 allRanges <- nubOrd $ [ range | (_,_,ranges) <- r, range <- ranges],
486492 allRanges' <- extend txt' allRanges,
487493 Just caRemoveAll <- removeAll allRanges',
488- ctxEdits <- [ x | x@ (_, d, _) <- r, d `elem` ctxDigs ],
494+ ctxEdits <- [ x | x@ (_, d, _) <- r, d `diagInRange` contextRange ],
489495 not $ null ctxEdits
490496 = caRemoveCtx ++ [caRemoveAll]
491497 | otherwise = []
0 commit comments