Skip to content

Commit 0f49c0e

Browse files
eddiemundojneira
andauthored
#600 Code action to ignore hlint hints module wide (#2458)
* adds codeaction to ignore hlint hints in the module (module scoped version of #600) * fix imports * fix imports 2 * remove outdated comment * fix tests * remove debug import Co-authored-by: Javier Neira <[email protected]>
1 parent cf84ef5 commit 0f49c0e

File tree

7 files changed

+212
-48
lines changed

7 files changed

+212
-48
lines changed

ghcide/src/Development/IDE/Spans/Pragmas.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -388,7 +388,7 @@ mkLexerPState dynFlags stringBuffer =
388388
<*> gopt Opt_Haddock
389389
<*> gopt Opt_KeepRawTokenStream
390390
<*> const False
391-
finalPState = mkPStatePure (mkLexerParserFlags dynFlags) stringBuffer startRealSrcLoc
391+
finalPState = mkPStatePure (mkLexerParserFlags finalDynFlags) stringBuffer startRealSrcLoc
392392
#else
393393
pState = mkPState finalDynFlags stringBuffer startRealSrcLoc
394394
PState{ options = pStateOptions } = pState

plugins/hls-hlint-plugin/src/Ide/Plugin/Hlint.hs

+115-40
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,9 @@
1313
{-# LANGUAGE TypeFamilies #-}
1414
{-# LANGUAGE ViewPatterns #-}
1515
{-# OPTIONS_GHC -Wno-orphans #-}
16+
{-# LANGUAGE MultiWayIf #-}
17+
{-# LANGUAGE NamedFieldPuns #-}
18+
{-# LANGUAGE RecordWildCards #-}
1619

1720
#ifdef HLINT_ON_GHC_LIB
1821
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc_lib(x,y,z)
@@ -23,7 +26,6 @@
2326
module Ide.Plugin.Hlint
2427
(
2528
descriptor
26-
--, provider
2729
) where
2830
import Control.Arrow ((&&&))
2931
import Control.Concurrent.STM
@@ -105,6 +107,15 @@ import qualified Language.LSP.Types.Lens as LSP
105107
import GHC.Generics (Generic)
106108
import Text.Regex.TDFA.Text ()
107109

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)
108119
import System.Environment (setEnv,
109120
unsetEnv)
110121
-- ---------------------------------------------------------------------
@@ -303,39 +314,57 @@ getHlintConfig pId =
303314
Config
304315
<$> usePropertyAction #flags pId properties
305316

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+
306329
-- ---------------------------------------------------------------------
307330
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 []
330361

362+
where
331363
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
334366
in LSP.CodeAction "Apply all hints" (Just LSP.CodeActionQuickFix) Nothing Nothing Nothing Nothing (Just cmd) Nothing
335367

336-
applyOneActions :: [LSP.CodeAction]
337-
applyOneActions = mapMaybe mkHlintAction (filter validCommand diags)
338-
339368
-- |Some hints do not have an associated refactoring
340369
validCommand (LSP.Diagnostic _ _ (Just (InR code)) (Just "hlint") _ _ _) =
341370
"refact:" `T.isPrefixOf` code
@@ -344,18 +373,64 @@ codeActionProvider ideState plId (CodeActionParams _ _ docId _ context) = Right
344373

345374
LSP.List diags = context ^. LSP.diagnostics
346375

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
359434
-- ---------------------------------------------------------------------
360435

361436
applyAllCmd :: CommandFunction IdeState Uri

plugins/hls-hlint-plugin/test/Main.hs

+81-7
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,7 @@
1+
{-# LANGUAGE NamedFieldPuns #-}
12
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE RecordWildCards #-}
4+
{-# LANGUAGE TypeOperators #-}
25
module Main
36
( main
47
) where
@@ -27,8 +30,27 @@ tests :: TestTree
2730
tests = testGroup "hlint" [
2831
suggestionsTests
2932
, configTests
33+
, ignoreHintTests
3034
]
3135

36+
getIgnoreHintText :: T.Text -> T.Text
37+
getIgnoreHintText name = "Ignore hint \"" <> name <> "\" in this module"
38+
39+
ignoreHintTests :: TestTree
40+
ignoreHintTests = testGroup "hlint ignore hint tests"
41+
[
42+
ignoreGoldenTest
43+
"Ignore hint in this module inserts -Wno-unrecognised-pragmas and hlint ignore pragma if warn unrecognized pragmas is off"
44+
"UnrecognizedPragmasOff"
45+
(Point 3 8)
46+
"Eta reduce"
47+
, ignoreGoldenTest
48+
"Ignore hint in this module inserts only hlint ignore pragma if warn unrecognized pragmas is on"
49+
"UnrecognizedPragmasOn"
50+
(Point 3 9)
51+
"Eta reduce"
52+
]
53+
3254
suggestionsTests :: TestTree
3355
suggestionsTests =
3456
testGroup "hlint suggestions" [
@@ -45,13 +67,19 @@ suggestionsTests =
4567

4668
cas <- map fromAction <$> getAllCodeActions doc
4769

70+
let redundantIdHintName = "Redundant id"
71+
let etaReduceHintName = "Eta reduce"
4872
let applyAll = find (\ca -> "Apply all hints" `T.isSuffixOf` (ca ^. L.title)) cas
49-
let redId = find (\ca -> "Redundant id" `T.isSuffixOf` (ca ^. L.title)) cas
50-
let redEta = find (\ca -> "Eta reduce" `T.isSuffixOf` (ca ^. L.title)) cas
73+
let redId = find (\ca -> redundantIdHintName `T.isInfixOf` (ca ^. L.title)) cas
74+
let redEta = find (\ca -> etaReduceHintName `T.isInfixOf` (ca ^. L.title)) cas
75+
let ignoreRedundantIdInThisModule = find (\ca -> getIgnoreHintText redundantIdHintName == (ca ^.L.title)) cas
76+
let ignoreEtaReduceThisModule = find (\ca -> getIgnoreHintText etaReduceHintName == (ca ^.L.title)) cas
5177

52-
liftIO $ isJust applyAll @? "There is 'Apply all hints' code action"
53-
liftIO $ isJust redId @? "There is 'Redundant id' code action"
54-
liftIO $ isJust redEta @? "There is 'Eta reduce' code action"
78+
liftIO $ isJust applyAll @? "There is Apply all hints code action"
79+
liftIO $ isJust redId @? "There is Redundant id code action"
80+
liftIO $ isJust redEta @? "There is Eta reduce code action"
81+
liftIO $ isJust ignoreRedundantIdInThisModule @? "There is ignore Redundant id code action"
82+
liftIO $ isJust ignoreEtaReduceThisModule @? "There is ignore Eta reduce code action"
5583

5684
executeCodeAction (fromJust redId)
5785

@@ -185,7 +213,7 @@ suggestionsTests =
185213
testHlintDiagnostics doc
186214

187215
cas <- map fromAction <$> getAllCodeActions doc
188-
let ca = find (\ca -> caTitle `T.isSuffixOf` (ca ^. L.title)) cas
216+
let ca = find (\ca -> caTitle `T.isInfixOf` (ca ^. L.title)) cas
189217
liftIO $ isJust ca @? ("There is '" ++ T.unpack caTitle ++"' code action")
190218

191219
executeCodeAction (fromJust ca)
@@ -284,9 +312,12 @@ configTests = testGroup "hlint plugin config" [
284312
d ^. L.severity @?= Just DsInfo
285313
]
286314

315+
testDir :: FilePath
316+
testDir = "test/testdata"
317+
287318
runHlintSession :: FilePath -> Session a -> IO a
288319
runHlintSession subdir =
289-
failIfSessionTimeout . runSessionWithServer hlintPlugin ("test/testdata" </> subdir)
320+
failIfSessionTimeout . runSessionWithServer hlintPlugin (testDir </> subdir)
290321

291322
noHlintDiagnostics :: [Diagnostic] -> Assertion
292323
noHlintDiagnostics diags =
@@ -326,3 +357,46 @@ knownBrokenForHlintOnGhcLib = knownBrokenForGhcVersions [GHC88, GHC86]
326357

327358
knownBrokenForHlintOnRawGhc :: String -> TestTree -> TestTree
328359
knownBrokenForHlintOnRawGhc = knownBrokenForGhcVersions [GHC810, GHC90]
360+
361+
-- 1's based
362+
data Point = Point {
363+
line :: !Int,
364+
column :: !Int
365+
}
366+
367+
makePoint line column
368+
| line >= 1 && column >= 1 = Point line column
369+
| otherwise = error "Line or column is less than 1."
370+
371+
pointToRange :: Point -> Range
372+
pointToRange Point {..}
373+
| line <- subtract 1 line
374+
, column <- subtract 1 column =
375+
Range (Position line column) (Position line $ column + 1)
376+
377+
getCodeActionTitle :: (Command |? CodeAction) -> Maybe T.Text
378+
getCodeActionTitle commandOrCodeAction
379+
| InR CodeAction {_title} <- commandOrCodeAction = Just _title
380+
| otherwise = Nothing
381+
382+
makeCodeActionNotFoundAtString :: Point -> String
383+
makeCodeActionNotFoundAtString Point {..} =
384+
"CodeAction not found at line: " <> show line <> ", column: " <> show column
385+
386+
makeCodeActionFoundAtString :: Point -> String
387+
makeCodeActionFoundAtString Point {..} =
388+
"CodeAction found at line: " <> show line <> ", column: " <> show column
389+
390+
ignoreGoldenTest :: TestName -> FilePath -> Point -> T.Text -> TestTree
391+
ignoreGoldenTest testCaseName goldenFilename point hintName =
392+
setupGoldenHlintTest testCaseName goldenFilename $ \document -> do
393+
waitForDiagnosticsFromSource document "hlint"
394+
actions <- getCodeActions document $ pointToRange point
395+
case find ((== Just (getIgnoreHintText hintName)) . getCodeActionTitle) actions of
396+
Just (InR codeAction) -> executeCodeAction codeAction
397+
_ -> liftIO $ assertFailure $ makeCodeActionNotFoundAtString point
398+
399+
setupGoldenHlintTest :: TestName -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree
400+
setupGoldenHlintTest testName path =
401+
goldenWithHaskellDoc hlintPlugin testName testDir path "expected" "hs"
402+
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
2+
{-# HLINT ignore "Eta reduce" #-}
3+
module UnrecognizedPragmasOff where
4+
foo x = id x
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
2+
module UnrecognizedPragmasOff where
3+
foo x = id x
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
{-# OPTIONS_GHC -Wunrecognised-pragmas #-}
2+
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}
3+
{-# HLINT ignore "Eta reduce" #-}
4+
module UnrecognizedPragmasOn where
5+
foo x = id x
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
{-# OPTIONS_GHC -Wunrecognised-pragmas #-}
2+
module UnrecognizedPragmasOn where
3+
foo x = id x

0 commit comments

Comments
 (0)