Skip to content

Commit fb60821

Browse files
committed
Use *only* incoming range to determine which code actions are in scope
Rather than doing a full compare with incoming `Diagnostic` objects from the client. This brings the "remove redundant imports/exports" code actions more in line with behavior described in haskell#4056, and has the pleasant side-effect of fixing broken code actions in neovim (haskell#3857).
1 parent 0b0eee3 commit fb60821

File tree

1 file changed

+19
-12
lines changed
  • plugins/hls-refactor-plugin/src/Development/IDE/Plugin

1 file changed

+19
-12
lines changed

plugins/hls-refactor-plugin/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 19 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,8 @@ import GHC.Exts (fromList)
8080
import qualified GHC.LanguageExtensions as Lang
8181
import Ide.Logger hiding
8282
(group)
83-
import Ide.PluginUtils (extractTextInRange,
83+
import Ide.PluginUtils (extendToFullLines,
84+
extractTextInRange,
8485
subRange)
8586
import Ide.Types
8687
import Language.LSP.Protocol.Message (Method (..),
@@ -112,16 +113,16 @@ import Text.Regex.TDFA ((=~), (=~~))
112113

113114
-- | Generate code actions.
114115
codeAction :: PluginMethodHandler IdeState 'Method_TextDocumentCodeAction
115-
codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) _range CodeActionContext{_diagnostics= xs}) = do
116+
codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) range _) = do
116117
contents <- lift $ LSP.getVirtualFile $ toNormalizedUri uri
117118
liftIO $ do
118119
let text = virtualFileText <$> contents
119120
mbFile = toNormalizedFilePath' <$> uriToFilePath uri
120-
diag <- atomically $ fmap (\(_, _, d) -> d) . filter (\(p, _, _) -> mbFile == Just p) <$> getDiagnostics state
121+
allDiags <- atomically $ fmap (\(_, _, d) -> d) . filter (\(p, _, _) -> mbFile == Just p) <$> getDiagnostics state
121122
(join -> parsedModule) <- runAction "GhcideCodeActions.getParsedModule" state $ getParsedModule `traverse` mbFile
122123
let
123-
actions = caRemoveRedundantImports parsedModule text diag xs uri
124-
<> caRemoveInvalidExports parsedModule text diag xs uri
124+
actions = caRemoveRedundantImports parsedModule text allDiags range uri
125+
<> caRemoveInvalidExports parsedModule text allDiags range uri
125126
pure $ InL $ actions
126127

127128
-------------------------------------------------------------------------------------------------
@@ -441,19 +442,25 @@ suggestRemoveRedundantImport ParsedModule{pm_parsed_source = L _ HsModule{hsmod
441442
= [("Remove import", [TextEdit (extendToWholeLineIfPossible contents _range) ""])]
442443
| otherwise = []
443444

445+
diagInRange :: Diagnostic -> Range -> Bool
446+
diagInRange Diagnostic {_range = dr} r = dr `subRange` extendedRange
447+
where
448+
-- Ensures the range captures full lines. Makes it easier to trigger the correct
449+
-- "remove redundant" code actions from anywhere on the offending line.
450+
extendedRange = extendToFullLines r
444451

445452
-- Note [Removing imports is preferred]
446453
-- It's good to prefer the remove imports code action because an unused import
447454
-- is likely to be removed and less likely the warning will be disabled.
448455
-- Therefore actions to remove a single or all redundant imports should be
449456
-- preferred, so that the client can prioritize them higher.
450-
caRemoveRedundantImports :: Maybe ParsedModule -> Maybe T.Text -> [Diagnostic] -> [Diagnostic] -> Uri -> [Command |? CodeAction]
451-
caRemoveRedundantImports m contents digs ctxDigs uri
457+
caRemoveRedundantImports :: Maybe ParsedModule -> Maybe T.Text -> [Diagnostic] -> Range -> Uri -> [Command |? CodeAction]
458+
caRemoveRedundantImports m contents allDiags contextRange uri
452459
| Just pm <- m,
453-
r <- join $ map (\d -> repeat d `zip` suggestRemoveRedundantImport pm contents d) digs,
460+
r <- join $ map (\d -> repeat d `zip` suggestRemoveRedundantImport pm contents d) allDiags,
454461
allEdits <- [ e | (_, (_, edits)) <- r, e <- edits],
455462
caRemoveAll <- removeAll allEdits,
456-
ctxEdits <- [ x | x@(d, _) <- r, d `elem` ctxDigs],
463+
ctxEdits <- [ x | x@(d, _) <- r, d `diagInRange` contextRange],
457464
not $ null ctxEdits,
458465
caRemoveCtx <- map (\(d, (title, tedit)) -> removeSingle title tedit d) ctxEdits
459466
= caRemoveCtx ++ [caRemoveAll]
@@ -477,8 +484,8 @@ caRemoveRedundantImports m contents digs ctxDigs uri
477484
_data_ = Nothing
478485
_changeAnnotations = Nothing
479486

480-
caRemoveInvalidExports :: Maybe ParsedModule -> Maybe T.Text -> [Diagnostic] -> [Diagnostic] -> Uri -> [Command |? CodeAction]
481-
caRemoveInvalidExports m contents digs ctxDigs uri
487+
caRemoveInvalidExports :: Maybe ParsedModule -> Maybe T.Text -> [Diagnostic] -> Range -> Uri -> [Command |? CodeAction]
488+
caRemoveInvalidExports m contents digs contextRange uri
482489
| Just pm <- m,
483490
Just txt <- contents,
484491
txt' <- indexedByPosition $ T.unpack txt,
@@ -488,7 +495,7 @@ caRemoveInvalidExports m contents digs ctxDigs uri
488495
allRanges <- nubOrd $ [ range | (_,_,ranges) <- r, range <- ranges],
489496
allRanges' <- extend txt' allRanges,
490497
Just caRemoveAll <- removeAll allRanges',
491-
ctxEdits <- [ x | x@(_, d, _) <- r, d `elem` ctxDigs],
498+
ctxEdits <- [ x | x@(_, d, _) <- r, d `diagInRange` contextRange],
492499
not $ null ctxEdits
493500
= caRemoveCtx ++ [caRemoveAll]
494501
| otherwise = []

0 commit comments

Comments
 (0)