Skip to content

Commit 4091538

Browse files
authored
[explicit-imports] Take in a predicate to filter modules (#1888)
1 parent 6409ce8 commit 4091538

File tree

1 file changed

+20
-11
lines changed

1 file changed

+20
-11
lines changed

plugins/hls-explicit-imports-plugin/src/Ide/Plugin/ExplicitImports.hs

Lines changed: 20 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@
1010

1111
module Ide.Plugin.ExplicitImports
1212
( descriptor
13+
, descriptorForModules
1314
, extractMinimalImports
1415
, within
1516
) where
@@ -45,7 +46,14 @@ importCommandId = "ImportLensCommand"
4546

4647
-- | The "main" function of a plugin
4748
descriptor :: PluginId -> PluginDescriptor IdeState
48-
descriptor plId =
49+
descriptor = descriptorForModules (/= moduleName pRELUDE)
50+
51+
descriptorForModules
52+
:: (ModuleName -> Bool)
53+
-- ^ Predicate to select modules that will be annotated
54+
-> PluginId
55+
-> PluginDescriptor IdeState
56+
descriptorForModules pred plId =
4957
(defaultPluginDescriptor plId)
5058
{
5159
-- This plugin provides a command handler
@@ -54,9 +62,9 @@ descriptor plId =
5462
pluginRules = minimalImportsRule,
5563
pluginHandlers = mconcat
5664
[ -- This plugin provides code lenses
57-
mkPluginHandler STextDocumentCodeLens lensProvider
65+
mkPluginHandler STextDocumentCodeLens $ lensProvider pred
5866
-- This plugin provides code actions
59-
, mkPluginHandler STextDocumentCodeAction codeActionProvider
67+
, mkPluginHandler STextDocumentCodeAction $ codeActionProvider pred
6068
]
6169
}
6270

@@ -87,8 +95,9 @@ runImportCommand _state (ImportCommandParams edit) = do
8795
-- the provider should produce one code lens associated to the import statement:
8896
--
8997
-- > import Data.List (intercalate, sortBy)
90-
lensProvider :: PluginMethodHandler IdeState TextDocumentCodeLens
98+
lensProvider :: (ModuleName -> Bool) -> PluginMethodHandler IdeState TextDocumentCodeLens
9199
lensProvider
100+
pred
92101
state -- ghcide state, used to retrieve typechecking artifacts
93102
pId -- plugin Id
94103
CodeLensParams {_textDocument = TextDocumentIdentifier {_uri}}
@@ -105,7 +114,7 @@ lensProvider
105114
sequence
106115
[ generateLens pId _uri edit
107116
| (imp, Just minImport) <- minImports,
108-
Just edit <- [mkExplicitEdit posMapping imp minImport]
117+
Just edit <- [mkExplicitEdit pred posMapping imp minImport]
109118
]
110119
return $ Right (List $ catMaybes commands)
111120
_ ->
@@ -115,8 +124,8 @@ lensProvider
115124

116125
-- | If there are any implicit imports, provide one code action to turn them all
117126
-- into explicit imports.
118-
codeActionProvider :: PluginMethodHandler IdeState TextDocumentCodeAction
119-
codeActionProvider ideState _pId (CodeActionParams _ _ docId range _context)
127+
codeActionProvider :: (ModuleName -> Bool) -> PluginMethodHandler IdeState TextDocumentCodeAction
128+
codeActionProvider pred ideState _pId (CodeActionParams _ _ docId range _context)
120129
| TextDocumentIdentifier {_uri} <- docId,
121130
Just nfp <- uriToNormalizedFilePath $ toNormalizedUri _uri = liftIO $
122131
do
@@ -135,7 +144,7 @@ codeActionProvider ideState _pId (CodeActionParams _ _ docId range _context)
135144
[ e
136145
| (imp, Just explicit) <-
137146
maybe [] getMinimalImportsResult minImports,
138-
Just e <- [mkExplicitEdit zeroMapping imp explicit]
147+
Just e <- [mkExplicitEdit pred zeroMapping imp explicit]
139148
]
140149
caExplicitImports = InR CodeAction {..}
141150
_title = "Make all imports explicit"
@@ -219,16 +228,16 @@ extractMinimalImports (Just hsc) (Just TcModuleResult {..}) = do
219228
return (imports, minimalImports)
220229
extractMinimalImports _ _ = return ([], Nothing)
221230

222-
mkExplicitEdit :: PositionMapping -> LImportDecl pass -> T.Text -> Maybe TextEdit
223-
mkExplicitEdit posMapping (L src imp) explicit
231+
mkExplicitEdit :: (ModuleName -> Bool) -> PositionMapping -> LImportDecl pass -> T.Text -> Maybe TextEdit
232+
mkExplicitEdit pred posMapping (L src imp) explicit
224233
-- Explicit import list case
225234
| ImportDecl {ideclHiding = Just (False, _)} <- imp =
226235
Nothing
227236
| not (isQualifiedImport imp),
228237
RealSrcSpan l <- src,
229238
L _ mn <- ideclName imp,
230239
-- (almost) no one wants to see an explicit import list for Prelude
231-
mn /= moduleName pRELUDE,
240+
pred mn,
232241
Just rng <- toCurrentRange posMapping $ realSrcSpanToRange l =
233242
Just $ TextEdit rng explicit
234243
| otherwise =

0 commit comments

Comments
 (0)