Skip to content

Commit 12587b3

Browse files
committed
Calculate imports in the command handler
This way we don't have to send the imports back and forth on every code action
1 parent b43a8cd commit 12587b3

File tree

1 file changed

+84
-78
lines changed

1 file changed

+84
-78
lines changed

plugins/default/src/Ide/Plugin/Retrie.hs

+84-78
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ import qualified Data.HashMap.Strict as HM
3535
import qualified Data.HashSet as Set
3636
import Data.IORef.Extra (atomicModifyIORef'_, newIORef,
3737
readIORef)
38-
import Data.List.Extra (nubOrdOn)
38+
import Data.List.Extra (find, nubOrdOn)
3939
import Data.String (IsString (fromString))
4040
import qualified Data.Text as T
4141
import qualified Data.Text.IO as T
@@ -86,6 +86,8 @@ import Retrie.SYB (listify)
8686
import Retrie.Util (Verbosity (Loud))
8787
import StringBuffer (stringToStringBuffer)
8888
import System.Directory (makeAbsolute)
89+
import Control.Monad.Trans.Maybe
90+
import Development.IDE.Core.PositionMapping
8991

9092
descriptor :: PluginId -> PluginDescriptor
9193
descriptor plId =
@@ -104,9 +106,7 @@ retrieCommand =
104106
-- | Parameters for the runRetrie PluginCommand.
105107
data RunRetrieParams = RunRetrieParams
106108
{ description :: T.Text,
107-
-- | rewrites for Retrie
108-
rewrites :: [Either ImportSpec RewriteSpec],
109-
-- | Originating file
109+
rewrites :: [RewriteSpec],
110110
originatingFile :: String,
111111
restrictToOriginatingFile :: Bool
112112
}
@@ -117,29 +117,55 @@ runRetrieCmd ::
117117
IdeState ->
118118
RunRetrieParams ->
119119
IO (Either ResponseError Value, Maybe (ServerMethod, ApplyWorkspaceEditParams))
120-
runRetrieCmd lsp state RunRetrieParams {..} =
120+
runRetrieCmd lsp state RunRetrieParams{..} =
121121
withIndefiniteProgress lsp description Cancellable $ do
122-
session <-
123-
runAction "Retrie.GhcSessionDeps" state $
124-
use_ GhcSessionDeps $
125-
toNormalizedFilePath originatingFile
126-
(errors, edits) <-
127-
callRetrie
128-
state
129-
(hscEnv session)
130-
rewrites
131-
(toNormalizedFilePath originatingFile)
132-
restrictToOriginatingFile
133-
unless (null errors) $
134-
sendFunc lsp $
135-
NotShowMessage $
136-
NotificationMessage "2.0" WindowShowMessage $
137-
ShowMessageParams MtWarning $
138-
T.unlines $
139-
"## Found errors during rewrite:" :
140-
["-" <> T.pack (show e) | e <- errors]
122+
res <- runMaybeT $ do
123+
let nfp = toNormalizedFilePath' originatingFile
124+
(session, _) <- MaybeT $
125+
runAction "Retrie.GhcSessionDeps" state $
126+
useWithStale GhcSessionDeps $
127+
toNormalizedFilePath originatingFile
128+
(ms, binds, _, _, _) <- MaybeT $ runAction "Retrie.getBinds" state $ getBinds nfp
129+
let importRewrites = concatMap (extractImports ms binds) rewrites
130+
(errors, edits) <- lift $
131+
callRetrie
132+
state
133+
(hscEnv session)
134+
(map Right rewrites <> map Left importRewrites)
135+
(toNormalizedFilePath originatingFile)
136+
restrictToOriginatingFile
137+
unless (null errors) $
138+
lift $ sendFunc lsp $
139+
NotShowMessage $
140+
NotificationMessage "2.0" WindowShowMessage $
141+
ShowMessageParams MtWarning $
142+
T.unlines $
143+
"## Found errors during rewrite:" :
144+
["-" <> T.pack (show e) | e <- errors]
145+
return (WorkspaceApplyEdit, ApplyWorkspaceEditParams edits)
141146
return
142-
(Right Null, Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams edits))
147+
(Right Null, res)
148+
149+
extractImports :: ModSummary -> [HsBindLR GhcRn GhcRn] -> RewriteSpec -> [ImportSpec]
150+
extractImports ModSummary{ms_mod} topLevelBinds (Unfold thing)
151+
| Just FunBind {fun_matches}
152+
<- find (\case FunBind{fun_id = L _ n} -> prettyPrint n == thing ; _ -> False) topLevelBinds
153+
, names <- listify p fun_matches
154+
=
155+
[ AddImport {..}
156+
| name <- names,
157+
Just ideclNameString <-
158+
[moduleNameString . GHC.moduleName <$> nameModule_maybe name],
159+
let ideclSource = False,
160+
let r = nameRdrName name,
161+
let ideclQualifiedBool = isQual r,
162+
let ideclAsString = moduleNameString . fst <$> isQual_maybe r,
163+
let ideclThing = Just (IEVar $ occNameString $ rdrNameOcc r)
164+
]
165+
where
166+
p name = nameModule_maybe name /= Just ms_mod
167+
-- TODO handle imports for all rewrites
168+
extractImports _ _ _ = []
143169

