Skip to content

Commit a9b796c

Browse files
berbermanjneiramergify[bot]
authored
Add code action for hiding shadowed identifiers from imports (#1322)
* Add code action for hiding shadowed identifiers from imports * Insert to the line above module decls if there are no existing import decls * Support handling multi imports * Remove trailing comma in processed import lists * Add tests * Make hlint happy * Fix macro * Fix a test suite * Update test * Minor refactor Co-authored-by: Javier Neira <atreyu.bbb@gmail.com> Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent fbb96e8 commit a9b796c

File tree

5 files changed

+294
-13
lines changed

5 files changed

+294
-13
lines changed

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

+91-4
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,13 @@ import OccName
5858
import qualified GHC.LanguageExtensions as Lang
5959
import Control.Lens (alaf)
6060
import 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

6269
descriptor :: PluginId -> PluginDescriptor IdeState
6370
descriptor 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 =
169181
findDeclContainingLoc :: Position -> [Located a] -> Maybe (Located a)
170182
findDeclContainingLoc 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+
172259
suggestDisableWarning :: ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
173260
suggestDisableWarning pm contents Diagnostic{..}
174261
| Just (StringValue (T.stripPrefix "-W" -> Just w)) <- _code =

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

+13-7
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,7 @@ import Development.IDE.GHC.Compat hiding (parseExpr)
3131
import Development.IDE.GHC.ExactPrint
3232
( Annotate, ASTElement(parseAST) )
3333
import FieldLabel (flLabel)
34-
import GhcPlugins (sigPrec)
34+
import GhcPlugins (sigPrec, mkRealSrcLoc)
3535
import Language.Haskell.GHC.ExactPrint
3636
import Language.Haskell.GHC.ExactPrint.Types (DeltaPos (DP), KeywordId (G), mkAnnKey)
3737
import Language.Haskell.LSP.Types
@@ -40,9 +40,9 @@ import Outputable (ppr, showSDocUnsafe, showSDoc)
4040
import Retrie.GHC (rdrNameOcc, unpackFS, mkRealSrcSpan, realSrcSpanEnd)
4141
import Development.IDE.Spans.Common
4242
import Development.IDE.GHC.Error
43-
import Safe (lastMay)
4443
import Data.Generics (listify)
4544
import GHC.Exts (IsList (fromList))
45+
import Control.Monad.Extra (whenJust)
4646

4747
------------------------------------------------------------------------------
4848

@@ -205,6 +205,7 @@ extendImport mparent identifier lDecl@(L l _) =
205205
-- extendImportTopLevel "foo" AST:
206206
--
207207
-- import A --> Error
208+
-- import A (foo) --> Error
208209
-- import A (bar) --> import A (bar, foo)
209210
extendImportTopLevel :: DynFlags -> String -> LImportDecl GhcPs -> TransformT (Either String) (LImportDecl GhcPs)
210211
extendImportTopLevel df idnetifier (L l it@ImportDecl {..})
@@ -382,6 +383,8 @@ deleteFromImport (T.pack -> symbol) (L l idecl) llies@(L lieLoc lies) _ =do
382383
lidecl' = L l $ idecl
383384
{ ideclHiding = Just (False, edited)
384385
}
386+
-- avoid import A (foo,)
387+
whenJust (lastMaybe deletedLies) removeTrailingCommaT
385388
when (not (null lies) && null deletedLies) $ do
386389
transferAnn llies edited id
387390
addSimpleAnnT edited dp00
@@ -408,13 +411,16 @@ deleteFromImport (T.pack -> symbol) (L l idecl) llies@(L lieLoc lies) _ =do
408411
(filter ((/= symbol) . T.pack . unpackFS . flLabel . unLoc) flds)
409412
killLie v = Just v
410413

414+
-- | Insert a import declaration hiding a symbole from Prelude
411415
hideImplicitPreludeSymbol
412416
:: String -> ParsedSource -> Maybe Rewrite
413417
hideImplicitPreludeSymbol symbol (L _ HsModule{..}) = do
414-
existingImp <- lastMay hsmodImports
415-
exisImpSpan <- realSpan $ getLoc existingImp
416-
let indentation = srcSpanStartCol exisImpSpan
417-
beg = realSrcSpanEnd exisImpSpan
418+
let predLine old = mkRealSrcLoc (srcLocFile old) (srcLocLine old - 1) (srcLocCol old)
419+
existingImpSpan = (fmap (id,) . realSpan . getLoc) =<< lastMaybe hsmodImports
420+
existingDeclSpan = (fmap (predLine, ) . realSpan . getLoc) =<< headMaybe hsmodDecls
421+
(f, s) <- existingImpSpan <|> existingDeclSpan
422+
let beg = f $ realSrcSpanEnd s
423+
indentation = srcSpanStartCol s
418424
ran = RealSrcSpan $ mkRealSrcSpan beg beg
419425
pure $ Rewrite ran $ \df -> do
420426
let symOcc = mkVarOcc symbol
@@ -424,6 +430,6 @@ hideImplicitPreludeSymbol symbol (L _ HsModule{..}) = do
424430
-- Re-labeling is needed to reflect annotations correctly
425431
L _ idecl0 <- liftParseAST @(ImportDecl GhcPs) df $ T.unpack impStmt
426432
let idecl = L ran idecl0
427-
addSimpleAnnT idecl (DP (1,indentation - 1))
433+
addSimpleAnnT idecl (DP (1, indentation - 1))
428434
[(G AnnImport, DP (1, indentation - 1))]
429435
pure idecl

ghcide/test/data/hiding/HideFunction.expected.append.E.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module HideFunction where
22

33
import AVec (fromList)
4-
import BVec (fromList,)
4+
import BVec (fromList)
55
import CVec hiding ((++), cons)
66
import DVec hiding ((++), cons, snoc)
77
import EVec as E

ghcide/test/data/hiding/HideFunction.expected.append.Prelude.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module HideFunction where
22

33
import AVec (fromList)
4-
import BVec (fromList,)
4+
import BVec (fromList)
55
import CVec hiding ((++), cons)
66
import DVec hiding ((++), cons, snoc)
77
import EVec as E hiding ((++))

0 commit comments

Comments
 (0)