Skip to content

Commit eb81835

Browse files
committed
Add code action for fixing misspelled variable names
The suggestions are extracted from GHC's error messages. To make parsing these error messages easier, we set the flag useUnicode=True, which makes GHC always use “smart quotes”.
1 parent f66c886 commit eb81835

File tree

3 files changed

+151
-7
lines changed

3 files changed

+151
-7
lines changed

src/Development/IDE/GHC/Util.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ runGhcEnv :: HscEnv -> Ghc a -> IO a
7272
runGhcEnv env act = do
7373
filesToClean <- newIORef emptyFilesToClean
7474
dirsToClean <- newIORef mempty
75-
let dflags = (hsc_dflags env){filesToClean=filesToClean, dirsToClean=dirsToClean}
75+
let dflags = (hsc_dflags env){filesToClean=filesToClean, dirsToClean=dirsToClean, useUnicode=True}
7676
ref <- newIORef env{hsc_dflags=dflags}
7777
unGhc act (Session ref) `finally` do
7878
cleanTempFiles dflags

src/Development/IDE/LSP/CodeAction.hs

Lines changed: 68 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ import Language.Haskell.LSP.VFS
1919
import Language.Haskell.LSP.Messages
2020
import qualified Data.Rope.UTF16 as Rope
2121
import Data.Char
22+
import Data.Maybe
2223
import qualified Data.Text as T
2324

2425
-- | Generate code actions.
@@ -48,9 +49,21 @@ suggestAction contents Diagnostic{_range=_range@Range{..},..}
4849
-- To import instances alone, use: import Data.List()
4950
| "The import of " `T.isInfixOf` _message
5051
, " is redundant" `T.isInfixOf` _message
51-
, let newlineAfter = maybe False (T.isPrefixOf "\n" . T.dropWhile (\x -> isSpace x && x /= '\n') . snd . textAtPosition _end) contents
52-
, let extend = newlineAfter && _character _start == 0 -- takes up an entire line, so remove the whole line
53-
= [("Remove import", [TextEdit (if extend then Range _start (Position (_line _end + 1) 0) else _range) ""])]
52+
= [("Remove import", [TextEdit (extendToWholeLineIfPossible contents _range) ""])]
53+
54+
-- File.hs:52:41: error:
55+
-- * Variable not in scope:
56+
-- suggestAcion :: Maybe T.Text -> Range -> Range
57+
-- * Perhaps you meant ‘suggestAction’ (line 83)
58+
-- File.hs:94:37: error:
59+
-- Not in scope: ‘T.isPrfixOf’
60+
-- Perhaps you meant one of these:
61+
-- ‘T.isPrefixOf’ (imported from Data.Text),
62+
-- ‘T.isInfixOf’ (imported from Data.Text),
63+
-- ‘T.isSuffixOf’ (imported from Data.Text)
64+
-- Module ‘Data.Text’ does not export ‘isPrfixOf’.
65+
| renameSuggestions@(_:_) <- extractRenamableTerms _message
66+
= [ ("Replace with ‘" <> name <> "", [mkRenameEdit contents _range name]) | name <- renameSuggestions ]
5467

5568
-- File.hs:22:8: error:
5669
-- Illegal lambda-case (use -XLambdaCase)
@@ -77,19 +90,68 @@ suggestAction contents Diagnostic{_range=_range@Range{..},..}
7790

7891
suggestAction _ _ = []
7992

