Skip to content
This repository was archived by the owner on Oct 7, 2020. It is now read-only.

Commit 6d12938

Browse files
authored
Merge pull request #889 from meck/actionUnusedTerm
Quickfix action to prefix unused terms with '_'
2 parents 024cde6 + 6ca6124 commit 6d12938

File tree

4 files changed

+65
-0
lines changed

4 files changed

+65
-0
lines changed

src/Haskell/Ide/Engine/Plugin/GhcMod.hs

Lines changed: 31 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -410,10 +410,13 @@ codeActionProvider' supportsDocChanges _ docId _ _ _ context =
410410
typedHoleActions = concatMap mkTypedHoleActions (mapMaybe getTypedHoles diags)
411411
missingSignatures = mapMaybe getMissingSignatures diags
412412
topLevelSignatureActions = map (uncurry mkMissingSignatureAction) missingSignatures
413+
unusedTerms = mapMaybe getUnusedTerms diags
414+
unusedTermActions = map (uncurry mkUnusedTermAction) unusedTerms
413415
in return $ IdeResultOk $ concat [ renameActions
414416
, redundantActions
415417
, typedHoleActions
416418
, topLevelSignatureActions
419+
, unusedTermActions
417420
]
418421

419422
where
@@ -512,6 +515,26 @@ codeActionProvider' supportsDocChanges _ docId _ _ _ context =
512515
kind = LSP.CodeActionQuickFix
513516
codeAction = LSP.CodeAction title (Just kind) (Just diags) (Just edit) Nothing
514517

518+
getUnusedTerms :: LSP.Diagnostic -> Maybe (LSP.Diagnostic, T.Text)
519+
getUnusedTerms diag@(LSP.Diagnostic _ _ _ (Just "ghcmod") msg _) =
520+
case extractUnusedTerm msg of
521+
Nothing -> Nothing
522+
Just signature -> Just (diag, signature)
523+
getUnusedTerms _ = Nothing
524+
525+
mkUnusedTermAction :: LSP.Diagnostic -> T.Text -> LSP.CodeAction
526+
mkUnusedTermAction diag term = LSP.CodeAction title (Just kind) (Just diags) Nothing (Just cmd)
527+
where title :: T.Text
528+
title = "Prefix " <> term <> " with _"
529+
diags = LSP.List [diag]
530+
newTerm = "_" <> term
531+
pos = diag ^. (LSP.range . LSP.start)
532+
kind = LSP.CodeActionQuickFix
533+
cmdArgs = LSP.List
534+
[ Object $ HM.fromList [("file", toJSON docUri),("pos", toJSON pos), ("text", toJSON newTerm)]]
535+
-- The command label isen't used since the command is never presented to the user
536+
cmd = LSP.Command "Unused command label" "hare:rename" (Just cmdArgs)
537+
515538
extractRenamableTerms :: T.Text -> [T.Text]
516539
extractRenamableTerms msg
517540
-- Account for both "Variable not in scope" and "Not in scope"
@@ -601,6 +624,14 @@ extractMissingSignature msg = extractSignature <$> stripMessageStart msg
601624
. T.strip
602625
extractSignature = T.strip
603626

627+
extractUnusedTerm :: T.Text -> Maybe T.Text
628+
extractUnusedTerm msg = extractTerm <$> stripMessageStart msg
629+
where
630+
stripMessageStart = T.stripPrefix "Defined but not used:"
631+
. T.strip
632+
extractTerm = T.dropWhile (== '')
633+
. T.dropWhileEnd (== '')
634+
. T.dropAround (\c -> c /= '' && c /= '')
604635

605636
-- ---------------------------------------------------------------------
606637

test/functional/FunctionalCodeActionsSpec.hs

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -301,6 +301,29 @@ spec = describe "code actions" $ do
301301

302302
liftIO $ contents `shouldBe` expected
303303

304+
describe "unused term code actions" $
305+
it "Prefixes with '_'" $
306+
runSession hieCommand fullCaps "test/testdata/" $ do
307+
doc <- openDoc "UnusedTerm.hs" "haskell"
308+
309+
_ <- waitForDiagnosticsSource "ghcmod"
310+
cas <- map fromAction <$> getAllCodeActions doc
311+
312+
liftIO $ map (^. L.title) cas `shouldContain` [ "Prefix imUnused with _"]
313+
314+
executeCodeAction $ head cas
315+
316+
edit <- getDocumentEdit doc
317+
318+
let expected = "{-# OPTIONS_GHC -Wall #-}\n\
319+
\module UnusedTerm () where\n\
320+
\_imUnused :: Int -> Int\n\
321+
\_imUnused 1 = 1\n\
322+
\_imUnused 2 = 2\n\
323+
\_imUnused _ = 3\n"
324+
325+
liftIO $ edit `shouldBe` expected
326+
304327
fromAction :: CAResult -> CodeAction
305328
fromAction (CACodeAction action) = action
306329
fromAction _ = error "Not a code action"

test/testdata/UnusedTerm.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
{-# OPTIONS_GHC -Wall #-}
2+
module UnusedTerm () where
3+
imUnused :: Int -> Int
4+
imUnused 1 = 1
5+
imUnused 2 = 2
6+
imUnused _ = 3

test/unit/CodeActionsSpec.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -146,3 +146,8 @@ spec = do
146146
\ Text.Megaparsec.Error.ShowErrorComponent e, Ord t) =>\n\
147147
\ OutputFormat -> Format.Result t e -> IO b"
148148
in extractMissingSignature msg `shouldBe` Just expected
149+
150+
describe "unused term code actions" $ do
151+
it "pick up unused term" $
152+
let msg = " Defined but not used: ‘imUnused’"
153+
in extractUnusedTerm msg `shouldBe` Just "imUnused"

0 commit comments

Comments
 (0)