144170
-------------------------------------------------------------------------------
145171

@@ -149,14 +175,31 @@ provider _a state plId (TextDocumentIdentifier uri) range ca = response $ do
149175
fp <- handleMaybe "uri" $ uriToFilePath' uri
150176
let nfp = toNormalizedFilePath' fp
151177

152-
tm <-
153-
handleMaybeM "no typechecked module" $
154-
useRule "retrie.typecheckModule" state TypeCheck nfp
178+
(ModSummary{ms_mod}, topLevelBinds, posMapping, hs_ruleds, hs_tyclds)
179+
<- handleMaybeM "typecheck" $ runAction "retrie" state $ getBinds nfp
180+
181+
pos <- handleMaybe "pos" $ _start <$> fromCurrentRange posMapping range
182+
let rewrites =
183+
concatMap (suggestBindRewrites fp pos ms_mod) topLevelBinds
184+
++ concatMap (suggestRuleRewrites fp pos ms_mod) hs_ruleds
185+
++ [ r
186+
| TyClGroup {group_tyclds} <- hs_tyclds,
187+
L l g <- group_tyclds,
188+
r <- suggestTypeRewrites fp ms_mod g,
189+
pos `isInsideSrcSpan` l
155190

156-
ModSummary {ms_mod} <-
157-
handleMaybeM "no mod summary" $
158-
useRule "retrie.typecheckModule" state GetModSummary nfp
191+
]
159192

193+
commands <- lift $
194+
forM rewrites $ \(title, kind, params) -> do
195+
c <- mkLspCommand plId (coerce retrieCommandName) title (Just [toJSON params])
196+
return $ CodeAction title (Just kind) Nothing Nothing (Just c)
197+
198+
return $ J.List [CACodeAction c | c <- commands]
199+
200+
getBinds :: NormalizedFilePath -> Action (Maybe (ModSummary, [HsBindLR GhcRn GhcRn], PositionMapping, [LRuleDecls GhcRn], [TyClGroup GhcRn]))
201+
getBinds nfp = runMaybeT $ do
202+
(tm, posMapping) <- MaybeT $ useWithStale TypeCheck nfp
160203
-- we use the typechecked source instead of the parsed source
161204
-- to be able to extract module names from the Ids,
162205
-- so that we can include adding the required imports in the retrie command
@@ -173,60 +216,29 @@ provider _a state plId (TextDocumentIdentifier uri) range ca = response $ do
173216
_
174217
) = rn
175218

176-
pos = _start range
177219
topLevelBinds =
178220
[ decl
179221
| (_, bagBinds) <- binds,
180222
L _ decl <- GHC.bagToList bagBinds
181223
]
182-
183-
rewrites =
184-
concatMap (suggestBindRewrites fp pos ms_mod) topLevelBinds
185-
++ concatMap (suggestRuleRewrites fp pos ms_mod) hs_ruleds
186-
++ [ r
187-
| TyClGroup {group_tyclds} <- hs_tyclds,
188-
L _ g <- group_tyclds,
189-
r <- suggestTypeRewrites fp pos ms_mod g
190-
]
191-
192-
commands <- lift $
193-
forM rewrites $ \(title, kind, params) -> do
194-
c <- mkLspCommand plId (coerce retrieCommandName) title (Just [toJSON params])
195-
return $ CodeAction title (Just kind) Nothing Nothing (Just c)
196-
197-
return $ J.List [CACodeAction c | c <- commands]
224+
return (tmrModSummary tm, topLevelBinds, posMapping, hs_ruleds, hs_tyclds)
198225

