Skip to content

Commit f03a7fa

Browse files
Add code actions for disabling a warning in the current file (#1235)
* Slacken some flaky tests The properties tested were previously unnecessarily strong and would break witht the addition of irrelevant code actions. We now don't care about position and total quantity of code actions, only that the ones we care about exist. * Add code action for disabling a warning * Fix test * Remove redundant import * Fix imports * Fix more tests Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
1 parent 691f2be commit f03a7fa

File tree

5 files changed

+135
-31
lines changed

5 files changed

+135
-31
lines changed

ghcide/src/Development/IDE/GHC/Warnings.hs

Lines changed: 15 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,14 +3,16 @@
33

44
module Development.IDE.GHC.Warnings(withWarnings) where
55

6+
import Data.List
67
import ErrUtils
7-
import GhcPlugins as GHC hiding (Var)
8+
import GhcPlugins as GHC hiding (Var, (<>))
89

910
import Control.Concurrent.Extra
1011
import qualified Data.Text as T
1112

1213
import Development.IDE.Types.Diagnostics
1314
import Development.IDE.GHC.Error
15+
import Language.Haskell.LSP.Types (NumberOrString (StringValue))
1416

1517

1618
-- | Take a GHC monadic action (e.g. @typecheckModule pm@ for some
@@ -27,8 +29,19 @@ withWarnings diagSource action = do
2729
warnings <- newVar []
2830
let newAction :: DynFlags -> WarnReason -> Severity -> SrcSpan -> PprStyle -> SDoc -> IO ()
2931
newAction dynFlags wr _ loc style msg = do
30-
let wr_d = fmap (wr,) $ diagFromErrMsg diagSource dynFlags $ mkWarnMsg dynFlags loc (queryQual style) msg
32+
let wr_d = map ((wr,) . third3 (attachReason wr)) $ diagFromErrMsg diagSource dynFlags $ mkWarnMsg dynFlags loc (queryQual style) msg
3133
modifyVar_ warnings $ return . (wr_d:)
3234
res <- action $ \x -> x{ms_hspp_opts = (ms_hspp_opts x){log_action = newAction}}
3335
warns <- readVar warnings
3436
return (reverse $ concat warns, res)
37+
38+
attachReason :: WarnReason -> Diagnostic -> Diagnostic
39+
attachReason wr d = d{_code = StringValue <$> showReason wr}
40+
where
41+
showReason = \case
42+
NoReason -> Nothing
43+
Reason flag -> showFlag flag
44+
ErrReason flag -> showFlag =<< flag
45+
46+
showFlag :: WarningFlag -> Maybe T.Text
47+
showFlag flag = ("-W" <>) . T.pack . flagSpecName <$> find ((== flag) . flagSpecFlag) wWarningFlags

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -203,6 +203,7 @@ suggestAction packageExports ideOptions parsedModule text diag = concat
203203
++ suggestNewImport packageExports pm diag
204204
++ suggestDeleteUnusedBinding pm text diag
205205
++ suggestExportUnusedTopBinding text pm diag
206+
++ suggestDisableWarning pm text diag
206207
| Just pm <- [parsedModule]
207208
] ++
208209
suggestFillHole diag -- Lowest priority
@@ -226,6 +227,15 @@ findInstanceHead df instanceHead decls =
226227
findDeclContainingLoc :: Position -> [Located a] -> Maybe (Located a)
227228
findDeclContainingLoc loc = find (\(L l _) -> loc `isInsideSrcSpan` l)
228229

230+
suggestDisableWarning :: ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
231+
suggestDisableWarning pm contents Diagnostic{..}
232+
| Just (StringValue (T.stripPrefix "-W" -> Just w)) <- _code =
233+
pure
234+
( "Disable \"" <> w <> "\" warnings"
235+
, [TextEdit (endOfModuleHeader pm contents) $ "{-# OPTIONS_GHC -Wno-" <> w <> " #-}\n"]
236+
)
237+
| otherwise = []
238+
229239
suggestRemoveRedundantImport :: ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
230240
suggestRemoveRedundantImport ParsedModule{pm_parsed_source = L _ HsModule{hsmodImports}} contents Diagnostic{_range=_range,..}
231241
-- The qualified import of ‘many’ from module ‘Control.Applicative’ is redundant
@@ -1247,3 +1257,17 @@ importStyles IdentInfo {parent, rendered, isDatacon}
12471257
renderImportStyle :: ImportStyle -> T.Text
12481258
renderImportStyle (ImportTopLevel x) = x
12491259
renderImportStyle (ImportViaParent x p) = p <> "(" <> x <> ")"
1260+
1261+
-- | Find the first non-blank line before the first of (module name / imports / declarations).
1262+
-- Useful for inserting pragmas.
1263+
endOfModuleHeader :: ParsedModule -> Maybe T.Text -> Range
1264+
endOfModuleHeader pm contents =
1265+
let mod = unLoc $ pm_parsed_source pm
1266+
modNameLoc = getLoc <$> hsmodName mod
1267+
firstImportLoc = getLoc <$> listToMaybe (hsmodImports mod)
1268+
firstDeclLoc = getLoc <$> listToMaybe (hsmodDecls mod)
1269+
line = fromMaybe 0 $ firstNonBlankBefore . _line . _start =<< srcSpanToRange =<<
1270+
modNameLoc <|> firstImportLoc <|> firstDeclLoc
1271+
firstNonBlankBefore n = (n -) . fromMaybe 0 . findIndex (not . T.null) . reverse . take n . T.lines <$> contents
1272+
loc = Position line 0
1273+
in Range loc loc

ghcide/test/exe/Main.hs

Lines changed: 94 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ import Control.Applicative.Combinators
1414
import Control.Exception (bracket_, catch)
1515
import qualified Control.Lens as Lens
1616
import Control.Monad
17-
import Control.Monad.IO.Class (liftIO)
17+
import Control.Monad.IO.Class (MonadIO, liftIO)
1818
import Data.Aeson (FromJSON, Value, toJSON)
1919
import qualified Data.Binary as Binary
2020
import Data.Default
@@ -64,6 +64,7 @@ import Development.IDE.Plugin.Test (WaitForIdeRuleResult(..), TestRequest(BlockS
6464
import Control.Monad.Extra (whenJust)
6565
import qualified Language.Haskell.LSP.Types.Lens as L
6666
import Control.Lens ((^.))
67+
import Data.Functor
6768

6869
main :: IO ()
6970
main = do
@@ -676,6 +677,7 @@ codeActionTests = testGroup "code actions"
676677
, removeImportTests
677678
, extendImportTests
678679
, suggestImportTests
680+
, disableWarningTests
679681
, fixConstructorImportTests
680682
, importRenameActionTests
681683
, fillTypedHoleTests
@@ -881,9 +883,8 @@ removeImportTests = testGroup "remove import actions"
881883
]
882884
docB <- createDoc "ModuleB.hs" "haskell" contentB
883885
_ <- waitForDiagnostics
884-
[CACodeAction action@CodeAction { _title = actionTitle }, _]
885-
<- getCodeActions docB (Range (Position 2 0) (Position 2 5))
886-
liftIO $ "Remove import" @=? actionTitle
886+
action <- assertJust "Code action not found" . firstJust (caWithTitle "Remove import")
887+
=<< getCodeActions docB (Range (Position 2 0) (Position 2 5))
887888
executeCodeAction action
888889
contentAfterAction <- documentContents docB
889890
let expectedContentAfterAction = T.unlines
@@ -907,9 +908,8 @@ removeImportTests = testGroup "remove import actions"
907908
]
908909
docB <- createDoc "ModuleB.hs" "haskell" contentB
909910
_ <- waitForDiagnostics
910-
[CACodeAction action@CodeAction { _title = actionTitle }, _]
911-
<- getCodeActions docB (Range (Position 2 0) (Position 2 5))
912-
liftIO $ "Remove import" @=? actionTitle
911+
action <- assertJust "Code action not found" . firstJust (caWithTitle "Remove import")
912+
=<< getCodeActions docB (Range (Position 2 0) (Position 2 5))
913913
executeCodeAction action
914914
contentAfterAction <- documentContents docB
915915
let expectedContentAfterAction = T.unlines
@@ -936,9 +936,8 @@ removeImportTests = testGroup "remove import actions"
936936
]
937937
docB <- createDoc "ModuleB.hs" "haskell" contentB
938938
_ <- waitForDiagnostics
939-
[CACodeAction action@CodeAction { _title = actionTitle }, _]
940-
<- getCodeActions docB (Range (Position 2 0) (Position 2 5))
941-
liftIO $ "Remove stuffA, stuffC from import" @=? actionTitle
939+
action <- assertJust "Code action not found" . firstJust (caWithTitle "Remove stuffA, stuffC from import")
940+
=<< getCodeActions docB (Range (Position 2 0) (Position 2 5))
942941
executeCodeAction action
943942
contentAfterAction <- documentContents docB
944943
let expectedContentAfterAction = T.unlines
@@ -965,9 +964,8 @@ removeImportTests = testGroup "remove import actions"
965964
]
966965
docB <- createDoc "ModuleB.hs" "haskell" contentB
967966
_ <- waitForDiagnostics
968-
[CACodeAction action@CodeAction { _title = actionTitle }, _]
969-
<- getCodeActions docB (Range (Position 2 0) (Position 2 5))
970-
liftIO $ "Remove !!, <?> from import" @=? actionTitle
967+
action <- assertJust "Code action not found" . firstJust (caWithTitle "Remove !!, <?> from import")
968+
=<< getCodeActions docB (Range (Position 2 0) (Position 2 5))
971969
executeCodeAction action
972970
contentAfterAction <- documentContents docB
973971
let expectedContentAfterAction = T.unlines
@@ -993,9 +991,8 @@ removeImportTests = testGroup "remove import actions"
993991
]
994992
docB <- createDoc "ModuleB.hs" "haskell" contentB
995993
_ <- waitForDiagnostics
996-
[CACodeAction action@CodeAction { _title = actionTitle }, _]
997-
<- getCodeActions docB (Range (Position 2 0) (Position 2 5))
998-
liftIO $ "Remove A from import" @=? actionTitle
994+
action <- assertJust "Code action not found" . firstJust (caWithTitle "Remove A from import")
995+
=<< getCodeActions docB (Range (Position 2 0) (Position 2 5))
999996
executeCodeAction action
1000997
contentAfterAction <- documentContents docB
1001998
let expectedContentAfterAction = T.unlines
@@ -1020,9 +1017,8 @@ removeImportTests = testGroup "remove import actions"
10201017
]
10211018
docB <- createDoc "ModuleB.hs" "haskell" contentB
10221019
_ <- waitForDiagnostics
1023-
[CACodeAction action@CodeAction { _title = actionTitle }, _]
1024-
<- getCodeActions docB (Range (Position 2 0) (Position 2 5))
1025-
liftIO $ "Remove A, E, F from import" @=? actionTitle
1020+
action <- assertJust "Code action not found" . firstJust (caWithTitle "Remove A, E, F from import")
1021+
=<< getCodeActions docB (Range (Position 2 0) (Position 2 5))
10261022
executeCodeAction action
10271023
contentAfterAction <- documentContents docB
10281024
let expectedContentAfterAction = T.unlines
@@ -1044,9 +1040,8 @@ removeImportTests = testGroup "remove import actions"
10441040
]
10451041
docB <- createDoc "ModuleB.hs" "haskell" contentB
10461042
_ <- waitForDiagnostics
1047-
[CACodeAction action@CodeAction { _title = actionTitle }, _]
1048-
<- getCodeActions docB (Range (Position 2 0) (Position 2 5))
1049-
liftIO $ "Remove import" @=? actionTitle
1043+
action <- assertJust "Code action not found" . firstJust (caWithTitle "Remove import")
1044+
=<< getCodeActions docB (Range (Position 2 0) (Position 2 5))
10501045
executeCodeAction action
10511046
contentAfterAction <- documentContents docB
10521047
let expectedContentAfterAction = T.unlines
@@ -1069,9 +1064,8 @@ removeImportTests = testGroup "remove import actions"
10691064
]
10701065
doc <- createDoc "ModuleC.hs" "haskell" content
10711066
_ <- waitForDiagnostics
1072-
[_, _, _, _, CACodeAction action@CodeAction { _title = actionTitle }]
1073-
<- getCodeActions doc (Range (Position 2 0) (Position 2 5))
1074-
liftIO $ "Remove all redundant imports" @=? actionTitle
1067+
action <- assertJust "Code action not found" . firstJust (caWithTitle "Remove all redundant imports")
1068+
=<< getCodeActions doc (Range (Position 2 0) (Position 2 5))
10751069
executeCodeAction action
10761070
contentAfterAction <- documentContents doc
10771071
let expectedContentAfterAction = T.unlines
@@ -1087,6 +1081,10 @@ removeImportTests = testGroup "remove import actions"
10871081
]
10881082
liftIO $ expectedContentAfterAction @=? contentAfterAction
10891083
]
1084+
where
1085+
caWithTitle t = \case
1086+
CACodeAction a@CodeAction{_title} -> guard (_title == t) >> Just a
1087+
_ -> Nothing
10901088

