@@ -58,6 +58,13 @@ import OccName
5858import qualified GHC.LanguageExtensions as Lang
5959import Control.Lens (alaf )
6060import Data.Monoid (Ap (.. ))
61+ import TcRnTypes (TcGblEnv (.. ), ImportAvails (.. ))
62+ import HscTypes (ImportedModsVal (.. ), importedByUser )
63+ import RdrName (GlobalRdrElt (.. ), lookupGlobalRdrEnv )
64+ import SrcLoc (realSrcSpanStart )
65+ import Module (moduleEnvElts )
66+ import qualified Data.Map as M
67+ import qualified Data.Set as S
6168
6269descriptor :: PluginId -> PluginDescriptor IdeState
6370descriptor plId =
@@ -80,11 +87,13 @@ codeAction lsp state _ (TextDocumentIdentifier uri) _range CodeActionContext{_di
8087 let text = Rope. toText . (_text :: VirtualFile -> Rope. Rope ) <$> contents
8188 mbFile = toNormalizedFilePath' <$> uriToFilePath uri
8289 diag <- fmap (\ (_, _, d) -> d) . filter (\ (p, _, _) -> mbFile == Just p) <$> getDiagnostics state
83- (ideOptions, join -> parsedModule, join -> env, join -> annotatedPS) <- runAction " CodeAction" state $
84- (,,,) <$> getIdeOptions
90+ (ideOptions, join -> parsedModule, join -> env, join -> annotatedPS, join -> tcM, join -> har ) <- runAction " CodeAction" state $
91+ (,,,,, ) <$> getIdeOptions
8592 <*> getParsedModule `traverse` mbFile
8693 <*> use GhcSession `traverse` mbFile
8794 <*> use GetAnnotatedParsedSource `traverse` mbFile
95+ <*> use TypeCheck `traverse` mbFile
96+ <*> use GetHieAst `traverse` mbFile
8897 -- This is quite expensive 0.6-0.7s on GHC
8998 pkgExports <- maybe mempty envPackageExports env
9099 localExports <- readVar (exportsMap $ shakeExtras state)
@@ -93,7 +102,7 @@ codeAction lsp state _ (TextDocumentIdentifier uri) _range CodeActionContext{_di
93102 df = ms_hspp_opts . pm_mod_summary <$> parsedModule
94103 actions =
95104 [ mkCA title [x] edit
96- | x <- xs, (title, tedit) <- suggestAction exportsMap ideOptions parsedModule text df annotatedPS x
105+ | x <- xs, (title, tedit) <- suggestAction exportsMap ideOptions parsedModule text df annotatedPS tcM har x
97106 , let edit = WorkspaceEdit (Just $ Map. singleton uri $ List tedit) Nothing
98107 ]
99108 actions' = caRemoveRedundantImports parsedModule text diag xs uri
@@ -123,9 +132,11 @@ suggestAction
123132 -> Maybe T. Text
124133 -> Maybe DynFlags
125134 -> Maybe (Annotated ParsedSource )
135+ -> Maybe TcModuleResult
136+ -> Maybe HieAstResult
126137 -> Diagnostic
127138 -> [(T. Text , [TextEdit ])]
128- suggestAction packageExports ideOptions parsedModule text df annSource diag =
139+ suggestAction packageExports ideOptions parsedModule text df annSource tcM har diag =
129140 concat
130141 -- Order these suggestions by priority
131142 [ suggestSignature True diag
@@ -140,6 +151,7 @@ suggestAction packageExports ideOptions parsedModule text df annSource diag =
140151 , suggestAddTypeAnnotationToSatisfyContraints text diag
141152 , rewrite df annSource $ \ df ps -> suggestConstraint df ps diag
142153 , rewrite df annSource $ \ _ ps -> suggestImplicitParameter ps diag
154+ , rewrite df annSource $ \ _ ps -> suggestHideShadow ps tcM har diag
143155 ] ++ concat
144156 [ suggestNewDefinition ideOptions pm text diag
145157 ++ suggestNewImport packageExports pm diag
@@ -169,6 +181,81 @@ findInstanceHead df instanceHead decls =
169181findDeclContainingLoc :: Position -> [Located a ] -> Maybe (Located a )
170182findDeclContainingLoc loc = find (\ (L l _) -> loc `isInsideSrcSpan` l)
171183
184+ -- Single:
185+ -- This binding for ‘mod’ shadows the existing binding
186+ -- imported from ‘Prelude’ at haskell-language-server/ghcide/src/Development/IDE/Plugin/CodeAction.hs:10:8-40
187+ -- (and originally defined in ‘GHC.Real’)typecheck(-Wname-shadowing)
188+ -- Multi:
189+ -- This binding for ‘pack’ shadows the existing bindings
190+ -- imported from ‘Data.ByteString’ at B.hs:6:1-22
191+ -- imported from ‘Data.ByteString.Lazy’ at B.hs:8:1-27
192+ -- imported from ‘Data.Text’ at B.hs:7:1-16
193+ suggestHideShadow :: ParsedSource -> Maybe TcModuleResult -> Maybe HieAstResult -> Diagnostic -> [(T. Text , [Rewrite ])]
194+ suggestHideShadow pm@ (L _ HsModule {hsmodImports}) mTcM mHar Diagnostic {_message, _range}
195+ | Just [identifier, modName, s] <-
196+ matchRegexUnifySpaces
197+ _message
198+ " This binding for ‘([^`]+)’ shadows the existing binding imported from ‘([^`]+)’ at ([^ ]*)" =
199+ suggests identifier modName s
200+ | Just [identifier] <-
201+ matchRegexUnifySpaces
202+ _message
203+ " This binding for ‘([^`]+)’ shadows the existing bindings" ,
204+ Just matched <- allMatchRegexUnifySpaces _message " imported from ‘([^’]+)’ at ([^ ]*)" ,
205+ mods <- [(modName, s) | [_, modName, s] <- matched],
206+ result <- nubOrdBy (compare `on` fst ) $ mods >>= uncurry (suggests identifier),
207+ hideAll <- (" Hide " <> identifier <> " from all occurence imports" , concat $ snd <$> result) =
208+ result <> [hideAll]
209+ | otherwise = []
210+ where
211+ suggests identifier modName s
212+ | Just tcM <- mTcM,
213+ Just har <- mHar,
214+ [s'] <- [x | (x, " " ) <- readSrcSpan $ T. unpack s],
215+ isUnusedImportedId tcM har (T. unpack identifier) (T. unpack modName) (RealSrcSpan s'),
216+ mDecl <- findImportDeclByModuleName hsmodImports $ T. unpack modName,
217+ title <- " Hide " <> identifier <> " from " <> modName =
218+ if modName == " Prelude" && null mDecl
219+ then [(title, maybeToList $ hideImplicitPreludeSymbol (T. unpack identifier) pm)]
220+ else maybeToList $ (title,) . pure . hideSymbol (T. unpack identifier) <$> mDecl
221+ | otherwise = []
222+
223+ findImportDeclByModuleName :: [LImportDecl GhcPs ] -> String -> Maybe (LImportDecl GhcPs )
224+ findImportDeclByModuleName decls modName = flip find decls $ \ case
225+ (L _ ImportDecl {.. }) -> modName == moduleNameString (unLoc ideclName)
226+ _ -> error " impossible"
227+
228+ isTheSameLine :: SrcSpan -> SrcSpan -> Bool
229+ isTheSameLine s1 s2
230+ | Just sl1 <- getStartLine s1,
231+ Just sl2 <- getStartLine s2 =
232+ sl1 == sl2
233+ | otherwise = False
234+ where
235+ getStartLine x = srcLocLine . realSrcSpanStart <$> realSpan x
236+
237+ isUnusedImportedId :: TcModuleResult -> HieAstResult -> String -> String -> SrcSpan -> Bool
238+ isUnusedImportedId
239+ TcModuleResult {tmrTypechecked = TcGblEnv {tcg_imports = ImportAvails {imp_mods}}}
240+ HAR {refMap}
241+ identifier
242+ modName
243+ importSpan
244+ | occ <- mkVarOcc identifier,
245+ impModsVals <- importedByUser . concat $ moduleEnvElts imp_mods,
246+ Just rdrEnv <-
247+ listToMaybe
248+ [ imv_all_exports
249+ | ImportedModsVal {.. } <- impModsVals,
250+ imv_name == mkModuleName modName,
251+ isTheSameLine imv_span importSpan
252+ ],
253+ [GRE {.. }] <- lookupGlobalRdrEnv rdrEnv occ,
254+ importedIdentifier <- Right gre_name,
255+ refs <- M. lookup importedIdentifier refMap =
256+ maybe True (not . any (\ (_, IdentifierDetails {.. }) -> identInfo == S. singleton Use )) refs
257+ | otherwise = False
258+
172259suggestDisableWarning :: ParsedModule -> Maybe T. Text -> Diagnostic -> [(T. Text , [TextEdit ])]
173260suggestDisableWarning pm contents Diagnostic {.. }
174261 | Just (StringValue (T. stripPrefix " -W" -> Just w)) <- _code =
0 commit comments