{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE CPP #-}
#include "ghc-api-version.h"
module Development.IDE.Plugin.CodeAction
(
plugin
, codeAction
, codeLens
, rulePackageExports
, executeAddSignatureCommand
) where
import Control.Monad (join, guard)
import Development.IDE.Plugin
import Development.IDE.GHC.Compat
import Development.IDE.Core.Rules
import Development.IDE.Core.RuleTypes
import Development.IDE.Core.Service
import Development.IDE.Core.Shake
import Development.IDE.GHC.Error
import Development.IDE.GHC.Util
import Development.IDE.LSP.Server
import Development.IDE.Plugin.CodeAction.PositionIndexed
import Development.IDE.Plugin.CodeAction.RuleTypes
import Development.IDE.Plugin.CodeAction.Rules
import Development.IDE.Types.Location
import Development.IDE.Types.Options
import Development.Shake (Rules)
import qualified Data.HashMap.Strict as Map
import qualified Language.Haskell.LSP.Core as LSP
import Language.Haskell.LSP.VFS
import Language.Haskell.LSP.Messages
import Language.Haskell.LSP.Types
import qualified Data.Rope.UTF16 as Rope
import Data.Aeson.Types (toJSON, fromJSON, Value(..), Result(..))
import Data.Char
import Data.Maybe
import Data.List.Extra
import qualified Data.Text as T
import Data.Tuple.Extra ((&&&))
import HscTypes
import SrcLoc (sortLocated)
import Parser
import Text.Regex.TDFA ((=~), (=~~))
import Text.Regex.TDFA.Text()
import Outputable (ppr, showSDocUnsafe)
import DynFlags (xFlags, FlagSpec(..))
import GHC.LanguageExtensions.Type (Extension)
import Data.Function
import Control.Arrow ((>>>))
import Data.Functor
import Control.Applicative ((<|>))
import Safe (atMay)
plugin :: Plugin c
plugin = codeActionPluginWithRules rules codeAction <> Plugin mempty setHandlersCodeLens
rules :: Rules ()
rules = rulePackageExports
codeAction
:: LSP.LspFuncs c
-> IdeState
-> TextDocumentIdentifier
-> Range
-> CodeActionContext
-> IO (Either ResponseError [CAResult])
codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext{_diagnostics=List xs} = do
contents <- LSP.getVirtualFileFunc lsp $ toNormalizedUri uri
let text = Rope.toText . (_text :: VirtualFile -> Rope.Rope) <$> contents
mbFile = toNormalizedFilePath' <$> uriToFilePath uri
(ideOptions, parsedModule, join -> env) <- runAction "CodeAction" state $
(,,) <$> getIdeOptions
<*> getParsedModule `traverse` mbFile
<*> use GhcSession `traverse` mbFile
pkgExports <- runAction "CodeAction:PackageExports" state $ (useNoFile_ . PackageExports) `traverse` env
let dflags = hsc_dflags . hscEnv <$> env
pure $ Right
[ CACodeAction $ CodeAction title (Just CodeActionQuickFix) (Just $ List [x]) (Just edit) Nothing
| x <- xs, (title, tedit) <- suggestAction dflags (fromMaybe mempty pkgExports) ideOptions ( join parsedModule ) text x
, let edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing
]
codeLens
:: LSP.LspFuncs c
-> IdeState
-> CodeLensParams
-> IO (Either ResponseError (List CodeLens))
codeLens _lsp ideState CodeLensParams{_textDocument=TextDocumentIdentifier uri} = do
commandId <- makeLspCommandId "typesignature.add"
fmap (Right . List) $ case uriToFilePath' uri of
Just (toNormalizedFilePath' -> filePath) -> do
_ <- runAction "codeLens" ideState (use TypeCheck filePath)
diag <- getDiagnostics ideState
hDiag <- getHiddenDiagnostics ideState
pure
[ CodeLens _range (Just (Command title commandId (Just $ List [toJSON edit]))) Nothing
| (dFile, _, dDiag@Diagnostic{_range=_range}) <- diag ++ hDiag
, dFile == filePath
, (title, tedit) <- suggestSignature False dDiag
, let edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing
]
Nothing -> pure []
executeAddSignatureCommand
:: LSP.LspFuncs c
-> IdeState
-> ExecuteCommandParams
-> IO (Either ResponseError Value, Maybe (ServerMethod, ApplyWorkspaceEditParams))
executeAddSignatureCommand _lsp _ideState ExecuteCommandParams{..}
| T.isSuffixOf "typesignature.add" _command
, Just (List [edit]) <- _arguments
, Success wedit <- fromJSON edit
= return (Right Null, Just (WorkspaceApplyEdit, ApplyWorkspaceEditParams wedit))
| otherwise
= return (Right Null, Nothing)
suggestAction
:: Maybe DynFlags
-> PackageExportsMap
-> IdeOptions
-> Maybe ParsedModule
-> Maybe T.Text
-> Diagnostic
-> [(T.Text, [TextEdit])]
suggestAction dflags packageExports ideOptions parsedModule text diag = concat
[ suggestAddExtension diag
, suggestExtendImport dflags text diag
, suggestFillHole diag
, suggestFillTypeWildcard diag
, suggestFixConstructorImport text diag
, suggestModuleTypo diag
, suggestReplaceIdentifier text diag
, suggestSignature True diag
, suggestConstraint text diag
, removeRedundantConstraints text diag
, suggestAddTypeAnnotationToSatisfyContraints text diag
] ++ concat
[ suggestNewDefinition ideOptions pm text diag
++ suggestRemoveRedundantImport pm text diag
++ suggestNewImport packageExports pm diag
++ suggestDeleteTopBinding pm diag
++ suggestExportUnusedTopBinding text pm diag
| Just pm <- [parsedModule]]
suggestRemoveRedundantImport :: ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
suggestRemoveRedundantImport ParsedModule{pm_parsed_source = L _ HsModule{hsmodImports}} contents Diagnostic{_range=_range,..}
| Just [_, bindings] <- matchRegex _message "The( qualified)? import of ‘([^’]*)’ from module [^ ]* is redundant"
, Just (L _ impDecl) <- find (\(L l _) -> srcSpanToRange l == _range ) hsmodImports
, Just c <- contents
, ranges <- map (rangesForBinding impDecl . T.unpack) (T.splitOn ", " bindings)
, ranges' <- extendAllToIncludeCommaIfPossible (indexedByPosition $ T.unpack c) (concat ranges)
, not (null ranges')
= [( "Remove " <> bindings <> " from import" , [ TextEdit r "" | r <- ranges' ] )]
| _message =~ ("The( qualified)? import of [^ ]* is redundant" :: String)
= [("Remove import", [TextEdit (extendToWholeLineIfPossible contents _range) ""])]
| otherwise = []
suggestDeleteTopBinding :: ParsedModule -> Diagnostic -> [(T.Text, [TextEdit])]
suggestDeleteTopBinding ParsedModule{pm_parsed_source = L _ HsModule{hsmodDecls}} Diagnostic{_range=_range,..}
| Just [name] <- matchRegex _message ".*Defined but not used: ‘([^ ]+)’"
, let allTopLevel = filter (isTopLevel . fst)
. map (\(L l b) -> (srcSpanToRange l, b))
. sortLocated
$ hsmodDecls
sameName = filter (matchesBindingName (T.unpack name) . snd) allTopLevel
, not (null sameName)
= [("Delete ‘" <> name <> "’", flip TextEdit "" . toNextBinding allTopLevel . fst <$> sameName )]
| otherwise = []
where
isTopLevel l = (_character . _start) l == 0
forwardLines lines r = r {_end = (_end r) {_line = (_line . _end $ r) + lines, _character = 0}}
toNextBinding bindings r@Range { _end = Position {_line = l} }
| Just (Range { _start = Position {_line = l'}}, _) <- find ((> l) . _line . _start . fst) bindings
= forwardLines (l' - l) r
toNextBinding _ r = r
matchesBindingName :: String -> HsDecl GhcPs -> Bool
matchesBindingName b (ValD FunBind {fun_id=L _ x}) = showSDocUnsafe (ppr x) == b
matchesBindingName b (SigD (TypeSig (L _ x:_) _)) = showSDocUnsafe (ppr x) == b
matchesBindingName _ _ = False
data ExportsAs = ExportName | ExportPattern | ExportAll
deriving (Eq)
suggestExportUnusedTopBinding :: Maybe T.Text -> ParsedModule -> Diagnostic -> [(T.Text, [TextEdit])]
suggestExportUnusedTopBinding srcOpt ParsedModule{pm_parsed_source = L _ HsModule{..}} Diagnostic{..}
| Just source <- srcOpt
, Just [name] <- matchRegex _message ".*Defined but not used: ‘([^ ]+)’"
<|> matchRegex _message ".*Defined but not used: type constructor or class ‘([^ ]+)’"
<|> matchRegex _message ".*Defined but not used: data constructor ‘([^ ]+)’"
, Just (exportType, _) <- find (matchWithDiagnostic _range . snd)
. mapMaybe
(\(L l b) -> if isTopLevel $ srcSpanToRange l
then exportsAs b else Nothing)
$ hsmodDecls
, Just pos <- _end . getLocatedRange <$> hsmodExports
, Just needComma <- needsComma source <$> hsmodExports
, let exportName = (if needComma then "," else "") <> printExport exportType name
insertPos = pos {_character = pred $ _character pos}
= [("Export ‘" <> name <> "’", [TextEdit (Range insertPos insertPos) exportName])]
| otherwise = []
where
needsComma :: T.Text -> Located [LIE GhcPs] -> Bool
needsComma _ (L _ []) = False
needsComma source x@(L _ exports) =
let closeParan = _end $ getLocatedRange x
lastExport = _end . getLocatedRange $ last exports
in not $ T.isInfixOf "," $ textInRange (Range lastExport closeParan) source
getLocatedRange :: Located a -> Range
getLocatedRange = srcSpanToRange . getLoc
matchWithDiagnostic :: Range -> Located (IdP GhcPs) -> Bool
matchWithDiagnostic Range{_start=l,_end=r} x =
let loc = _start . getLocatedRange $ x
in loc >= l && loc <= r
printExport :: ExportsAs -> T.Text -> T.Text
printExport ExportName x = x
printExport ExportPattern x = "pattern " <> x
printExport ExportAll x = x <> "(..)"
isTopLevel :: Range -> Bool
isTopLevel l = (_character . _start) l == 0
exportsAs :: HsDecl p -> Maybe (ExportsAs, Located (IdP p))
exportsAs (ValD FunBind {fun_id}) = Just (ExportName, fun_id)
exportsAs (ValD (PatSynBind PSB {psb_id})) = Just (ExportPattern, psb_id)
exportsAs (TyClD SynDecl{tcdLName}) = Just (ExportName, tcdLName)
exportsAs (TyClD DataDecl{tcdLName}) = Just (ExportAll, tcdLName)
exportsAs (TyClD ClassDecl{tcdLName}) = Just (ExportAll, tcdLName)
exportsAs (TyClD FamDecl{tcdFam}) = Just (ExportAll, fdLName tcdFam)
exportsAs _ = Nothing
suggestAddTypeAnnotationToSatisfyContraints :: Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
suggestAddTypeAnnotationToSatisfyContraints sourceOpt Diagnostic{_range=_range,..}
| Just [ty, lit] <- matchRegex _message (pat False False True)
<|> matchRegex _message (pat False False False)
= codeEdit ty lit (makeAnnotatedLit ty lit)
| Just source <- sourceOpt
, Just [ty, lit] <- matchRegex _message (pat True True False)
= let lit' = makeAnnotatedLit ty lit;
tir = textInRange _range source
in codeEdit ty lit (T.replace lit lit' tir)
| otherwise = []
where
makeAnnotatedLit ty lit = "(" <> lit <> " :: " <> ty <> ")"
pat multiple at inThe = T.concat [ ".*Defaulting the following constraint"
, if multiple then "s" else ""
, " to type ‘([^ ]+)’ "
, ".*arising from the literal ‘(.+)’"
, if inThe then ".+In the.+argument" else ""
, if at then ".+at" else ""
, ".+In the expression"
]
codeEdit ty lit replacement =
let title = "Add type annotation ‘" <> ty <> "’ to ‘" <> lit <> "’"
edits = [TextEdit _range replacement]
in [( title, edits )]
suggestReplaceIdentifier :: Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
suggestReplaceIdentifier contents Diagnostic{_range=_range,..}
| renameSuggestions@(_:_) <- extractRenamableTerms _message
= [ ("Replace with ‘" <> name <> "’", [mkRenameEdit contents _range name]) | name <- renameSuggestions ]
| otherwise = []
suggestNewDefinition :: IdeOptions -> ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
suggestNewDefinition ideOptions parsedModule contents Diagnostic{_message, _range}
| Just [name, typ] <- matchRegex message "Variable not in scope: ([^ ]+) :: ([^*•]+)"
= newDefinitionAction ideOptions parsedModule _range name typ
| Just [name, typ] <- matchRegex message "Found hole: _([^ ]+) :: ([^*•]+) Or perhaps"
, [(label, newDefinitionEdits)] <- newDefinitionAction ideOptions parsedModule _range name typ
= [(label, mkRenameEdit contents _range name : newDefinitionEdits)]
| otherwise = []
where
message = unifySpaces _message
newDefinitionAction :: IdeOptions -> ParsedModule -> Range -> T.Text -> T.Text -> [(T.Text, [TextEdit])]
newDefinitionAction IdeOptions{..} parsedModule Range{_start} name typ
| Range _ lastLineP : _ <-
[ srcSpanToRange l
| (L l _) <- hsmodDecls
, _start `isInsideSrcSpan` l]
, nextLineP <- Position{ _line = _line lastLineP + 1, _character = 0}
= [ ("Define " <> sig
, [TextEdit (Range nextLineP nextLineP) (T.unlines ["", sig, name <> " = error \"not implemented\""])]
)]
| otherwise = []
where
colon = if optNewColonConvention then " : " else " :: "
sig = name <> colon <> T.dropWhileEnd isSpace typ
ParsedModule{pm_parsed_source = L _ HsModule{hsmodDecls}} = parsedModule
suggestFillTypeWildcard :: Diagnostic -> [(T.Text, [TextEdit])]
suggestFillTypeWildcard Diagnostic{_range=_range,..}
| "Found type wildcard" `T.isInfixOf` _message
, " standing for " `T.isInfixOf` _message
, typeSignature <- extractWildCardTypeSignature _message
= [("Use type signature: ‘" <> typeSignature <> "’", [TextEdit _range typeSignature])]
| otherwise = []
suggestAddExtension :: Diagnostic -> [(T.Text, [TextEdit])]
suggestAddExtension Diagnostic{_range=_range,..}
| exts@(_:_) <- filter (`Map.member` ghcExtensions) $ T.split (not . isAlpha) $ T.replace "-X" "" _message
= [("Add " <> x <> " extension", [TextEdit (Range (Position 0 0) (Position 0 0)) $ "{-# LANGUAGE " <> x <> " #-}\n"]) | x <- exts]
| otherwise = []
ghcExtensions :: Map.HashMap T.Text Extension
ghcExtensions = Map.fromList . filter notStrictFlag . map ( ( T.pack . flagSpecName ) &&& flagSpecFlag ) $ xFlags
where
notStrictFlag (name, _) = name /= "Strict"
suggestModuleTypo :: Diagnostic -> [(T.Text, [TextEdit])]
suggestModuleTypo Diagnostic{_range=_range,..}
| "Could not find module" `T.isInfixOf` _message
, "Perhaps you meant" `T.isInfixOf` _message = let
findSuggestedModules = map (head . T.words) . drop 2 . T.lines
proposeModule mod = ("replace with " <> mod, [TextEdit _range mod])
in map proposeModule $ nubOrd $ findSuggestedModules _message
| otherwise = []
suggestFillHole :: Diagnostic -> [(T.Text, [TextEdit])]
suggestFillHole Diagnostic{_range=_range,..}
| topOfHoleFitsMarker `T.isInfixOf` _message = let
findSuggestedHoleFits :: T.Text -> [T.Text]
findSuggestedHoleFits = extractFitNames . selectLinesWithFits . dropPreceding . T.lines
proposeHoleFit name = ("replace hole `" <> holeName <> "` with " <> name, [TextEdit _range name])
holeName = T.strip $ last $ T.splitOn ":" $ head . T.splitOn "::" $ head $ filter ("Found hole" `T.isInfixOf`) $ T.lines _message
dropPreceding = dropWhile (not . (topOfHoleFitsMarker `T.isInfixOf`))
selectLinesWithFits = filter ("::" `T.isInfixOf`)
extractFitNames = map (T.strip . head . T.splitOn " :: ")
in map proposeHoleFit $ nubOrd $ findSuggestedHoleFits _message
| otherwise = []
suggestExtendImport :: Maybe DynFlags -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
suggestExtendImport (Just dflags) contents Diagnostic{_range=_range,..}
| Just [binding, mod, srcspan] <-
matchRegex _message
"Perhaps you want to add ‘([^’]*)’ to the import list in the import of ‘([^’]*)’ *\\((.*)\\).$"
, Just c <- contents
, POk _ (L _ name) <- runParser dflags (T.unpack binding) parseIdentifier
= let range = case [ x | (x,"") <- readSrcSpan (T.unpack srcspan)] of
[s] -> let x = srcSpanToRange s
in x{_end = (_end x){_character = succ (_character (_end x))}}
_ -> error "bug in srcspan parser"
importLine = textInRange range c
in [("Add " <> binding <> " to the import list of " <> mod
, [TextEdit range (addBindingToImportList (T.pack $ printRdrName name) importLine)])]
| otherwise = []
suggestExtendImport Nothing _ _ = []
suggestFixConstructorImport :: Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
suggestFixConstructorImport _ Diagnostic{_range=_range,..}
| Just [constructor, typ] <-
matchRegex _message
"‘([^’]*)’ is a data constructor of ‘([^’]*)’ To import it use"
= let fixedImport = typ <> "(" <> constructor <> ")"
in [("Fix import of " <> fixedImport, [TextEdit _range fixedImport])]
| otherwise = []
suggestSignature :: Bool -> Diagnostic -> [(T.Text, [TextEdit])]
suggestSignature isQuickFix Diagnostic{_range=_range@Range{..},..}
| _message =~
("(Top-level binding|Polymorphic local binding|Pattern synonym) with no type signature" :: T.Text) = let
signature = removeInitialForAll
$ T.takeWhile (\x -> x/='*' && x/='•')
$ T.strip $ unifySpaces $ last $ T.splitOn "type signature: " $ filterNewlines _message
startOfLine = Position (_line _start) startCharacter
beforeLine = Range startOfLine startOfLine
title = if isQuickFix then "add signature: " <> signature else signature
action = TextEdit beforeLine $ signature <> "\n" <> T.replicate startCharacter " "
in [(title, [action])]
where removeInitialForAll :: T.Text -> T.Text
removeInitialForAll (T.breakOnEnd " :: " -> (nm, ty))
| "forall" `T.isPrefixOf` ty = nm <> T.drop 2 (snd (T.breakOn "." ty))
| otherwise = nm <> ty
startCharacter
| "Polymorphic local binding" `T.isPrefixOf` _message
= _character _start
| otherwise
= 0
suggestSignature _ _ = []
suggestConstraint :: Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
suggestConstraint mContents diag@Diagnostic {..}
| Just contents <- mContents
, Just missingConstraint <- findMissingConstraint _message
= let codeAction = if _message =~ ("the type signature for:" :: String)
then suggestFunctionConstraint
else suggestInstanceConstraint
in codeAction contents diag missingConstraint
| otherwise = []
where
findMissingConstraint :: T.Text -> Maybe T.Text
findMissingConstraint t =
let regex = "(No instance for|Could not deduce) \\((.+)\\) arising from a use of"
in matchRegex t regex <&> last
normalizeConstraints :: T.Text -> T.Text -> T.Text
normalizeConstraints existingConstraints constraint =
let constraintsInit = if "(" `T.isPrefixOf` existingConstraints
then T.dropEnd 1 existingConstraints
else "(" <> existingConstraints
in constraintsInit <> ", " <> constraint <> ")"
suggestInstanceConstraint :: T.Text -> Diagnostic -> T.Text -> [(T.Text, [TextEdit])]
suggestInstanceConstraint contents Diagnostic {..} missingConstraint
| Just [instanceDeclaration] <- matchRegex _message "In the instance declaration for ‘([^`]*)’"
= let instanceLine = contents
& T.splitOn ("instance " <> instanceDeclaration)
& head & T.lines & length
startOfConstraint = Position instanceLine (length ("instance " :: String))
range = Range startOfConstraint startOfConstraint
newConstraint = missingConstraint <> " => "
in [(actionTitle missingConstraint, [TextEdit range newConstraint])]
| Just [instanceLineStr, constraintFirstCharStr]
<- matchRegex _message "bound by the instance declaration at .+:([0-9]+):([0-9]+)"
= let existingConstraints = findExistingConstraints _message
newConstraints = normalizeConstraints existingConstraints missingConstraint
instanceLine = readPositionNumber instanceLineStr
constraintFirstChar = readPositionNumber constraintFirstCharStr
startOfConstraint = Position instanceLine constraintFirstChar
endOfConstraint = Position instanceLine $
constraintFirstChar + T.length existingConstraints
range = Range startOfConstraint endOfConstraint
in [(actionTitle missingConstraint, [TextEdit range newConstraints])]
| otherwise = []
where
findExistingConstraints :: T.Text -> T.Text
findExistingConstraints t =
T.replace "from the context: " "" . T.strip $ T.lines t !! 1
readPositionNumber :: T.Text -> Int
readPositionNumber = T.unpack >>> read >>> pred
actionTitle :: T.Text -> T.Text
actionTitle constraint = "Add `" <> constraint
<> "` to the context of the instance declaration"
findTypeSignatureName :: T.Text -> Maybe T.Text
findTypeSignatureName t = matchRegex t "([^ ]+) :: " <&> head
findTypeSignatureLine :: T.Text -> T.Text -> Int
findTypeSignatureLine contents typeSignatureName =
T.splitOn (typeSignatureName <> " :: ") contents & head & T.lines & length
suggestFunctionConstraint :: T.Text -> Diagnostic -> T.Text -> [(T.Text, [TextEdit])]
suggestFunctionConstraint contents Diagnostic{..} missingConstraint
| Just typeSignatureName <- findTypeSignatureName _message
= let mExistingConstraints = findExistingConstraints _message
newConstraint = buildNewConstraints missingConstraint mExistingConstraints
typeSignatureLine = findTypeSignatureLine contents typeSignatureName
typeSignatureFirstChar = T.length $ typeSignatureName <> " :: "
startOfConstraint = Position typeSignatureLine typeSignatureFirstChar
endOfConstraint = Position typeSignatureLine $
typeSignatureFirstChar + maybe 0 T.length mExistingConstraints
range = Range startOfConstraint endOfConstraint
in [(actionTitle missingConstraint typeSignatureName, [TextEdit range newConstraint])]
| otherwise = []
where
findExistingConstraints :: T.Text -> Maybe T.Text
findExistingConstraints message =
if message =~ ("from the context:" :: String)
then fmap (T.strip . head) $ matchRegex message "\\. ([^=]+)"
else Nothing
buildNewConstraints :: T.Text -> Maybe T.Text -> T.Text
buildNewConstraints constraint mExistingConstraints =
case mExistingConstraints of
Just existingConstraints -> normalizeConstraints existingConstraints constraint
Nothing -> constraint <> " => "
actionTitle :: T.Text -> T.Text -> T.Text
actionTitle constraint typeSignatureName = "Add `" <> constraint
<> "` to the context of the type signature for `" <> typeSignatureName <> "`"
removeRedundantConstraints :: Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
removeRedundantConstraints mContents Diagnostic{..}
| Just contents <- mContents
, True <- "Redundant constraint" `T.isInfixOf` _message
, Just typeSignatureName <- findTypeSignatureName _message
, Just redundantConstraintList <- findRedundantConstraints _message
, Just constraints <- findConstraints contents typeSignatureName
= let constraintList = parseConstraints constraints
newConstraints = buildNewConstraints constraintList redundantConstraintList
typeSignatureLine = findTypeSignatureLine contents typeSignatureName
typeSignatureFirstChar = T.length $ typeSignatureName <> " :: "
startOfConstraint = Position typeSignatureLine typeSignatureFirstChar
endOfConstraint = Position typeSignatureLine $
typeSignatureFirstChar + T.length (constraints <> " => ")
range = Range startOfConstraint endOfConstraint
in [(actionTitle redundantConstraintList typeSignatureName, [TextEdit range newConstraints])]
| otherwise = []
where
parseConstraints :: T.Text -> [T.Text]
parseConstraints t = t
& (T.strip >>> stripConstraintsParens >>> T.splitOn ",")
<&> T.strip
stripConstraintsParens :: T.Text -> T.Text
stripConstraintsParens constraints =
if "(" `T.isPrefixOf` constraints
then constraints & T.drop 1 & T.dropEnd 1 & T.strip
else constraints
findRedundantConstraints :: T.Text -> Maybe [T.Text]
findRedundantConstraints t = t
& T.lines
& head
& T.strip
& (`matchRegex` "Redundant constraints?: (.+)")
<&> (head >>> parseConstraints)
findConstraints :: T.Text -> T.Text -> Maybe T.Text
findConstraints contents typeSignatureName = do
constraints <- contents
& T.splitOn (typeSignatureName <> " :: ")
& (`atMay` 1)
>>= (T.splitOn " => " >>> (`atMay` 0))
guard $ not $ "\n" `T.isInfixOf` constraints || T.strip constraints /= constraints
return constraints
formatConstraints :: [T.Text] -> T.Text
formatConstraints [] = ""
formatConstraints [constraint] = constraint
formatConstraints constraintList = constraintList
& T.intercalate ", "
& \cs -> "(" <> cs <> ")"
formatConstraintsWithArrow :: [T.Text] -> T.Text
formatConstraintsWithArrow [] = ""
formatConstraintsWithArrow cs = cs & formatConstraints & (<> " => ")
buildNewConstraints :: [T.Text] -> [T.Text] -> T.Text
buildNewConstraints constraintList redundantConstraintList =
formatConstraintsWithArrow $ constraintList \\ redundantConstraintList
actionTitle :: [T.Text] -> T.Text -> T.Text
actionTitle constraintList typeSignatureName =
"Remove redundant constraint" <> (if length constraintList == 1 then "" else "s") <> " `"
<> formatConstraints constraintList
<> "` from the context of the type signature for `" <> typeSignatureName <> "`"
suggestNewImport :: PackageExportsMap -> ParsedModule -> Diagnostic -> [(T.Text, [TextEdit])]
suggestNewImport packageExportsMap ParsedModule {pm_parsed_source = L _ HsModule {..}} Diagnostic{_message}
| msg <- unifySpaces _message
, Just name <- extractNotInScopeName msg
, Just insertLine <- case hsmodImports of
[] -> case srcSpanStart $ getLoc (head hsmodDecls) of
RealSrcLoc s -> Just $ srcLocLine s - 1
_ -> Nothing
_ -> case srcSpanEnd $ getLoc (last hsmodImports) of
RealSrcLoc s -> Just $ srcLocLine s
_ -> Nothing
, insertPos <- Position insertLine 0
, extendImportSuggestions <- matchRegex msg
"Perhaps you want to add ‘[^’]*’ to the import list in the import of ‘([^’]*)’"
= [(imp, [TextEdit (Range insertPos insertPos) (imp <> "\n")])
| imp <- constructNewImportSuggestions packageExportsMap name extendImportSuggestions
]
suggestNewImport _ _ _ = []
constructNewImportSuggestions
:: PackageExportsMap -> NotInScope -> Maybe [T.Text] -> [T.Text]
constructNewImportSuggestions exportsMap thingMissing notTheseModules = nubOrd
[ renderNewImport identInfo m
| (identInfo, m) <- fromMaybe [] $ Map.lookup name exportsMap
, canUseIdent thingMissing identInfo
, m `notElem` fromMaybe [] notTheseModules
]
where
renderNewImport identInfo m
| Just q <- qual = "import qualified " <> m <> " as " <> q
| otherwise = "import " <> m <> " (" <> importWhat identInfo <> ")"
(qual, name) = case T.splitOn "." (notInScope thingMissing) of
[n] -> (Nothing, n)
segments -> (Just (T.concat $ init segments), last segments)
importWhat IdentInfo {parent, rendered}
| Just p <- parent = p <> "(" <> rendered <> ")"
| otherwise = rendered
canUseIdent :: NotInScope -> IdentInfo -> Bool
canUseIdent NotInScopeDataConstructor{} = isDatacon
canUseIdent _ = const True
data NotInScope
= NotInScopeDataConstructor T.Text
| NotInScopeTypeConstructorOrClass T.Text
| NotInScopeThing T.Text
deriving Show
notInScope :: NotInScope -> T.Text
notInScope (NotInScopeDataConstructor t) = t
notInScope (NotInScopeTypeConstructorOrClass t) = t
notInScope (NotInScopeThing t) = t
extractNotInScopeName :: T.Text -> Maybe NotInScope
extractNotInScopeName x
| Just [name] <- matchRegex x "Data constructor not in scope: ([^ ]+)"
= Just $ NotInScopeDataConstructor name
| Just [name] <- matchRegex x "Not in scope: data constructor [^‘]*‘([^’]*)’"
= Just $ NotInScopeDataConstructor name
| Just [name] <- matchRegex x "ot in scope: type constructor or class [^‘]*‘([^’]*)’"
= Just $ NotInScopeTypeConstructorOrClass name
| Just [name] <- matchRegex x "ot in scope: \\(([^‘ ]+)\\)"
= Just $ NotInScopeThing name
| Just [name] <- matchRegex x "ot in scope: ([^‘ ]+)"
= Just $ NotInScopeThing name
| Just [name] <- matchRegex x "ot in scope:[^‘]*‘([^’]*)’"
= Just $ NotInScopeThing name
| otherwise
= Nothing
topOfHoleFitsMarker :: T.Text
topOfHoleFitsMarker =
#if MIN_GHC_API_VERSION(8,6,0)
"Valid hole fits include"
#else
"Valid substitutions include"
#endif
mkRenameEdit :: Maybe T.Text -> Range -> T.Text -> TextEdit
mkRenameEdit contents range name =
if maybeIsInfixFunction == Just True
then TextEdit range ("`" <> name <> "`")
else TextEdit range name
where
maybeIsInfixFunction = do
curr <- textInRange range <$> contents
pure $ "`" `T.isPrefixOf` curr && "`" `T.isSuffixOf` curr
extractWildCardTypeSignature :: T.Text -> T.Text
extractWildCardTypeSignature =
("(" `T.append`) . (`T.append` ")") .
T.takeWhile (/='’') . T.dropWhile (=='‘') . T.dropWhile (/='‘') .
snd . T.breakOnEnd "standing for "
extractRenamableTerms :: T.Text -> [T.Text]
extractRenamableTerms msg
| "ot in scope:" `T.isInfixOf` msg = extractSuggestions msg
| otherwise = []
where
extractSuggestions = map getEnclosed
. concatMap singleSuggestions
. filter isKnownSymbol
. T.lines
singleSuggestions = T.splitOn "), "
isKnownSymbol t = " (imported from" `T.isInfixOf` t || " (line " `T.isInfixOf` t
getEnclosed = T.dropWhile (== '‘')
. T.dropWhileEnd (== '’')
. T.dropAround (\c -> c /= '‘' && c /= '’')
extendToWholeLineIfPossible :: Maybe T.Text -> Range -> Range
extendToWholeLineIfPossible contents range@Range{..} =
let newlineAfter = maybe False (T.isPrefixOf "\n" . T.dropWhile (\x -> isSpace x && x /= '\n') . snd . splitTextAtPosition _end) contents
extend = newlineAfter && _character _start == 0
in if extend then Range _start (Position (_line _end + 1) 0) else range
splitTextAtPosition :: Position -> T.Text -> (T.Text, T.Text)
splitTextAtPosition (Position row col) x
| (preRow, mid:postRow) <- splitAt row $ T.splitOn "\n" x
, (preCol, postCol) <- T.splitAt col mid
= (T.intercalate "\n" $ preRow ++ [preCol], T.intercalate "\n" $ postCol : postRow)
| otherwise = (x, T.empty)
textInRange :: Range -> T.Text -> T.Text
textInRange (Range (Position startRow startCol) (Position endRow endCol)) text =
case compare startRow endRow of
LT ->
let (linesInRangeBeforeEndLine, endLineAndFurtherLines) = splitAt (endRow - startRow) linesBeginningWithStartLine
(textInRangeInFirstLine, linesBetween) = case linesInRangeBeforeEndLine of
[] -> ("", [])
firstLine:linesInBetween -> (T.drop startCol firstLine, linesInBetween)
maybeTextInRangeInEndLine = T.take endCol <$> listToMaybe endLineAndFurtherLines
in T.intercalate "\n" (textInRangeInFirstLine : linesBetween ++ maybeToList maybeTextInRangeInEndLine)
EQ ->
let line = fromMaybe "" (listToMaybe linesBeginningWithStartLine)
in T.take (endCol - startCol) (T.drop startCol line)
GT -> ""
where
linesBeginningWithStartLine = drop startRow (T.splitOn "\n" text)
rangesForBinding :: ImportDecl GhcPs -> String -> [Range]
rangesForBinding ImportDecl{ideclHiding = Just (False, L _ lies)} b =
concatMap (map srcSpanToRange . rangesForBinding' b') lies
where
b' = wrapOperatorInParens (unqualify b)
wrapOperatorInParens x = if isAlpha (head x) then x else "(" <> x <> ")"
unqualify x = snd $ breakOnEnd "." x
rangesForBinding _ _ = []
rangesForBinding' :: String -> LIE GhcPs -> [SrcSpan]
rangesForBinding' b (L l x@IEVar{}) | showSDocUnsafe (ppr x) == b = [l]
rangesForBinding' b (L l x@IEThingAbs{}) | showSDocUnsafe (ppr x) == b = [l]
rangesForBinding' b (L l (IEThingAll x)) | showSDocUnsafe (ppr x) == b = [l]
rangesForBinding' b (L l (IEThingWith thing _ inners labels))
| showSDocUnsafe (ppr thing) == b = [l]
| otherwise =
[ l' | L l' x <- inners, showSDocUnsafe (ppr x) == b] ++
[ l' | L l' x <- labels, showSDocUnsafe (ppr x) == b]
rangesForBinding' _ _ = []
addBindingToImportList :: T.Text -> T.Text -> T.Text
addBindingToImportList binding importLine = case T.breakOn "(" importLine of
(pre, T.uncons -> Just (_, rest)) ->
case T.uncons (T.dropWhile isSpace rest) of
Just (')', _) -> T.concat [pre, "(", binding, rest]
_ -> T.concat [pre, "(", binding, ", ", rest]
_ ->
error
$ "importLine does not have the expected structure: "
<> T.unpack importLine
matchRegex :: T.Text -> T.Text -> Maybe [T.Text]
matchRegex message regex = case unifySpaces message =~~ regex of
Just (_ :: T.Text, _ :: T.Text, _ :: T.Text, bindings) -> Just bindings
Nothing -> Nothing
setHandlersCodeLens :: PartialHandlers c
setHandlersCodeLens = PartialHandlers $ \WithMessage{..} x -> return x{
LSP.codeLensHandler = withResponse RspCodeLens codeLens,
LSP.executeCommandHandler = withResponseAndRequest RspExecuteCommand ReqApplyWorkspaceEdit executeAddSignatureCommand
}
filterNewlines :: T.Text -> T.Text
filterNewlines = T.concat . T.lines
unifySpaces :: T.Text -> T.Text
unifySpaces = T.unwords . T.words