@@ -15,7 +15,7 @@ module Ide.Plugin.Hlint
15
15
descriptor
16
16
-- , provider
17
17
) where
18
-
18
+ import Refact.Apply
19
19
import Control.DeepSeq
20
20
import Control.Exception
21
21
import Control.Lens ((^.) )
@@ -79,11 +79,11 @@ import Text.Regex.TDFA.Text()
79
79
descriptor :: PluginId -> PluginDescriptor
80
80
descriptor plId = (defaultPluginDescriptor plId)
81
81
{ pluginRules = rules
82
- -- , pluginCommands =
83
- -- [ PluginCommand "applyOne" "Apply a single hint" applyOneCmd
82
+ , pluginCommands =
83
+ [ PluginCommand " applyOne" " Apply a single hint" applyOneCmd
84
84
-- , PluginCommand "applyAll" "Apply all hints to the file" applyAllCmd
85
- -- ]
86
- -- , pluginCodeActionProvider = Just codeActionProvider
85
+ ]
86
+ , pluginCodeActionProvider = Just codeActionProvider
87
87
}
88
88
89
89
data GetHlintDiagnostics = GetHlintDiagnostics
@@ -115,7 +115,7 @@ rules = do
115
115
getModuleEx :: NormalizedFilePath -> Action (Either ParseError ModuleEx )
116
116
getModuleEx fp = do
117
117
#ifndef GHC_LIB
118
- pm <- use_ GetParsedModule fp
118
+ pm <- getParsedModule fp
119
119
let anns = pm_annotations pm
120
120
let modu = pm_parsed_source pm
121
121
return $ Right (createModuleEx anns modu)
@@ -214,6 +214,92 @@ hlintSettings hlintDataDir enableOverrides = do
214
214
215
215
-- ---------------------------------------------------------------------
216
216
217
+ codeActionProvider :: CodeActionProvider
218
+ codeActionProvider _ _ plId docId _ context = (Right . LSP. List . map CACodeAction ) <$> hlintActions
219
+ where
220
+
221
+ hlintActions :: IO [LSP. CodeAction ]
222
+ hlintActions = catMaybes <$> mapM mkHlintAction (filter validCommand diags)
223
+
224
+ -- | Some hints do not have an associated refactoring
225
+ validCommand (LSP. Diagnostic _ _ (Just (LSP. StringValue code)) (Just " hlint" ) _ _ _) =
226
+ case code of
227
+ " Eta reduce" -> False
228
+ _ -> True
229
+ validCommand _ = False
230
+
231
+ LSP. List diags = context ^. LSP. diagnostics
232
+
233
+ mkHlintAction :: LSP. Diagnostic -> IO (Maybe LSP. CodeAction )
234
+ mkHlintAction diag@ (LSP. Diagnostic (LSP. Range start _) _s (Just (LSP. StringValue code)) (Just " hlint" ) m _ _) =
235
+ Just . codeAction <$> mkLspCommand plId " applyOne" title (Just args)
236
+ where
237
+ codeAction cmd = LSP. CodeAction title (Just LSP. CodeActionQuickFix ) (Just (LSP. List [diag])) Nothing (Just cmd)
238
+ title = " Apply hint:" <> head (T. lines m)
239
+ -- need 'file', 'start_pos' and hint title (to distinguish between alternative suggestions at the same location)
240
+ args = [toJSON (AOP (docId ^. LSP. uri) start code)]
241
+ mkHlintAction (LSP. Diagnostic _r _s _c _source _m _ _) = return Nothing
242
+
243
+ -- ---------------------------------------------------------------------
244
+
245
+ data ApplyOneParams = AOP
246
+ { file :: Uri
247
+ , start_pos :: Position
248
+ -- | There can be more than one hint suggested at the same position, so HintTitle is used to distinguish between them.
249
+ , hintTitle :: HintTitle
250
+ } deriving (Eq ,Show ,Generic ,FromJSON ,ToJSON )
251
+
252
+ type HintTitle = T. Text
253
+
254
+ data OneHint = OneHint
255
+ { oneHintPos :: Position
256
+ , oneHintTitle :: HintTitle
257
+ } deriving (Eq , Show )
258
+
259
+ applyOneCmd :: CommandFunction ApplyOneParams
260
+ applyOneCmd _lf ide (AOP uri pos title) = do
261
+ let oneHint = OneHint pos title
262
+ let file = uriToFilePath' uri
263
+ applyHint file (Just oneHint)
264
+ logm $ " applyOneCmd:file=" ++ show file
265
+ logm $ " applyOneCmd:res=" ++ show res
266
+ case res of
267
+ Left err -> return $ IdeResultFail
268
+ (IdeError PluginError (T. pack $ " applyOne: " ++ show err) Null )
269
+ Right fs -> return (IdeResultOk fs)
270
+
271
+ applyHint :: FilePath -> Maybe OneHint -> IO (Either String WorkspaceEdit )
272
+ applyHint fp mhint fileMap = do
273
+ runExceptT $ do
274
+ ideas <- getIdeas fp mhint
275
+ let commands = map (show &&& ideaRefactoring) ideas
276
+ liftIO $ logm $ " applyHint:apply=" ++ show commands
277
+ -- set Nothing as "position" for "applyRefactorings" because
278
+ -- applyRefactorings expects the provided position to be _within_ the scope
279
+ -- of each refactoring it will apply.
280
+ -- But "Idea"s returned by HLint pont to starting position of the expressions
281
+ -- that contain refactorings, so they are often outside the refactorings' boundaries.
282
+ -- Example:
283
+ -- Given an expression "hlintTest = reid $ (myid ())"
284
+ -- Hlint returns an idea at the position (1,13)
285
+ -- That contains "Redundant brackets" refactoring at position (1,20):
286
+ --
287
+ -- [("src/App/Test.hs:5:13: Warning: Redundant bracket\nFound:\n reid $ (myid ())\nWhy not:\n reid $ myid ()\n",[Replace {rtype = Expr, pos = SrcSpan {startLine = 5, startCol = 20, endLine = 5, endCol = 29}, subts = [("x",SrcSpan {startLine = 5, startCol = 21, endLine = 5, endCol = 28})], orig = "x"}])]
288
+ --
289
+ -- If we provide "applyRefactorings" with "Just (1,13)" then
290
+ -- the "Redundant bracket" hint will never be executed
291
+ -- because SrcSpan (1,20,??,??) doesn't contain position (1,13).
292
+ res <- liftIO $ (Right <$> applyRefactorings Nothing commands fp) `catches`
293
+ [ Handler $ \ e -> return (Left (show (e :: IOException )))
294
+ , Handler $ \ e -> return (Left (show (e :: ErrorCall )))
295
+ ]
296
+ case res of
297
+ Right appliedFile -> do
298
+ diff <- ExceptT $ Right <$> makeDiffResult fp (T. pack appliedFile) fileMap
299
+ liftIO $ logm $ " applyHint:diff=" ++ show diff
300
+ return diff
301
+ Left err ->
302
+ throwE (show err)
217
303
218
304
-- ---------------------------------------------------------------------
219
305
{-
0 commit comments