93+
mkRenameEdit :: Maybe T.Text -> Range -> T.Text -> TextEdit
94+
mkRenameEdit contents range name =
95+
if fromMaybe False maybeIsInfixFunction
96+
then TextEdit range ("`" <> name <> "`")
97+
else TextEdit range name
98+
where
99+
maybeIsInfixFunction = do
100+
curr <- textInRange range <$> contents
101+
pure $ "`" `T.isPrefixOf` curr && "`" `T.isSuffixOf` curr
102+
103+
104+
extractRenamableTerms :: T.Text -> [T.Text]
105+
extractRenamableTerms msg
106+
-- Account for both "Variable not in scope" and "Not in scope"
107+
| "ot in scope:" `T.isInfixOf` msg = extractSuggestions msg
108+
| otherwise = []
109+
where
110+
extractSuggestions = map getEnclosed
111+
. concatMap singleSuggestions
112+
. filter isKnownSymbol
113+
. T.lines
114+
singleSuggestions = T.splitOn "), " -- Each suggestion is comma delimited
115+
isKnownSymbol t = " (imported from" `T.isInfixOf` t || " (line " `T.isInfixOf` t
116+
getEnclosed = T.dropWhile (== '')
117+
. T.dropWhileEnd (== '')
118+
. T.dropAround (\c -> c /= '' && c /= '')
119+
120+
-- | If a range takes up a whole line (it begins at the start of the line and there's only whitespace
121+
-- between the end of the range and the next newline), extend the range to take up the whole line.
122+
extendToWholeLineIfPossible :: Maybe T.Text -> Range -> Range
123+
extendToWholeLineIfPossible contents range@Range{..} =
124+
let newlineAfter = maybe False (T.isPrefixOf "\n" . T.dropWhile (\x -> isSpace x && x /= '\n') . snd . splitTextAtPosition _end) contents
125+
extend = newlineAfter && _character _start == 0 -- takes up an entire line, so remove the whole line
126+
in if extend then Range _start (Position (_line _end + 1) 0) else range
80127

81128
-- | All the GHC extensions
82129
ghcExtensions :: Set.HashSet T.Text
83130
ghcExtensions = Set.fromList $ map (T.pack . show) ghcEnumerateExtensions
84131

85-
86-
textAtPosition :: Position -> T.Text -> (T.Text, T.Text)
87-
textAtPosition (Position row col) x
132+
splitTextAtPosition :: Position -> T.Text -> (T.Text, T.Text)
133+
splitTextAtPosition (Position row col) x
88134
| (preRow, mid:postRow) <- splitAt row $ T.splitOn "\n" x
89135
, (preCol, postCol) <- T.splitAt col mid
90136
= (T.intercalate "\n" $ preRow ++ [preCol], T.intercalate "\n" $ postCol : postRow)
91137
| otherwise = (x, T.empty)
92138

139+
textInRange :: Range -> T.Text -> T.Text
140+
textInRange (Range (Position startRow startCol) (Position endRow endCol)) text =
141+
case compare startRow endRow of
142+
LT ->
143+
let (linesInRangeBeforeEndLine, endLineAndFurtherLines) = splitAt (endRow - startRow) linesBeginningWithStartLine
144+
(textInRangeInFirstLine, linesBetween) = case linesInRangeBeforeEndLine of
145+
[] -> ("", [])
146+
firstLine:linesInBetween -> (T.drop startCol firstLine, linesInBetween)
147+
maybeTextInRangeInEndLine = T.take endCol <$> listToMaybe endLineAndFurtherLines
148+
in T.intercalate "\n" (textInRangeInFirstLine : linesBetween ++ maybeToList maybeTextInRangeInEndLine)
149+
EQ ->
150+
let line = fromMaybe "" (listToMaybe linesBeginningWithStartLine)
151+
in T.take (endCol - startCol) (T.drop startCol line)
152+
GT -> ""
153+
where
154+
linesBeginningWithStartLine = drop startRow (T.splitOn "\n" text)
93155

94156
setHandlersCodeAction :: PartialHandlers
95157
setHandlersCodeAction = PartialHandlers $ \WithMessage{..} x -> return x{

test/exe/Main.hs

Lines changed: 82 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66
module Main (main) where
77

88
import Control.Monad (void)
9+
import Control.Monad.IO.Class (liftIO)
910
import qualified Data.Text as T
1011
import Development.IDE.Test
1112
import Development.IDE.Test.Runfiles
@@ -26,6 +27,7 @@ main = defaultMain $ testGroup "HIE"
2627
closeDoc doc
2728
void (message :: Session ProgressDoneNotification)
2829
, diagnosticTests
30+
, codeActionTests
2931
]
3032

3133

@@ -182,6 +184,86 @@ diagnosticTests = testGroup "diagnostics"
182184
]
183185
]
184186

