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

Quickfix action to prefix unused terms with '_' #889

Merged
merged 1 commit into from
Oct 23, 2018
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
31 changes: 31 additions & 0 deletions src/Haskell/Ide/Engine/Plugin/GhcMod.hs
Original file line number Diff line number Diff line change
Expand Up @@ -410,10 +410,13 @@ codeActionProvider' supportsDocChanges _ docId _ _ _ context =
typedHoleActions = concatMap mkTypedHoleActions (mapMaybe getTypedHoles diags)
missingSignatures = mapMaybe getMissingSignatures diags
topLevelSignatureActions = map (uncurry mkMissingSignatureAction) missingSignatures
unusedTerms = mapMaybe getUnusedTerms diags
unusedTermActions = map (uncurry mkUnusedTermAction) unusedTerms
in return $ IdeResultOk $ concat [ renameActions
, redundantActions
, typedHoleActions
, topLevelSignatureActions
, unusedTermActions
]

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

getUnusedTerms :: LSP.Diagnostic -> Maybe (LSP.Diagnostic, T.Text)
getUnusedTerms diag@(LSP.Diagnostic _ _ _ (Just "ghcmod") msg _) =
case extractUnusedTerm msg of
Nothing -> Nothing
Just signature -> Just (diag, signature)
getUnusedTerms _ = Nothing

mkUnusedTermAction :: LSP.Diagnostic -> T.Text -> LSP.CodeAction
mkUnusedTermAction diag term = LSP.CodeAction title (Just kind) (Just diags) Nothing (Just cmd)
where title :: T.Text
title = "Prefix " <> term <> " with _"
diags = LSP.List [diag]
newTerm = "_" <> term
pos = diag ^. (LSP.range . LSP.start)
kind = LSP.CodeActionQuickFix
cmdArgs = LSP.List
[ Object $ HM.fromList [("file", toJSON docUri),("pos", toJSON pos), ("text", toJSON newTerm)]]
-- The command label isen't used since the command is never presented to the user
cmd = LSP.Command "Unused command label" "hare:rename" (Just cmdArgs)
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I love being able to do hare:rename as a command.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Yes! I started by importing hare, then thought wait a minute...


extractRenamableTerms :: T.Text -> [T.Text]
extractRenamableTerms msg
-- Account for both "Variable not in scope" and "Not in scope"
Expand Down Expand Up @@ -601,6 +624,14 @@ extractMissingSignature msg = extractSignature <$> stripMessageStart msg
. T.strip
extractSignature = T.strip

extractUnusedTerm :: T.Text -> Maybe T.Text
extractUnusedTerm msg = extractTerm <$> stripMessageStart msg
where
stripMessageStart = T.stripPrefix "Defined but not used:"
. T.strip
extractTerm = T.dropWhile (== '‘')
. T.dropWhileEnd (== '’')
. T.dropAround (\c -> c /= '‘' && c /= '’')

-- ---------------------------------------------------------------------

Expand Down
23 changes: 23 additions & 0 deletions test/functional/FunctionalCodeActionsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -301,6 +301,29 @@ spec = describe "code actions" $ do

liftIO $ contents `shouldBe` expected

describe "unused term code actions" $
it "Prefixes with '_'" $
runSession hieCommand fullCaps "test/testdata/" $ do
doc <- openDoc "UnusedTerm.hs" "haskell"

_ <- waitForDiagnosticsSource "ghcmod"
cas <- map fromAction <$> getAllCodeActions doc

liftIO $ map (^. L.title) cas `shouldContain` [ "Prefix imUnused with _"]

executeCodeAction $ head cas

edit <- getDocumentEdit doc

let expected = "{-# OPTIONS_GHC -Wall #-}\n\
\module UnusedTerm () where\n\
\_imUnused :: Int -> Int\n\
\_imUnused 1 = 1\n\
\_imUnused 2 = 2\n\
\_imUnused _ = 3\n"

liftIO $ edit `shouldBe` expected

fromAction :: CAResult -> CodeAction
fromAction (CACodeAction action) = action
fromAction _ = error "Not a code action"
Expand Down
6 changes: 6 additions & 0 deletions test/testdata/UnusedTerm.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
{-# OPTIONS_GHC -Wall #-}
module UnusedTerm () where
imUnused :: Int -> Int
imUnused 1 = 1
imUnused 2 = 2
imUnused _ = 3
5 changes: 5 additions & 0 deletions test/unit/CodeActionsSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -146,3 +146,8 @@ spec = do
\ Text.Megaparsec.Error.ShowErrorComponent e, Ord t) =>\n\
\ OutputFormat -> Format.Result t e -> IO b"
in extractMissingSignature msg `shouldBe` Just expected

describe "unused term code actions" $ do
it "pick up unused term" $
let msg = " Defined but not used: ‘imUnused’"
in extractUnusedTerm msg `shouldBe` Just "imUnused"