@@ -19,6 +19,7 @@ import Language.Haskell.LSP.VFS
1919import Language.Haskell.LSP.Messages
2020import qualified Data.Rope.UTF16 as Rope
2121import Data.Char
22+ import Data.Maybe
2223import 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
7891suggestAction _ _ = []
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
82129ghcExtensions :: Set. HashSet T. Text
83130ghcExtensions = 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
94156setHandlersCodeAction :: PartialHandlers
95157setHandlersCodeAction = PartialHandlers $ \ WithMessage {.. } x -> return x{
0 commit comments