Skip to content

Commit 66fbce7

Browse files
committed
Use structured diagnostics for redundant imports
1 parent be30f3e commit 66fbce7

File tree

1 file changed

+32
-31
lines changed
  • plugins/hls-refactor-plugin/src/Development/IDE/Plugin

1 file changed

+32
-31
lines changed

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

Lines changed: 32 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -22,14 +22,15 @@ import Control.Arrow (second,
2222
(&&&),
2323
(>>>))
2424
import Control.Concurrent.STM.Stats (atomically)
25+
import Control.Lens hiding (List,
26+
uncons, use)
2527
import Control.Monad.Extra
2628
import Control.Monad.IO.Class
2729
import Control.Monad.Trans.Except (ExceptT (ExceptT))
2830
import Control.Monad.Trans.Maybe
2931
import Data.Char
3032
import qualified Data.DList as DL
3133
import Data.Function
32-
import Data.Functor
3334
import qualified Data.HashMap.Strict as Map
3435
import qualified Data.HashSet as Set
3536
import Data.List.Extra
@@ -49,6 +50,9 @@ import Development.IDE.Core.Service
4950
import Development.IDE.Core.Shake hiding (Log)
5051
import Development.IDE.GHC.Compat hiding
5152
(ImplicitPrelude)
53+
import Development.IDE.GHC.Compat.Error (TcRnMessage (..),
54+
_TcRnMessage,
55+
msgEnvelopeErrorL)
5256
#if !MIN_VERSION_ghc(9,11,0)
5357
import Development.IDE.GHC.Compat.Util
5458
#endif
@@ -78,6 +82,8 @@ import GHC (DeltaPos (..
7882
import GHC.Iface.Ext.Types (ContextInfo (..),
7983
IdentifierDetails (..))
8084
import qualified GHC.LanguageExtensions as Lang
85+
import GHC.Tc.Errors.Types (UnusedImportName (..),
86+
UnusedImportReason (..))
8187
import Ide.Logger hiding
8288
(group)
8389
import Ide.PluginUtils (extendToFullLines,
@@ -138,12 +144,12 @@ codeAction state _ (CodeActionParams _ _ (TextDocumentIdentifier uri) range _) =
138144
contents <- liftIO $ runAction "hls-refactor-plugin.codeAction.getUriContents" state $ getUriContents $ toNormalizedUri uri
139145
liftIO $ do
140146
let mbFile = toNormalizedFilePath' <$> uriToFilePath uri
141-
allDiags <- atomically $ fmap fdLspDiagnostic . filter (\d -> mbFile == Just (fdFilePath d)) <$> getDiagnostics state
147+
allDiags <- atomically $ filter (\d -> mbFile == Just (fdFilePath d)) <$> getDiagnostics state
142148
(join -> parsedModule) <- runAction "GhcideCodeActions.getParsedModule" state $ getParsedModule `traverse` mbFile
143149
let
144150
textContents = fmap Rope.toText contents
145151
actions = caRemoveRedundantImports parsedModule textContents allDiags range uri
146-
<> caRemoveInvalidExports parsedModule textContents allDiags range uri
152+
<> caRemoveInvalidExports parsedModule textContents (fdLspDiagnostic <$> allDiags) range uri
147153
pure $ InL actions
148154

149155
-------------------------------------------------------------------------------------------------
@@ -447,33 +453,28 @@ isUnusedImportedId
447453
maybe True (not . any (\(_, IdentifierDetails {..}) -> identInfo == S.singleton Use)) refs
448454
| otherwise = False
449455

450-
suggestRemoveRedundantImport :: ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
451-
suggestRemoveRedundantImport ParsedModule{pm_parsed_source = L _ HsModule{hsmodImports}} contents Diagnostic{_range=_range,..}
452-
-- The qualified import of ‘many’ from module ‘Control.Applicative’ is redundant
453-
| Just [_, bindings] <- matchRegexUnifySpaces _message "The( qualified)? import of ‘([^’]*)’ from module [^ ]* is redundant"
454-
, Just (L _ impDecl) <- find (\(L (locA -> l) _) -> _start _range `isInsideSrcSpan` l && _end _range `isInsideSrcSpan` l ) hsmodImports
455-
, Just c <- contents
456-
, ranges <- map (rangesForBindingImport impDecl . T.unpack) (T.splitOn ", " bindings >>= trySplitIntoOriginalAndRecordField)
456+
suggestRemoveRedundantImport :: ParsedModule -> Maybe T.Text -> FileDiagnostic -> [(T.Text, [TextEdit])]
457+
suggestRemoveRedundantImport _ contents
458+
FileDiagnostic{fdStructuredMessage,fdLspDiagnostic=Diagnostic{_range=_range}}
459+
| Just (TcRnUnusedImport impDecl (UnusedImportSome names)) <- fdStructuredMessage ^? _SomeStructuredMessage. msgEnvelopeErrorL . _TcRnMessage
460+
, Just c <- contents
461+
, let bindings = names >>= bindingsInImp
462+
, ranges <- map (rangesForBindingImport impDecl . T.unpack) bindings
457463
, ranges' <- extendAllToIncludeCommaIfPossible False (indexedByPosition $ T.unpack c) (concat ranges)
458464
, not (null ranges')
459-
= [( "Remove " <> bindings <> " from import" , [ TextEdit r "" | r <- ranges' ] )]
460-
461-
-- File.hs:16:1: warning:
462-
-- The import of `Data.List' is redundant
463-
-- except perhaps to import instances from `Data.List'
464-
-- To import instances alone, use: import Data.List()
465-
| _message =~ ("The( qualified)? import of [^ ]* is redundant" :: String)
466-
= [("Remove import", [TextEdit (extendToWholeLineIfPossible contents _range) ""])]
465+
= [( "Remove " <> T.intercalate ", " (pprBinding <$> names) <> " from import" , [ TextEdit r "" | r <- ranges' ] )]
466+
| Just (TcRnUnusedImport _ UnusedImportNone) <- fdStructuredMessage ^? _SomeStructuredMessage. msgEnvelopeErrorL . _TcRnMessage =
467+
[("Remove import", [TextEdit (extendToWholeLineIfPossible contents _range) ""])]
467468
| otherwise = []
468469
where
469-
-- In case of an unused record field import, the binding from the message will not match any import directly
470-
-- In this case, we try if we can additionally extract a record field name
471-
-- Example: The import of ‘B(b2)’ from module ‘ModuleB’ is redundant
472-
trySplitIntoOriginalAndRecordField :: T.Text -> [T.Text]
473-
trySplitIntoOriginalAndRecordField binding =
474-
case matchRegexUnifySpaces binding "([^ ]+)\\(([^)]+)\\)" of
475-
Just [_, fields] -> [binding, fields]
476-
_ -> [binding]
470+
bindingsInImp ::UnusedImportName -> [T.Text]
471+
bindingsInImp (UnusedImportNameRecField NoParent name) = [printOutputable name]
472+
bindingsInImp b@(UnusedImportNameRecField (ParentIs _) field) = [pprBinding b,printOutputable field]
473+
bindingsInImp (UnusedImportNameRegular name) = [printOutputable name]
474+
pprBinding ::UnusedImportName -> T.Text
475+
pprBinding (UnusedImportNameRecField NoParent name) = printOutputable $ occName name
476+
pprBinding (UnusedImportNameRecField (ParentIs parent) field) = printOutputable parent <> "("<> printOutputable field <> ")"
477+
pprBinding (UnusedImportNameRegular name) = printOutputable name
477478

478479
diagInRange :: Diagnostic -> Range -> Bool
479480
diagInRange Diagnostic {_range = dr} r = dr `subRange` extendedRange
@@ -488,19 +489,19 @@ diagInRange Diagnostic {_range = dr} r = dr `subRange` extendedRange
488489
-- is likely to be removed and less likely the warning will be disabled.
489490
-- Therefore actions to remove a single or all redundant imports should be
490491
-- preferred, so that the client can prioritize them higher.
491-
caRemoveRedundantImports :: Maybe ParsedModule -> Maybe T.Text -> [Diagnostic] -> Range -> Uri -> [Command |? CodeAction]
492+
caRemoveRedundantImports :: Maybe ParsedModule -> Maybe T.Text -> [FileDiagnostic] -> Range -> Uri -> [Command |? CodeAction]
492493
caRemoveRedundantImports m contents allDiags contextRange uri
493494
| Just pm <- m,
494495
r <- join $ map (\d -> repeat d `zip` suggestRemoveRedundantImport pm contents d) allDiags,
495496
allEdits <- [ e | (_, (_, edits)) <- r, e <- edits],
496497
caRemoveAll <- removeAll allEdits,
497-
ctxEdits <- [ x | x@(d, _) <- r, d `diagInRange` contextRange],
498+
ctxEdits <- [ x | x@(d, _) <- r, fdLspDiagnostic d `diagInRange` contextRange],
498499
not $ null ctxEdits,
499500
caRemoveCtx <- map (\(d, (title, tedit)) -> removeSingle title tedit d) ctxEdits
500501
= caRemoveCtx ++ [caRemoveAll]
501502
| otherwise = []
502503
where
503-
removeSingle title tedit diagnostic = mkCA title (Just CodeActionKind_QuickFix) Nothing [diagnostic] WorkspaceEdit{..} where
504+
removeSingle title tedit diagnostic = mkCA title (Just CodeActionKind_QuickFix) Nothing [fdLspDiagnostic diagnostic] WorkspaceEdit{..} where
504505
_changes = Just $ M.singleton uri tedit
505506
_documentChanges = Nothing
506507
_changeAnnotations = Nothing
@@ -1946,7 +1947,7 @@ textInRange (Range (Position (fromIntegral -> startRow) (fromIntegral -> startCo
19461947
linesBeginningWithStartLine = drop startRow (T.splitOn "\n" text)
19471948

19481949
-- | Returns the ranges for a binding in an import declaration
1949-
rangesForBindingImport :: ImportDecl GhcPs -> String -> [Range]
1950+
rangesForBindingImport :: ImportDecl GhcRn -> String -> [Range]
19501951
rangesForBindingImport ImportDecl{
19511952
ideclImportList = Just (Exactly, L _ lies)
19521953
} b =
@@ -1988,7 +1989,7 @@ smallerRangesForBindingExport lies b =
19881989
[ locA l' | L l' x <- inners, T.unpack (printOutputable x) == b']
19891990
ranges' _ = []
19901991

1991-
rangesForBinding' :: String -> LIE GhcPs -> [SrcSpan]
1992+
rangesForBinding' :: String -> LIE GhcRn -> [SrcSpan]
19921993
#if MIN_VERSION_ghc(9,9,0)
19931994
rangesForBinding' b (L (locA -> l) (IEVar _ nm _))
19941995
#else

0 commit comments

Comments
 (0)