199226
suggestBindRewrites ::
200227
String ->
201228
Position ->
202229
GHC.Module ->
203230
HsBindLR GhcRn GhcRn ->
204231
[(T.Text, CodeActionKind, RunRetrieParams)]
205-
suggestBindRewrites originatingFile pos ms_mod (FunBind {fun_id = L l' rdrName, fun_matches})
232+
suggestBindRewrites originatingFile pos ms_mod (FunBind {fun_id = L l' rdrName})
206233
| pos `isInsideSrcSpan` l' =
207234
let pprName = prettyPrint rdrName
208235
pprNameText = T.pack pprName
209-
names = listify p fun_matches
210-
p name = nameModule_maybe name /= Just ms_mod
211-
imports =
212-
[ AddImport {..}
213-
| name <- names,
214-
Just ideclNameString <-
215-
[moduleNameString . GHC.moduleName <$> nameModule_maybe name],
216-
let ideclSource = False,
217-
let r = nameRdrName name,
218-
let ideclQualifiedBool = isQual r,
219-
let ideclAsString = moduleNameString . fst <$> isQual_maybe r,
220-
let ideclThing = Just (IEVar $ occNameString $ rdrNameOcc r)
221-
]
222236
unfoldRewrite restrictToOriginatingFile =
223-
let rewrites =
224-
[Right $ Unfold (qualify ms_mod pprName)]
225-
++ map Left imports
237+
let rewrites = [Unfold (qualify ms_mod pprName)]
226238
description = "Unfold " <> pprNameText <> describeRestriction restrictToOriginatingFile
227239
in (description, CodeActionRefactorInline, RunRetrieParams {..})
228240
foldRewrite restrictToOriginatingFile =
229-
let rewrites = [Right $ Fold (qualify ms_mod pprName)]
241+
let rewrites = [Fold (qualify ms_mod pprName)]
230242
description = "Fold " <> pprNameText <> describeRestriction restrictToOriginatingFile
231243
in (description, CodeActionRefactorExtract, RunRetrieParams {..})
232244
in [unfoldRewrite False, unfoldRewrite True, foldRewrite False, foldRewrite True]
@@ -237,30 +249,26 @@ describeRestriction :: IsString p => Bool -> p
237249
describeRestriction restrictToOriginatingFile =
238250
if restrictToOriginatingFile then " in current file" else ""
239251

240-
-- TODO add imports to the rewrite
241252
suggestTypeRewrites ::
242253
(Outputable (IdP pass)) =>
243254
String ->
244-
Position ->
245255
GHC.Module ->
246256
TyClDecl pass ->
247257
[(T.Text, CodeActionKind, RunRetrieParams)]
248-
suggestTypeRewrites originatingFile pos ms_mod (SynDecl {tcdLName = L l rdrName})
249-
| pos `isInsideSrcSpan` l =
258+
suggestTypeRewrites originatingFile ms_mod (SynDecl {tcdLName = L _ rdrName}) =
250259
let pprName = prettyPrint rdrName
251260
pprNameText = T.pack pprName
252261
unfoldRewrite restrictToOriginatingFile =
253-
let rewrites = [Right $ TypeForward (qualify ms_mod pprName)]
262+
let rewrites = [TypeForward (qualify ms_mod pprName)]
254263
description = "Unfold " <> pprNameText <> describeRestriction restrictToOriginatingFile
255264
in (description, CodeActionRefactorInline, RunRetrieParams {..})
256265
foldRewrite restrictToOriginatingFile =
257-
let rewrites = [Right $ TypeBackward (qualify ms_mod pprName)]
266+
let rewrites = [TypeBackward (qualify ms_mod pprName)]
258267
description = "Fold " <> pprNameText <> describeRestriction restrictToOriginatingFile
259268
in (description, CodeActionRefactorExtract, RunRetrieParams {..})
260269
in [unfoldRewrite False, unfoldRewrite True, foldRewrite False, foldRewrite True]
261-
suggestTypeRewrites _ _ _ _ = []
270+
suggestTypeRewrites _ _ _ = []
262271

263-
-- TODO add imports to the rewrite
264272
suggestRuleRewrites ::
265273
FilePath ->
266274
Position ->
@@ -285,8 +293,7 @@ suggestRuleRewrites originatingFile pos ms_mod (L _ (HsRules {rds_rules})) =
285293
]
286294
where
287295
forwardRewrite ruleName restrictToOriginatingFile =
288-
let rewrites =
289-
[Right $ RuleForward (qualify ms_mod ruleName)]
296+
let rewrites = [RuleForward (qualify ms_mod ruleName)]
290297
description = "Apply rule " <> T.pack ruleName <> " forward" <>
291298
describeRestriction restrictToOriginatingFile
292299

@@ -295,8 +302,7 @@ suggestRuleRewrites originatingFile pos ms_mod (L _ (HsRules {rds_rules})) =
295302
RunRetrieParams {..}
296303
)
297304
backwardsRewrite ruleName restrictToOriginatingFile =
298-
let rewrites =
299-
[Right $ RuleBackward (qualify ms_mod ruleName)]
305+
let rewrites = [RuleBackward (qualify ms_mod ruleName)]
300306
description = "Apply rule " <> T.pack ruleName <> " backwards"
301307
in ( description,
302308
CodeActionRefactor,

0 commit comments

Comments
 (0)