Skip to content

Commit 299cf09

Browse files
committed
adds codeaction to ignore hlint hints in the module (module scoped version of haskell#600)
1 parent ddacbce commit 299cf09

File tree

6 files changed

+213
-50
lines changed

6 files changed

+213
-50
lines changed

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

Lines changed: 113 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -6,13 +6,13 @@
66
{-# LANGUAGE FlexibleInstances #-}
77
{-# LANGUAGE OverloadedLabels #-}
88
{-# LANGUAGE OverloadedStrings #-}
9-
{-# LANGUAGE PackageImports #-}
109
{-# LANGUAGE PatternSynonyms #-}
1110
{-# LANGUAGE ScopedTypeVariables #-}
12-
{-# LANGUAGE TupleSections #-}
1311
{-# LANGUAGE TypeFamilies #-}
14-
{-# LANGUAGE ViewPatterns #-}
1512
{-# OPTIONS_GHC -Wno-orphans #-}
13+
{-# LANGUAGE MultiWayIf #-}
14+
{-# LANGUAGE NamedFieldPuns #-}
15+
{-# LANGUAGE RecordWildCards #-}
1616

1717
#ifdef HLINT_ON_GHC_LIB
1818
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc_lib(x,y,z)
@@ -23,7 +23,6 @@
2323
module Ide.Plugin.Hlint
2424
(
2525
descriptor
26-
--, provider
2726
) where
2827
import Control.Arrow ((&&&))
2928
import Control.Concurrent.STM
@@ -105,6 +104,13 @@ import qualified Language.LSP.Types.Lens as LSP
105104
import GHC.Generics (Generic)
106105
import Text.Regex.TDFA.Text ()
107106

107+
import Development.IDE.Spans.Pragmas (LineSplitTextEdits (LineSplitTextEdits),
108+
NextPragmaInfo (NextPragmaInfo),
109+
getNextPragmaInfo,
110+
lineSplitDeleteTextEdit,
111+
lineSplitInsertTextEdit,
112+
lineSplitTextEdits,
113+
nextPragmaLine)
108114
import System.Environment (setEnv,
109115
unsetEnv)
110116
-- ---------------------------------------------------------------------
@@ -303,39 +309,57 @@ getHlintConfig pId =
303309
Config
304310
<$> usePropertyAction #flags pId properties
305311

312+
runHlintAction
313+
:: (Eq k, Hashable k, Show k, Show (RuleResult k), Typeable k, Typeable (RuleResult k), NFData k, NFData (RuleResult k))
314+
=> IdeState
315+
-> NormalizedFilePath -> String -> k -> IO (Maybe (RuleResult k))
316+
runHlintAction ideState normalizedFilePath desc rule = runAction desc ideState $ use rule normalizedFilePath
317+
318+
runGetFileContentsAction :: IdeState -> NormalizedFilePath -> IO (Maybe (FileVersion, Maybe T.Text))
319+
runGetFileContentsAction ideState normalizedFilePath = runHlintAction ideState normalizedFilePath "Hlint.GetFileContents" GetFileContents
320+
321+
runGetModSummaryAction :: IdeState -> NormalizedFilePath -> IO (Maybe ModSummaryResult)
322+
runGetModSummaryAction ideState normalizedFilePath = runHlintAction ideState normalizedFilePath "Hlint.GetModSummary" GetModSummary
323+
306324
-- ---------------------------------------------------------------------
307325
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
326+
codeActionProvider ideState pluginId (CodeActionParams _ _ documentId _ context)
327+
| let TextDocumentIdentifier uri = documentId
328+
, Just docNormalizedFilePath <- uriToNormalizedFilePath (toNormalizedUri uri)
329+
= liftIO $ fmap (Right . LSP.List . map LSP.InR) $ do
330+
allDiagnostics <- atomically $ getDiagnostics ideState
331+
let numHintsInDoc = length
332+
[diagnostic | (diagnosticNormalizedFilePath, _, diagnostic) <- allDiagnostics
333+
, validCommand diagnostic
334+
, diagnosticNormalizedFilePath == docNormalizedFilePath
335+
]
336+
let numHintsInContext = length
337+
[diagnostic | diagnostic <- diags
338+
, validCommand diagnostic
339+
]
340+
file <- runGetFileContentsAction ideState docNormalizedFilePath
341+
singleHintCodeActions <-
342+
if | Just (_, source) <- file -> do
343+
modSummaryResult <- runGetModSummaryAction ideState docNormalizedFilePath
344+
pure if | Just modSummaryResult <- modSummaryResult
345+
, Just source <- source
346+
, let dynFlags = ms_hspp_opts $ msrModSummary modSummaryResult ->
347+
diags >>= diagnosticToCodeActions dynFlags source pluginId documentId
348+
| otherwise -> []
349+
| otherwise -> pure []
350+
if numHintsInDoc > 1 && numHintsInContext > 0 then do
351+
pure $ singleHintCodeActions ++ [applyAllAction]
352+
else
353+
pure singleHintCodeActions
354+
| otherwise
355+
= pure $ Right $ LSP.List []
330356

357+
where
331358
applyAllAction =
332-
let args = Just [toJSON (docId ^. LSP.uri)]
333-
cmd = mkLspCommand plId "applyAll" "Apply all hints" args
359+
let args = Just [toJSON (documentId ^. LSP.uri)]
360+
cmd = mkLspCommand pluginId "applyAll" "Apply all hints" args
334361
in LSP.CodeAction "Apply all hints" (Just LSP.CodeActionQuickFix) Nothing Nothing Nothing Nothing (Just cmd) Nothing
335362

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

345369
LSP.List diags = context ^. LSP.diagnostics
346370

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-
371+
-- | Convert a hlint diagonistic into an apply and an ignore code action
372+
-- if applicable
373+
diagnosticToCodeActions :: DynFlags -> T.Text -> PluginId -> TextDocumentIdentifier -> LSP.Diagnostic -> [LSP.CodeAction]
374+
diagnosticToCodeActions dynFlags fileContents pluginId documentId diagnostic
375+
| LSP.Diagnostic{ _source = Just "hlint", _code = Just (InR code), _range = LSP.Range start _ } <- diagnostic
376+
, let TextDocumentIdentifier uri = documentId
377+
, let isHintApplicable = "refact:" `T.isPrefixOf` code
378+
, let hint = T.replace "refact:" "" code
379+
, let suppressHintTitle = "Ignore hint \"" <> hint <> "\" in this module"
380+
, let suppressHintTextEdits = mkSuppressHintTextEdits dynFlags fileContents hint
381+
, let suppressHintWorkspaceEdit =
382+
LSP.WorkspaceEdit
383+
(Just (Map.singleton uri (List suppressHintTextEdits)))
384+
Nothing
385+
Nothing
386+
= catMaybes
387+
[ if | isHintApplicable
388+
, let applyHintTitle = "Apply hint \"" <> hint <> "\""
389+
applyHintArguments = [toJSON (AOP (documentId ^. LSP.uri) start hint)]
390+
applyHintCommand = mkLspCommand pluginId "applyOne" applyHintTitle (Just applyHintArguments) ->
391+
Just (mkCodeAction applyHintTitle diagnostic Nothing (Just applyHintCommand))
392+
| otherwise -> Nothing
393+
, Just (mkCodeAction suppressHintTitle diagnostic (Just suppressHintWorkspaceEdit) Nothing)
394+
]
395+
| otherwise = []
396+
397+
mkCodeAction :: T.Text -> LSP.Diagnostic -> Maybe LSP.WorkspaceEdit -> Maybe LSP.Command -> LSP.CodeAction
398+
mkCodeAction title diagnostic workspaceEdit command =
399+
LSP.CodeAction
400+
{ _title = title
401+
, _kind = Just LSP.CodeActionQuickFix
402+
, _diagnostics = Just (LSP.List [diagnostic])
403+
, _isPreferred = Nothing
404+
, _disabled = Nothing
405+
, _edit = workspaceEdit
406+
, _command = command
407+
, _xdata = Nothing
408+
}
409+
410+
mkSuppressHintTextEdits :: DynFlags -> T.Text -> T.Text -> [LSP.TextEdit]
411+
mkSuppressHintTextEdits dynFlags fileContents hint =
412+
let
413+
NextPragmaInfo{ nextPragmaLine, lineSplitTextEdits } = getNextPragmaInfo dynFlags (Just fileContents)
414+
nextPragmaLinePosition = Position nextPragmaLine 0
415+
nextPragmaRange = Range nextPragmaLinePosition nextPragmaLinePosition
416+
wnoUnrecognisedPragmasText =
417+
if wopt Opt_WarnUnrecognisedPragmas dynFlags
418+
then Just "{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}\n"
419+
else Nothing
420+
hlintIgnoreText = Just ("{-# HLINT ignore \"" <> hint <> "\" #-}\n")
421+
-- we combine the texts into a single text because lsp-test currently
422+
-- applies text edits backwards and I want the options pragma to
423+
-- appear above the hlint pragma in the tests
424+
combinedText = mconcat $ catMaybes [wnoUnrecognisedPragmasText, hlintIgnoreText]
425+
combinedTextEdit = LSP.TextEdit nextPragmaRange combinedText
426+
lineSplitTextEditList = maybe [] (\LineSplitTextEdits{..} -> [lineSplitInsertTextEdit, lineSplitDeleteTextEdit]) lineSplitTextEdits
427+
in
428+
combinedTextEdit : lineSplitTextEditList
359429
-- ---------------------------------------------------------------------
360430

361431
applyAllCmd :: CommandFunction IdeState Uri

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

Lines changed: 85 additions & 7 deletions
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
@@ -9,6 +12,7 @@ import Data.List (find)
912
import qualified Data.Map as Map
1013
import Data.Maybe (fromJust, isJust)
1114
import qualified Data.Text as T
15+
import qualified Debug.Trace as Debug
1216
import Ide.Plugin.Config (Config (..), PluginConfig (..),
1317
hlintOn)
1418
import qualified Ide.Plugin.Config as Plugin
@@ -27,8 +31,30 @@ tests :: TestTree
2731
tests = testGroup "hlint" [
2832
suggestionsTests
2933
, configTests
34+
, ignoreHintTests
3035
]
3136

37+
getIgnoreHintText :: T.Text -> T.Text
38+
getIgnoreHintText name = "Ignore hint \"" <> name <> "\" in this module"
39+
40+
ignoreHintTests :: TestTree
41+
ignoreHintTests = testGroup "hlint ignore hint tests"
42+
[
43+
ignoreGoldenTest
44+
"Ignore hint in this module inserts -Wno-unrecognised-pragmas and hlint ignore pragma if warn unrecognized pragmas is off"
45+
"UnrecognizedPragmasOff"
46+
(Point 3 8)
47+
"Eta reduce"
48+
-- in this test the options and hlint pragmas are inserted in opposite order
49+
-- in the golden test but in correct order in vscode and coc.nvim so lsp-test
50+
-- applies text edits backwards.
51+
, ignoreGoldenTest
52+
"Ignore hint in this module inserts only hlint ignore pragma if warn unrecognized pragmas is on"
53+
"UnrecognizedPragmasOn"
54+
(Point 3 9)
55+
"Eta reduce"
56+
]
57+
3258
suggestionsTests :: TestTree
3359
suggestionsTests =
3460
testGroup "hlint suggestions" [
@@ -45,13 +71,19 @@ suggestionsTests =
4571

4672
cas <- map fromAction <$> getAllCodeActions doc
4773

74+
let redundantIdHintName = "Redundant id"
75+
let etaReduceHintName = "Eta reduce"
4876
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
77+
let redId = find (\ca -> redundantIdHintName `T.isInfixOf` (ca ^. L.title)) cas
78+
let redEta = find (\ca -> etaReduceHintName `T.isInfixOf` (ca ^. L.title)) cas
79+
let ignoreRedundantIdInThisModule = find (\ca -> getIgnoreHintText redundantIdHintName == (ca ^.L.title)) cas
80+
let ignoreEtaReduceThisModule = find (\ca -> getIgnoreHintText etaReduceHintName == (ca ^.L.title)) cas
5181

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"
82+
liftIO $ isJust applyAll @? "There is Apply all hints code action"
83+
liftIO $ isJust redId @? "There is Redundant id code action"
84+
liftIO $ isJust redEta @? "There is Eta reduce code action"
85+
liftIO $ isJust ignoreRedundantIdInThisModule @? "There is ignore Redundant id code action"
86+
liftIO $ isJust ignoreEtaReduceThisModule @? "There is ignore Eta reduce code action"
5587

5688
executeCodeAction (fromJust redId)
5789

@@ -185,7 +217,7 @@ suggestionsTests =
185217
testHlintDiagnostics doc
186218

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

191223
executeCodeAction (fromJust ca)
@@ -284,9 +316,12 @@ configTests = testGroup "hlint plugin config" [
284316
d ^. L.severity @?= Just DsInfo
285317
]
286318

319+
testDir :: FilePath
320+
testDir = "test/testdata"
321+
287322
runHlintSession :: FilePath -> Session a -> IO a
288323
runHlintSession subdir =
289-
failIfSessionTimeout . runSessionWithServer hlintPlugin ("test/testdata" </> subdir)
324+
failIfSessionTimeout . runSessionWithServer hlintPlugin (testDir </> subdir)
290325

291326
noHlintDiagnostics :: [Diagnostic] -> Assertion
292327
noHlintDiagnostics diags =
@@ -326,3 +361,46 @@ knownBrokenForHlintOnGhcLib = knownBrokenForGhcVersions [GHC88, GHC86]
326361

327362
knownBrokenForHlintOnRawGhc :: String -> TestTree -> TestTree
328363
knownBrokenForHlintOnRawGhc = knownBrokenForGhcVersions [GHC810, GHC90]
364+
365+
-- 1's based
366+
data Point = Point {
367+
line :: !Int,
368+
column :: !Int
369+
}
370+
371+
makePoint line column
372+
| line >= 1 && column >= 1 = Point line column
373+
| otherwise = error "Line or column is less than 1."
374+
375+
pointToRange :: Point -> Range
376+
pointToRange Point {..}
377+
| line <- subtract 1 line
378+
, column <- subtract 1 column =
379+
Range (Position line column) (Position line $ column + 1)
380+
381+
getCodeActionTitle :: (Command |? CodeAction) -> Maybe T.Text
382+
getCodeActionTitle commandOrCodeAction
383+
| InR CodeAction {_title} <- commandOrCodeAction = Just _title
384+
| otherwise = Nothing
385+
386+
makeCodeActionNotFoundAtString :: Point -> String
387+
makeCodeActionNotFoundAtString Point {..} =
388+
"CodeAction not found at line: " <> show line <> ", column: " <> show column
389+
390+
makeCodeActionFoundAtString :: Point -> String
391+
makeCodeActionFoundAtString Point {..} =
392+
"CodeAction found at line: " <> show line <> ", column: " <> show column
393+
394+
ignoreGoldenTest :: TestName -> FilePath -> Point -> T.Text -> TestTree
395+
ignoreGoldenTest testCaseName goldenFilename point hintName =
396+
setupGoldenHlintTest testCaseName goldenFilename $ \document -> do
397+
waitForDiagnosticsFromSource document "hlint"
398+
actions <- getCodeActions document $ pointToRange point
399+
case find ((== Just (getIgnoreHintText hintName)) . getCodeActionTitle) actions of
400+
Just (InR codeAction) -> executeCodeAction codeAction
401+
_ -> liftIO $ assertFailure $ makeCodeActionNotFoundAtString point
402+
403+
setupGoldenHlintTest :: TestName -> FilePath -> (TextDocumentIdentifier -> Session ()) -> TestTree
404+
setupGoldenHlintTest testName path =
405+
goldenWithHaskellDoc hlintPlugin testName testDir path "expected" "hs"
406+
Lines changed: 4 additions & 0 deletions
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
Lines changed: 3 additions & 0 deletions
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
Lines changed: 5 additions & 0 deletions
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
Lines changed: 3 additions & 0 deletions
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)