13
13
{-# LANGUAGE TypeFamilies #-}
14
14
{-# LANGUAGE ViewPatterns #-}
15
15
{-# OPTIONS_GHC -Wno-orphans #-}
16
+ {-# LANGUAGE MultiWayIf #-}
17
+ {-# LANGUAGE NamedFieldPuns #-}
18
+ {-# LANGUAGE RecordWildCards #-}
16
19
17
20
#ifdef HLINT_ON_GHC_LIB
18
21
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc_lib(x,y,z)
23
26
module Ide.Plugin.Hlint
24
27
(
25
28
descriptor
26
- -- , provider
27
29
) where
28
30
import Control.Arrow ((&&&) )
29
31
import Control.Concurrent.STM
@@ -105,6 +107,15 @@ import qualified Language.LSP.Types.Lens as LSP
105
107
import GHC.Generics (Generic )
106
108
import Text.Regex.TDFA.Text ()
107
109
110
+ import Development.IDE.GHC.Compat.Core (WarningFlag (Opt_WarnUnrecognisedPragmas ),
111
+ wopt )
112
+ import Development.IDE.Spans.Pragmas (LineSplitTextEdits (LineSplitTextEdits ),
113
+ NextPragmaInfo (NextPragmaInfo ),
114
+ getNextPragmaInfo ,
115
+ lineSplitDeleteTextEdit ,
116
+ lineSplitInsertTextEdit ,
117
+ lineSplitTextEdits ,
118
+ nextPragmaLine )
108
119
import System.Environment (setEnv ,
109
120
unsetEnv )
110
121
-- ---------------------------------------------------------------------
@@ -303,39 +314,57 @@ getHlintConfig pId =
303
314
Config
304
315
<$> usePropertyAction # flags pId properties
305
316
317
+ runHlintAction
318
+ :: (Eq k , Hashable k , Show k , Show (RuleResult k ), Typeable k , Typeable (RuleResult k ), NFData k , NFData (RuleResult k ))
319
+ => IdeState
320
+ -> NormalizedFilePath -> String -> k -> IO (Maybe (RuleResult k ))
321
+ runHlintAction ideState normalizedFilePath desc rule = runAction desc ideState $ use rule normalizedFilePath
322
+
323
+ runGetFileContentsAction :: IdeState -> NormalizedFilePath -> IO (Maybe (FileVersion , Maybe T. Text ))
324
+ runGetFileContentsAction ideState normalizedFilePath = runHlintAction ideState normalizedFilePath " Hlint.GetFileContents" GetFileContents
325
+
326
+ runGetModSummaryAction :: IdeState -> NormalizedFilePath -> IO (Maybe ModSummaryResult )
327
+ runGetModSummaryAction ideState normalizedFilePath = runHlintAction ideState normalizedFilePath " Hlint.GetModSummary" GetModSummary
328
+
306
329
-- ---------------------------------------------------------------------
307
330
codeActionProvider :: PluginMethodHandler IdeState TextDocumentCodeAction
308
- codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right . LSP. List . map InR <$> liftIO getCodeActions
309
- where
310
-
311
- getCodeActions = do
312
- allDiags <- atomically $ getDiagnostics ideState
313
- let docNfp = toNormalizedFilePath' <$> uriToFilePath' (docId ^. LSP. uri)
314
- numHintsInDoc = length
315
- [d | (nfp, _, d) <- allDiags
316
- , validCommand d
317
- , Just nfp == docNfp
318
- ]
319
- numHintsInContext = length
320
- [d | d <- diags
321
- , validCommand d
322
- ]
323
- -- We only want to show the applyAll code action if there is more than 1
324
- -- hint in the current document and if code action range contains at
325
- -- least one hint
326
- if numHintsInDoc > 1 && numHintsInContext > 0 then do
327
- pure $ applyAllAction: applyOneActions
328
- else
329
- pure applyOneActions
331
+ codeActionProvider ideState pluginId (CodeActionParams _ _ documentId _ context)
332
+ | let TextDocumentIdentifier uri = documentId
333
+ , Just docNormalizedFilePath <- uriToNormalizedFilePath (toNormalizedUri uri)
334
+ = liftIO $ fmap (Right . LSP. List . map LSP. InR ) $ do
335
+ allDiagnostics <- atomically $ getDiagnostics ideState
336
+ let numHintsInDoc = length
337
+ [diagnostic | (diagnosticNormalizedFilePath, _, diagnostic) <- allDiagnostics
338
+ , validCommand diagnostic
339
+ , diagnosticNormalizedFilePath == docNormalizedFilePath
340
+ ]
341
+ let numHintsInContext = length
342
+ [diagnostic | diagnostic <- diags
343
+ , validCommand diagnostic
344
+ ]
345
+ file <- runGetFileContentsAction ideState docNormalizedFilePath
346
+ singleHintCodeActions <-
347
+ if | Just (_, source) <- file -> do
348
+ modSummaryResult <- runGetModSummaryAction ideState docNormalizedFilePath
349
+ pure if | Just modSummaryResult <- modSummaryResult
350
+ , Just source <- source
351
+ , let dynFlags = ms_hspp_opts $ msrModSummary modSummaryResult ->
352
+ diags >>= diagnosticToCodeActions dynFlags source pluginId documentId
353
+ | otherwise -> []
354
+ | otherwise -> pure []
355
+ if numHintsInDoc > 1 && numHintsInContext > 0 then do
356
+ pure $ singleHintCodeActions ++ [applyAllAction]
357
+ else
358
+ pure singleHintCodeActions
359
+ | otherwise
360
+ = pure $ Right $ LSP. List []
330
361
362
+ where
331
363
applyAllAction =
332
- let args = Just [toJSON (docId ^. LSP. uri)]
333
- cmd = mkLspCommand plId " applyAll" " Apply all hints" args
364
+ let args = Just [toJSON (documentId ^. LSP. uri)]
365
+ cmd = mkLspCommand pluginId " applyAll" " Apply all hints" args
334
366
in LSP. CodeAction " Apply all hints" (Just LSP. CodeActionQuickFix ) Nothing Nothing Nothing Nothing (Just cmd) Nothing
335
367
336
- applyOneActions :: [LSP. CodeAction ]
337
- applyOneActions = mapMaybe mkHlintAction (filter validCommand diags)
338
-
339
368
-- | Some hints do not have an associated refactoring
340
369
validCommand (LSP. Diagnostic _ _ (Just (InR code)) (Just " hlint" ) _ _ _) =
341
370
" refact:" `T.isPrefixOf` code
@@ -344,18 +373,64 @@ codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right
344
373
345
374
LSP. List diags = context ^. LSP. diagnostics
346
375
347
- mkHlintAction :: LSP. Diagnostic -> Maybe LSP. CodeAction
348
- mkHlintAction diag@ (LSP. Diagnostic (LSP. Range start _) _s (Just (InR code)) (Just " hlint" ) _ _ _) =
349
- Just . codeAction $ mkLspCommand plId " applyOne" title (Just args)
350
- where
351
- codeAction cmd = LSP. CodeAction title (Just LSP. CodeActionQuickFix ) (Just (LSP. List [diag])) Nothing Nothing Nothing (Just cmd) Nothing
352
- -- we have to recover the original ideaHint removing the prefix
353
- ideaHint = T. replace " refact:" " " code
354
- title = " Apply hint: " <> ideaHint
355
- -- need 'file', 'start_pos' and hint title (to distinguish between alternative suggestions at the same location)
356
- args = [toJSON (AOP (docId ^. LSP. uri) start ideaHint)]
357
- mkHlintAction (LSP. Diagnostic _r _s _c _source _m _ _) = Nothing
358
-
376
+ -- | Convert a hlint diagonistic into an apply and an ignore code action
377
+ -- if applicable
378
+ diagnosticToCodeActions :: DynFlags -> T. Text -> PluginId -> TextDocumentIdentifier -> LSP. Diagnostic -> [LSP. CodeAction ]
379
+ diagnosticToCodeActions dynFlags fileContents pluginId documentId diagnostic
380
+ | LSP. Diagnostic { _source = Just " hlint" , _code = Just (InR code), _range = LSP. Range start _ } <- diagnostic
381
+ , let TextDocumentIdentifier uri = documentId
382
+ , let isHintApplicable = " refact:" `T.isPrefixOf` code
383
+ , let hint = T. replace " refact:" " " code
384
+ , let suppressHintTitle = " Ignore hint \" " <> hint <> " \" in this module"
385
+ , let suppressHintTextEdits = mkSuppressHintTextEdits dynFlags fileContents hint
386
+ , let suppressHintWorkspaceEdit =
387
+ LSP. WorkspaceEdit
388
+ (Just (Map. singleton uri (List suppressHintTextEdits)))
389
+ Nothing
390
+ Nothing
391
+ = catMaybes
392
+ [ if | isHintApplicable
393
+ , let applyHintTitle = " Apply hint \" " <> hint <> " \" "
394
+ applyHintArguments = [toJSON (AOP (documentId ^. LSP. uri) start hint)]
395
+ applyHintCommand = mkLspCommand pluginId " applyOne" applyHintTitle (Just applyHintArguments) ->
396
+ Just (mkCodeAction applyHintTitle diagnostic Nothing (Just applyHintCommand))
397
+ | otherwise -> Nothing
398
+ , Just (mkCodeAction suppressHintTitle diagnostic (Just suppressHintWorkspaceEdit) Nothing )
399
+ ]
400
+ | otherwise = []
401
+
402
+ mkCodeAction :: T. Text -> LSP. Diagnostic -> Maybe LSP. WorkspaceEdit -> Maybe LSP. Command -> LSP. CodeAction
403
+ mkCodeAction title diagnostic workspaceEdit command =
404
+ LSP. CodeAction
405
+ { _title = title
406
+ , _kind = Just LSP. CodeActionQuickFix
407
+ , _diagnostics = Just (LSP. List [diagnostic])
408
+ , _isPreferred = Nothing
409
+ , _disabled = Nothing
410
+ , _edit = workspaceEdit
411
+ , _command = command
412
+ , _xdata = Nothing
413
+ }
414
+
415
+ mkSuppressHintTextEdits :: DynFlags -> T. Text -> T. Text -> [LSP. TextEdit ]
416
+ mkSuppressHintTextEdits dynFlags fileContents hint =
417
+ let
418
+ NextPragmaInfo { nextPragmaLine, lineSplitTextEdits } = getNextPragmaInfo dynFlags (Just fileContents)
419
+ nextPragmaLinePosition = Position nextPragmaLine 0
420
+ nextPragmaRange = Range nextPragmaLinePosition nextPragmaLinePosition
421
+ wnoUnrecognisedPragmasText =
422
+ if wopt Opt_WarnUnrecognisedPragmas dynFlags
423
+ then Just " {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}\n "
424
+ else Nothing
425
+ hlintIgnoreText = Just (" {-# HLINT ignore \" " <> hint <> " \" #-}\n " )
426
+ -- we combine the texts into a single text because lsp-test currently
427
+ -- applies text edits backwards and I want the options pragma to
428
+ -- appear above the hlint pragma in the tests
429
+ combinedText = mconcat $ catMaybes [wnoUnrecognisedPragmasText, hlintIgnoreText]
430
+ combinedTextEdit = LSP. TextEdit nextPragmaRange combinedText
431
+ lineSplitTextEditList = maybe [] (\ LineSplitTextEdits {.. } -> [lineSplitInsertTextEdit, lineSplitDeleteTextEdit]) lineSplitTextEdits
432
+ in
433
+ combinedTextEdit : lineSplitTextEditList
359
434
-- ---------------------------------------------------------------------
360
435
361
436
applyAllCmd :: CommandFunction IdeState Uri
0 commit comments