10911089
extendImportTests :: TestTree
10921090
extendImportTests = testGroup "extend import actions"
@@ -1441,6 +1439,57 @@ suggestImportTests = testGroup "suggest import actions"
14411439
else
14421440
liftIO $ [_title | CACodeAction CodeAction{_title} <- actions, _title == newImp ] @?= []
14431441

1442+
disableWarningTests :: TestTree
1443+
disableWarningTests =
1444+
testGroup "disable warnings" $
1445+
[
1446+
( "missing-signatures"
1447+
, T.unlines
1448+
[ "{-# OPTIONS_GHC -Wall #-}"
1449+
, "main = putStrLn \"hello\""
1450+
]
1451+
, T.unlines
1452+
[ "{-# OPTIONS_GHC -Wall #-}"
1453+
, "{-# OPTIONS_GHC -Wno-missing-signatures #-}"
1454+
, "main = putStrLn \"hello\""
1455+
]
1456+
)
1457+
,
1458+
( "unused-imports"
1459+
, T.unlines
1460+
[ "{-# OPTIONS_GHC -Wall #-}"
1461+
, ""
1462+
, ""
1463+
, "module M where"
1464+
, ""
1465+
, "import Data.Functor"
1466+
]
1467+
, T.unlines
1468+
[ "{-# OPTIONS_GHC -Wall #-}"
1469+
, "{-# OPTIONS_GHC -Wno-unused-imports #-}"
1470+
, ""
1471+
, ""
1472+
, "module M where"
1473+
, ""
1474+
, "import Data.Functor"
1475+
]
1476+
)
1477+
]
1478+
<&> \(warning, initialContent, expectedContent) -> testSession (T.unpack warning) $ do
1479+
doc <- createDoc "Module.hs" "haskell" initialContent
1480+
_ <- waitForDiagnostics
1481+
codeActs <- mapMaybe caResultToCodeAct <$> getCodeActions doc (Range (Position 0 0) (Position 0 0))
1482+
case find (\CodeAction{_title} -> _title == "Disable \"" <> warning <> "\" warnings") codeActs of
1483+
Nothing -> liftIO $ assertFailure "No code action with expected title"
1484+
Just action -> do
1485+
executeCodeAction action
1486+
contentAfterAction <- documentContents doc
1487+
liftIO $ expectedContent @=? contentAfterAction
1488+
where
1489+
caResultToCodeAct = \case
1490+
CACommand _ -> Nothing
1491+
CACodeAction c -> Just c
1492+
14441493
insertNewDefinitionTests :: TestTree
14451494
insertNewDefinitionTests = testGroup "insert new definition actions"
14461495
[ testSession "insert new function definition" $ do
@@ -2192,7 +2241,12 @@ removeRedundantConstraintsTests = let
21922241
doc <- createDoc "Testing.hs" "haskell" code
21932242
_ <- waitForDiagnostics
21942243
actionsOrCommands <- getCodeActions doc (Range (Position 4 0) (Position 4 maxBound))
2195-
liftIO $ assertBool "Found some actions" (null actionsOrCommands)
2244+
liftIO $ assertBool "Found some actions (other than \"disable warnings\")"
2245+
$ all isDisableWarningAction actionsOrCommands
2246+
where
2247+
isDisableWarningAction = \case
2248+
CACodeAction CodeAction{_title} -> "Disable" `T.isPrefixOf` _title && "warnings" `T.isSuffixOf` _title
2249+
_ -> False
21962250

21972251
in testGroup "remove redundant function constraints"
21982252
[ check
@@ -4037,7 +4091,10 @@ asyncTests = testGroup "async"
40374091
]
40384092
void waitForDiagnostics
40394093
actions <- getCodeActions doc (Range (Position 1 0) (Position 1 0))
4040-
liftIO $ [ _title | CACodeAction CodeAction{_title} <- actions] @=? ["add signature: foo :: a -> a"]
4094+
liftIO $ [ _title | CACodeAction CodeAction{_title} <- actions] @=?
4095+
[ "add signature: foo :: a -> a"
4096+
, "Disable \"missing-signatures\" warnings"
4097+
]
40414098
, testSession "request" $ do
40424099
-- Execute a custom request that will block for 1000 seconds
40434100
void $ sendRequest (CustomClientMethod "test") $ BlockSeconds 1000
@@ -4048,7 +4105,10 @@ asyncTests = testGroup "async"
40484105
]
40494106
void waitForDiagnostics
40504107
actions <- getCodeActions doc (Range (Position 0 0) (Position 0 0))
4051-
liftIO $ [ _title | CACodeAction CodeAction{_title} <- actions] @=? ["add signature: foo :: a -> a"]
4108+
liftIO $ [ _title | CACodeAction CodeAction{_title} <- actions] @=?
4109+
[ "add signature: foo :: a -> a"
4110+
, "Disable \"missing-signatures\" warnings"
4111+
]
40524112
]
40534113