187+
codeActionTests :: TestTree
188+
codeActionTests = testGroup "code actions"
189+
[ renameActionTests
190+
]
191+
192+
renameActionTests :: TestTree
193+
renameActionTests = testGroup "rename actions"
194+
[ testSession "change to local variable name" $ do
195+
let content = T.unlines
196+
[ "module Testing where"
197+
, "foo :: Int -> Int"
198+
, "foo argName = argNme"
199+
]
200+
doc <- openDoc' "Testing.hs" "haskell" content
201+
_ <- waitForDiagnostics
202+
[CACodeAction action@CodeAction { _title = actionTitle }]
203+
<- getCodeActions doc (Range (Position 2 14) (Position 2 20))
204+
liftIO $ "Replace with ‘argName’" @=? actionTitle
205+
executeCodeAction action
206+
contentAfterAction <- documentContents doc
207+
let expectedContentAfterAction = T.unlines
208+
[ "module Testing where"
209+
, "foo :: Int -> Int"
210+
, "foo argName = argName"
211+
]
212+
liftIO $ expectedContentAfterAction @=? contentAfterAction
213+
, testSession "change to name of imported function" $ do
214+
let content = T.unlines
215+
[ "module Testing where"
216+
, "import Data.Maybe (maybeToList)"
217+
, "foo :: Maybe a -> [a]"
218+
, "foo = maybToList"
219+
]
220+
doc <- openDoc' "Testing.hs" "haskell" content
221+
_ <- waitForDiagnostics
222+
[CACodeAction action@CodeAction { _title = actionTitle }]
223+
<- getCodeActions doc (Range (Position 3 6) (Position 3 16))
224+
liftIO $ "Replace with ‘maybeToList’" @=? actionTitle
225+
executeCodeAction action
226+
contentAfterAction <- documentContents doc
227+
let expectedContentAfterAction = T.unlines
228+
[ "module Testing where"
229+
, "import Data.Maybe (maybeToList)"
230+
, "foo :: Maybe a -> [a]"
231+
, "foo = maybeToList"
232+
]
233+
liftIO $ expectedContentAfterAction @=? contentAfterAction
234+
, testSession "suggest multiple local variable names" $ do
235+
let content = T.unlines
236+
[ "module Testing where"
237+
, "foo :: Char -> Char -> Char -> Char"
238+
, "foo argument1 argument2 argument3 = argumentX"
239+
]
240+
doc <- openDoc' "Testing.hs" "haskell" content
241+
_ <- waitForDiagnostics
242+
actionsOrCommands <- getCodeActions doc (Range (Position 2 36) (Position 2 45))
243+
let actionTitles = [ actionTitle | CACodeAction CodeAction{ _title = actionTitle } <- actionsOrCommands ]
244+
expectedActionTitles = ["Replace with ‘argument1’", "Replace with ‘argument2’", "Replace with ‘argument3’"]
245+
liftIO $ expectedActionTitles @=? actionTitles
246+
, testSession "change infix function" $ do
247+
let content = T.unlines
248+
[ "module Testing where"
249+
, "monus :: Int -> Int"
250+
, "monus x y = max 0 (x - y)"
251+
, "foo x y = x `monnus` y"
252+
]
253+
doc <- openDoc' "Testing.hs" "haskell" content
254+
_ <- waitForDiagnostics
255+
actionsOrCommands <- getCodeActions doc (Range (Position 3 12) (Position 3 20))
256+
[fixTypo] <- pure [action | CACodeAction action@CodeAction{ _title = actionTitle } <- actionsOrCommands, "monus" `T.isInfixOf` actionTitle ]
257+
executeCodeAction fixTypo
258+
contentAfterAction <- documentContents doc
259+
let expectedContentAfterAction = T.unlines
260+
[ "module Testing where"
261+
, "monus :: Int -> Int"
262+
, "monus x y = max 0 (x - y)"
263+
, "foo x y = x `monus` y"
264+
]
265+
liftIO $ expectedContentAfterAction @=? contentAfterAction
266+
]
185267

186268
----------------------------------------------------------------------
187269
-- Utils

0 commit comments

Comments
 (0)