@@ -35,7 +35,7 @@ import qualified Data.HashMap.Strict as HM
35
35
import qualified Data.HashSet as Set
36
36
import Data.IORef.Extra (atomicModifyIORef'_ , newIORef ,
37
37
readIORef )
38
- import Data.List.Extra (nubOrdOn )
38
+ import Data.List.Extra (find , nubOrdOn )
39
39
import Data.String (IsString (fromString ))
40
40
import qualified Data.Text as T
41
41
import qualified Data.Text.IO as T
@@ -86,6 +86,8 @@ import Retrie.SYB (listify)
86
86
import Retrie.Util (Verbosity (Loud ))
87
87
import StringBuffer (stringToStringBuffer )
88
88
import System.Directory (makeAbsolute )
89
+ import Control.Monad.Trans.Maybe
90
+ import Development.IDE.Core.PositionMapping
89
91
90
92
descriptor :: PluginId -> PluginDescriptor
91
93
descriptor plId =
@@ -104,9 +106,7 @@ retrieCommand =
104
106
-- | Parameters for the runRetrie PluginCommand.
105
107
data RunRetrieParams = RunRetrieParams
106
108
{ description :: T. Text ,
107
- -- | rewrites for Retrie
108
- rewrites :: [Either ImportSpec RewriteSpec ],
109
- -- | Originating file
109
+ rewrites :: [RewriteSpec ],
110
110
originatingFile :: String ,
111
111
restrictToOriginatingFile :: Bool
112
112
}
@@ -117,29 +117,55 @@ runRetrieCmd ::
117
117
IdeState ->
118
118
RunRetrieParams ->
119
119
IO (Either ResponseError Value , Maybe (ServerMethod , ApplyWorkspaceEditParams ))
120
- runRetrieCmd lsp state RunRetrieParams {.. } =
120
+ runRetrieCmd lsp state RunRetrieParams {.. } =
121
121
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)
141
146
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 _ _ _ = []
143
169
144
170
-------------------------------------------------------------------------------
145
171
@@ -149,14 +175,31 @@ provider _a state plId (TextDocumentIdentifier uri) range ca = response $ do
149
175
fp <- handleMaybe " uri" $ uriToFilePath' uri
150
176
let nfp = toNormalizedFilePath' fp
151
177
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
155
190
156
- ModSummary {ms_mod} <-
157
- handleMaybeM " no mod summary" $
158
- useRule " retrie.typecheckModule" state GetModSummary nfp
191
+ ]
159
192
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
160
203
-- we use the typechecked source instead of the parsed source
161
204
-- to be able to extract module names from the Ids,
162
205
-- 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
173
216
_
174
217
) = rn
175
218
176
- pos = _start range
177
219
topLevelBinds =
178
220
[ decl
179
221
| (_, bagBinds) <- binds,
180
222
L _ decl <- GHC. bagToList bagBinds
181
223
]
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)
198
225
199
226
suggestBindRewrites ::
200
227
String ->
201
228
Position ->
202
229
GHC. Module ->
203
230
HsBindLR GhcRn GhcRn ->
204
231
[(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})
206
233
| pos `isInsideSrcSpan` l' =
207
234
let pprName = prettyPrint rdrName
208
235
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
- ]
222
236
unfoldRewrite restrictToOriginatingFile =
223
- let rewrites =
224
- [Right $ Unfold (qualify ms_mod pprName)]
225
- ++ map Left imports
237
+ let rewrites = [Unfold (qualify ms_mod pprName)]
226
238
description = " Unfold " <> pprNameText <> describeRestriction restrictToOriginatingFile
227
239
in (description, CodeActionRefactorInline , RunRetrieParams {.. })
228
240
foldRewrite restrictToOriginatingFile =
229
- let rewrites = [Right $ Fold (qualify ms_mod pprName)]
241
+ let rewrites = [Fold (qualify ms_mod pprName)]
230
242
description = " Fold " <> pprNameText <> describeRestriction restrictToOriginatingFile
231
243
in (description, CodeActionRefactorExtract , RunRetrieParams {.. })
232
244
in [unfoldRewrite False , unfoldRewrite True , foldRewrite False , foldRewrite True ]
@@ -237,30 +249,26 @@ describeRestriction :: IsString p => Bool -> p
237
249
describeRestriction restrictToOriginatingFile =
238
250
if restrictToOriginatingFile then " in current file" else " "
239
251
240
- -- TODO add imports to the rewrite
241
252
suggestTypeRewrites ::
242
253
(Outputable (IdP pass )) =>
243
254
String ->
244
- Position ->
245
255
GHC. Module ->
246
256
TyClDecl pass ->
247
257
[(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}) =
250
259
let pprName = prettyPrint rdrName
251
260
pprNameText = T. pack pprName
252
261
unfoldRewrite restrictToOriginatingFile =
253
- let rewrites = [Right $ TypeForward (qualify ms_mod pprName)]
262
+ let rewrites = [TypeForward (qualify ms_mod pprName)]
254
263
description = " Unfold " <> pprNameText <> describeRestriction restrictToOriginatingFile
255
264
in (description, CodeActionRefactorInline , RunRetrieParams {.. })
256
265
foldRewrite restrictToOriginatingFile =
257
- let rewrites = [Right $ TypeBackward (qualify ms_mod pprName)]
266
+ let rewrites = [TypeBackward (qualify ms_mod pprName)]
258
267
description = " Fold " <> pprNameText <> describeRestriction restrictToOriginatingFile
259
268
in (description, CodeActionRefactorExtract , RunRetrieParams {.. })
260
269
in [unfoldRewrite False , unfoldRewrite True , foldRewrite False , foldRewrite True ]
261
- suggestTypeRewrites _ _ _ _ = []
270
+ suggestTypeRewrites _ _ _ = []
262
271
263
- -- TODO add imports to the rewrite
264
272
suggestRuleRewrites ::
265
273
FilePath ->
266
274
Position ->
@@ -285,8 +293,7 @@ suggestRuleRewrites originatingFile pos ms_mod (L _ (HsRules {rds_rules})) =
285
293
]
286
294
where
287
295
forwardRewrite ruleName restrictToOriginatingFile =
288
- let rewrites =
289
- [Right $ RuleForward (qualify ms_mod ruleName)]
296
+ let rewrites = [RuleForward (qualify ms_mod ruleName)]
290
297
description = " Apply rule " <> T. pack ruleName <> " forward" <>
291
298
describeRestriction restrictToOriginatingFile
292
299
@@ -295,8 +302,7 @@ suggestRuleRewrites originatingFile pos ms_mod (L _ (HsRules {rds_rules})) =
295
302
RunRetrieParams {.. }
296
303
)
297
304
backwardsRewrite ruleName restrictToOriginatingFile =
298
- let rewrites =
299
- [Right $ RuleBackward (qualify ms_mod ruleName)]
305
+ let rewrites = [RuleBackward (qualify ms_mod ruleName)]
300
306
description = " Apply rule " <> T. pack ruleName <> " backwards"
301
307
in ( description,
302
308
CodeActionRefactor ,
0 commit comments