40544114

@@ -4425,3 +4485,9 @@ withTempDir :: (FilePath -> IO a) -> IO a
44254485
withTempDir f = System.IO.Extra.withTempDir $ \dir -> do
44264486
dir' <- canonicalizePath dir
44274487
f dir'
4488+
4489+
-- | Assert that a value is not 'Nothing', and extract the value.
4490+
assertJust :: MonadIO m => String -> Maybe a -> m a
4491+
assertJust s = \case
4492+
Nothing -> liftIO $ assertFailure s
4493+
Just x -> pure x

test/functional/Class.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ tests = testGroup
3232
@?=
3333
[ Just "Add placeholders for '=='"
3434
, Just "Add placeholders for '/='"
35+
, Just "Disable \"missing-methods\" warnings"
3536
]
3637
, glodenTest "Creates a placeholder for '=='" "T1" "eq"
3738
$ \(eqAction:_) -> do

test/functional/FunctionalCodeAction.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -367,7 +367,7 @@ redundantImportTests = testGroup "redundant import code actions" [
367367
, testCase "doesn't touch other imports" $ runSession hlsCommand noLiteralCaps "test/testdata/redundantImportTest/" $ do
368368
doc <- openDoc "src/MultipleImports.hs" "haskell"
369369
_ <- waitForDiagnosticsFromSource doc "typecheck"
370-
CACommand cmd : _ <- getAllCodeActions doc
370+
_ : CACommand cmd : _ <- getAllCodeActions doc
371371
executeCommand cmd
372372
contents <- documentContents doc
373373
liftIO $ T.lines contents @?=

0 commit comments

Comments
 (0)