Skip to content

Commit d1b64bc

Browse files
committed
Refactor suggest constraint code action to use exactprint
Tweaking the suggest constraints tests to reflect the increased precision in whitespace preservation
1 parent 38ce4c5 commit d1b64bc

File tree

2 files changed

+107
-112
lines changed

2 files changed

+107
-112
lines changed

ghcide/src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 101 additions & 106 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@ import Development.IDE.Core.Shake
3232
import Development.IDE.GHC.Error
3333
import Development.IDE.GHC.ExactPrint
3434
import Development.IDE.LSP.Server
35+
import Development.IDE.Plugin.CodeAction.ExactPrint
3536
import Development.IDE.Plugin.CodeAction.PositionIndexed
3637
import Development.IDE.Plugin.CodeAction.RuleTypes
3738
import Development.IDE.Plugin.CodeAction.Rules
@@ -53,7 +54,7 @@ import Data.List.NonEmpty (NonEmpty((:|)))
5354
import qualified Data.List.NonEmpty as NE
5455
import qualified Data.Text as T
5556
import Text.Regex.TDFA (mrAfter, (=~), (=~~))
56-
import Outputable (ppr, showSDocUnsafe)
57+
import Outputable (Outputable, ppr, showSDoc, showSDocUnsafe)
5758
import Data.Function
5859
import Control.Arrow ((>>>))
5960
import Data.Functor
@@ -91,20 +92,38 @@ codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext{_diag
9192
let text = Rope.toText . (_text :: VirtualFile -> Rope.Rope) <$> contents
9293
mbFile = toNormalizedFilePath' <$> uriToFilePath uri
9394
diag <- fmap (\(_, _, d) -> d) . filter (\(p, _, _) -> mbFile == Just p) <$> getDiagnostics state
94-
(ideOptions, join -> parsedModule, join -> env) <- runAction "CodeAction" state $
95-
(,,) <$> getIdeOptions
95+
(ideOptions, join -> parsedModule, join -> env, join -> annotatedPS) <- runAction "CodeAction" state $
96+
(,,,) <$> getIdeOptions
9697
<*> getParsedModule `traverse` mbFile
9798
<*> use GhcSession `traverse` mbFile
99+
<*> use GetAnnotatedParsedSource `traverse` mbFile
98100
-- This is quite expensive 0.6-0.7s on GHC
99101
pkgExports <- runAction "CodeAction:PackageExports" state $ (useNoFile_ . PackageExports) `traverse` env
100102
localExports <- readVar (exportsMap $ shakeExtras state)
101-
let exportsMap = localExports <> fromMaybe mempty pkgExports
102-
pure . Right $
103-
[ CACodeAction $ CodeAction title (Just CodeActionQuickFix) (Just $ List [x]) (Just edit) Nothing
103+
let
104+
exportsMap = localExports <> fromMaybe mempty pkgExports
105+
df = ms_hspp_opts . pm_mod_summary <$> parsedModule
106+
actions =
107+
[ mkCA title [x] edit
104108
| x <- xs, (title, tedit) <- suggestAction exportsMap ideOptions parsedModule text x
105109
, let edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing
106110
] <> caRemoveRedundantImports parsedModule text diag xs uri
107111

112+
actions' =
113+
[mkCA title [x] edit
114+
| x <- xs
115+
, Just ps <- [annotatedPS]
116+
, Just dynflags <- [df]
117+
, (title, graft) <- suggestExactAction dynflags ps x
118+
, let edit = either error id $
119+
rewriteToEdit dynflags uri (annsA ps) graft
120+
]
121+
pure $ Right $ actions' <> actions
122+
123+
mkCA :: T.Text -> [Diagnostic] -> WorkspaceEdit -> CAResult
124+
mkCA title diags edit =
125+
CACodeAction $ CodeAction title (Just CodeActionQuickFix) (Just $ List diags) (Just edit) Nothing
126+
108127
-- | Generate code lenses.
109128
codeLens
110129
:: LSP.LspFuncs c
@@ -151,6 +170,16 @@ commandHandler lsp _ideState ExecuteCommandParams{..}
151170
| otherwise
152171
= return (Right Null, Nothing)
153172

173+
suggestExactAction ::
174+
DynFlags ->
175+
Annotated ParsedSource ->
176+
Diagnostic ->
177+
[(T.Text, Rewrite)]
178+
suggestExactAction df ps x =
179+
concat
180+
[ suggestConstraint df (astA ps) x
181+
]
182+
154183
suggestAction
155184
:: ExportsMap
156185
-> IdeOptions
@@ -169,15 +198,32 @@ suggestAction packageExports ideOptions parsedModule text diag = concat
169198
, removeRedundantConstraints text diag
170199
, suggestAddTypeAnnotationToSatisfyContraints text diag
171200
] ++ concat
172-
[ suggestConstraint pm text diag
173-
++ suggestNewDefinition ideOptions pm text diag
201+
[ suggestNewDefinition ideOptions pm text diag
174202
++ suggestNewImport packageExports pm diag
175203
++ suggestDeleteUnusedBinding pm text diag
176204
++ suggestExportUnusedTopBinding text pm diag
177205
| Just pm <- [parsedModule]
178206
] ++
179207
suggestFillHole diag -- Lowest priority
180208

209+
findSigOfDecl :: (IdP p -> Bool) -> [LHsDecl p] -> Maybe (Sig p)
210+
findSigOfDecl pred decls =
211+
listToMaybe
212+
[ sig
213+
| L _ (SigD _ sig@(TypeSig _ idsSig _)) <- decls,
214+
any (pred . unLoc) idsSig
215+
]
216+
217+
findInstanceHead :: (Outputable (HsType p)) => DynFlags -> String -> [LHsDecl p] -> Maybe (LHsType p)
218+
findInstanceHead df instanceHead decls =
219+
listToMaybe
220+
[ hsib_body
221+
| L _ (InstD _ (ClsInstD _ ClsInstDecl {cid_poly_ty = HsIB {hsib_body}})) <- decls,
222+
showSDoc df (ppr hsib_body) == instanceHead
223+
]
224+
225+
findDeclContainingLoc :: Position -> [Located a] -> Maybe (Located a)
226+
findDeclContainingLoc loc = find (\(L l _) -> loc `isInsideSrcSpan` l)
181227

182228
suggestRemoveRedundantImport :: ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
183229
suggestRemoveRedundantImport ParsedModule{pm_parsed_source = L _ HsModule{hsmodImports}} contents Diagnostic{_range=_range,..}
@@ -210,14 +256,9 @@ caRemoveRedundantImports m contents digs ctxDigs uri
210256
= caRemoveCtx ++ [caRemoveAll]
211257
| otherwise = []
212258
where
213-
removeSingle title tedit diagnostic = CACodeAction CodeAction{..} where
259+
removeSingle title tedit diagnostic = mkCA title [diagnostic] WorkspaceEdit{..} where
214260
_changes = Just $ Map.singleton uri $ List tedit
215-
_title = title
216-
_kind = Just CodeActionQuickFix
217-
_diagnostics = Just $ List [diagnostic]
218261
_documentChanges = Nothing
219-
_edit = Just WorkspaceEdit{..}
220-
_command = Nothing
221262
removeAll tedit = CACodeAction CodeAction {..} where
222263
_changes = Just $ Map.singleton uri $ List tedit
223264
_title = "Remove all redundant imports"
@@ -687,13 +728,12 @@ suggestSignature isQuickFix Diagnostic{_range=_range@Range{..},..}
687728
suggestSignature _ _ = []
688729

689730
-- | Suggests a constraint for a declaration for which a constraint is missing.
690-
suggestConstraint :: ParsedModule -> Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
691-
suggestConstraint parsedModule mContents diag@Diagnostic {..}
692-
| Just contents <- mContents
693-
, Just missingConstraint <- findMissingConstraint _message
731+
suggestConstraint :: DynFlags -> ParsedSource -> Diagnostic -> [(T.Text, Rewrite)]
732+
suggestConstraint df parsedModule diag@Diagnostic {..}
733+
| Just missingConstraint <- findMissingConstraint _message
694734
= let codeAction = if _message =~ ("the type signature for:" :: String)
695-
then suggestFunctionConstraint parsedModule
696-
else suggestInstanceConstraint contents
735+
then suggestFunctionConstraint df parsedModule
736+
else suggestInstanceConstraint df parsedModule
697737
in codeAction diag missingConstraint
698738
| otherwise = []
699739
where
@@ -702,59 +742,43 @@ suggestConstraint parsedModule mContents diag@Diagnostic {..}
702742
let regex = "(No instance for|Could not deduce) \\((.+)\\) arising from a use of"
703743
in matchRegexUnifySpaces t regex <&> last
704744

705-
normalizeConstraints :: T.Text -> T.Text -> T.Text
706-
normalizeConstraints existingConstraints constraint =
707-
let constraintsInit = if "(" `T.isPrefixOf` existingConstraints
708-
then T.dropEnd 1 existingConstraints
709-
else "(" <> existingConstraints
710-
in constraintsInit <> ", " <> constraint <> ")"
711-
712745
-- | Suggests a constraint for an instance declaration for which a constraint is missing.
713-
suggestInstanceConstraint :: T.Text -> Diagnostic -> T.Text -> [(T.Text, [TextEdit])]
714-
suggestInstanceConstraint contents Diagnostic {..} missingConstraint
715-
-- Suggests a constraint for an instance declaration with no existing constraints.
716-
-- • No instance for (Eq a) arising from a use of ‘==’
717-
-- Possible fix: add (Eq a) to the context of the instance declaration
718-
-- • In the expression: x == y
719-
-- In an equation for ‘==’: (Wrap x) == (Wrap y) = x == y
720-
-- In the instance declaration for ‘Eq (Wrap a)’
721-
| Just [instanceDeclaration] <- matchRegexUnifySpaces _message "In the instance declaration for ‘([^`]*)’"
722-
= let instanceLine = contents
723-
& T.splitOn ("instance " <> instanceDeclaration)
724-
& head & T.lines & length
725-
startOfConstraint = Position instanceLine (length ("instance " :: String))
726-
range = Range startOfConstraint startOfConstraint
727-
newConstraint = missingConstraint <> " => "
728-
in [(actionTitle missingConstraint, [TextEdit range newConstraint])]
729-
730-
-- Suggests a constraint for an instance declaration with one or more existing constraints.
731-
-- • Could not deduce (Eq b) arising from a use of ‘==’
732-
-- from the context: Eq a
733-
-- bound by the instance declaration at /path/to/Main.hs:7:10-32
734-
-- Possible fix: add (Eq b) to the context of the instance declaration
735-
-- • In the second argument of ‘(&&)’, namely ‘x' == y'’
736-
-- In the expression: x == y && x' == y'
737-
-- In an equation for ‘==’:
738-
-- (Pair x x') == (Pair y y') = x == y && x' == y'
739-
| Just [instanceLineStr, constraintFirstCharStr]
740-
<- matchRegexUnifySpaces _message "bound by the instance declaration at .+:([0-9]+):([0-9]+)"
741-
= let existingConstraints = findExistingConstraints _message
742-
newConstraints = normalizeConstraints existingConstraints missingConstraint
743-
instanceLine = readPositionNumber instanceLineStr
744-
constraintFirstChar = readPositionNumber constraintFirstCharStr
745-
startOfConstraint = Position instanceLine constraintFirstChar
746-
endOfConstraint = Position instanceLine $
747-
constraintFirstChar + T.length existingConstraints
748-
range = Range startOfConstraint endOfConstraint
749-
in [(actionTitle missingConstraint, [TextEdit range newConstraints])]
746+
suggestInstanceConstraint :: DynFlags -> ParsedSource -> Diagnostic -> T.Text -> [(T.Text, Rewrite)]
747+
748+
suggestInstanceConstraint df (L _ HsModule {hsmodDecls}) Diagnostic {..} missingConstraint
749+
| Just instHead <- instanceHead
750+
= [(actionTitle missingConstraint , appendConstraint (T.unpack missingConstraint) instHead)]
750751
| otherwise = []
751752
where
752-
findExistingConstraints :: T.Text -> T.Text
753-
findExistingConstraints t =
754-
T.replace "from the context: " "" . T.strip $ T.lines t !! 1
753+
instanceHead
754+
-- Suggests a constraint for an instance declaration with no existing constraints.
755+
-- • No instance for (Eq a) arising from a use of ‘==’
756+
-- Possible fix: add (Eq a) to the context of the instance declaration
757+
-- • In the expression: x == y
758+
-- In an equation for ‘==’: (Wrap x) == (Wrap y) = x == y
759+
-- In the instance declaration for ‘Eq (Wrap a)’
760+
| Just [instanceDeclaration] <- matchRegexUnifySpaces _message "In the instance declaration for ‘([^`]*)’"
761+
, Just instHead <- findInstanceHead df (T.unpack instanceDeclaration) hsmodDecls
762+
= Just instHead
763+
-- Suggests a constraint for an instance declaration with one or more existing constraints.
764+
-- • Could not deduce (Eq b) arising from a use of ‘==’
765+
-- from the context: Eq a
766+
-- bound by the instance declaration at /path/to/Main.hs:7:10-32
767+
-- Possible fix: add (Eq b) to the context of the instance declaration
768+
-- • In the second argument of ‘(&&)’, namely ‘x' == y'’
769+
-- In the expression: x == y && x' == y'
770+
-- In an equation for ‘==’:
771+
-- (Pair x x') == (Pair y y') = x == y && x' == y'
772+
| Just [instanceLineStr, constraintFirstCharStr]
773+
<- matchRegexUnifySpaces _message "bound by the instance declaration at .+:([0-9]+):([0-9]+)"
774+
, Just (L _ (InstD _ (ClsInstD _ ClsInstDecl {cid_poly_ty = HsIB{hsib_body}})))
775+
<- findDeclContainingLoc (Position (readPositionNumber instanceLineStr) (readPositionNumber constraintFirstCharStr)) hsmodDecls
776+
= Just hsib_body
777+
| otherwise
778+
= Nothing
755779

756780
readPositionNumber :: T.Text -> Int
757-
readPositionNumber = T.unpack >>> read >>> pred
781+
readPositionNumber = T.unpack >>> read
758782

759783
actionTitle :: T.Text -> T.Text
760784
actionTitle constraint = "Add `" <> constraint
@@ -768,8 +792,9 @@ findTypeSignatureLine contents typeSignatureName =
768792
T.splitOn (typeSignatureName <> " :: ") contents & head & T.lines & length
769793

770794
-- | Suggests a constraint for a type signature with any number of existing constraints.
771-
suggestFunctionConstraint :: ParsedModule -> Diagnostic -> T.Text -> [(T.Text, [TextEdit])]
772-
suggestFunctionConstraint ParsedModule{pm_parsed_source = L _ HsModule{hsmodDecls}} Diagnostic{..} missingConstraint
795+
suggestFunctionConstraint :: DynFlags -> ParsedSource -> Diagnostic -> T.Text -> [(T.Text, Rewrite)]
796+
797+
suggestFunctionConstraint df (L _ HsModule {hsmodDecls}) Diagnostic {..} missingConstraint
773798
-- • No instance for (Eq a) arising from a use of ‘==’
774799
-- Possible fix:
775800
-- add (Eq a) to the context of
@@ -792,43 +817,13 @@ suggestFunctionConstraint ParsedModule{pm_parsed_source = L _ HsModule{hsmodDecl
792817
-- In an equation for ‘eq’:
793818
-- eq (Pair x y) (Pair x' y') = x == x' && y == y'
794819
| Just typeSignatureName <- findTypeSignatureName _message
795-
= let mExistingConstraints = findExistingConstraints _message
796-
newConstraint = buildNewConstraints missingConstraint mExistingConstraints
797-
in case findRangeOfContextForFunctionNamed typeSignatureName of
798-
Just range -> [(actionTitle missingConstraint typeSignatureName, [TextEdit range newConstraint])]
799-
Nothing -> []
800-
| otherwise = []
820+
, Just (TypeSig _ _ HsWC{hswc_body = HsIB {hsib_body = sig}})
821+
<- findSigOfDecl ((T.unpack typeSignatureName ==) . showSDoc df . ppr) hsmodDecls
822+
, title <- actionTitle missingConstraint typeSignatureName
823+
= [(title, appendConstraint (T.unpack $ missingConstraint) sig)]
824+
| otherwise
825+
= []
801826
where
802-
findRangeOfContextForFunctionNamed :: T.Text -> Maybe Range
803-
findRangeOfContextForFunctionNamed typeSignatureName = do
804-
locatedType <- listToMaybe
805-
[ locatedType
806-
| L _ (SigD _ (TypeSig _ identifiers (HsWC _ (HsIB _ locatedType)))) <- hsmodDecls
807-
, any (`isSameName` T.unpack typeSignatureName) $ fmap unLoc identifiers
808-
]
809-
let typeBody = dropForAll locatedType
810-
srcSpanToRange $ case splitLHsQualTy typeBody of
811-
(L contextSrcSpan _ , _) ->
812-
if isGoodSrcSpan contextSrcSpan
813-
then contextSrcSpan -- The type signature has explicit context
814-
else -- No explicit context, return SrcSpan at the start of type (after a potential `forall`)
815-
let start = srcSpanStart $ getLoc typeBody in mkSrcSpan start start
816-
817-
isSameName :: IdP GhcPs -> String -> Bool
818-
isSameName x name = showSDocUnsafe (ppr x) == name
819-
820-
findExistingConstraints :: T.Text -> Maybe T.Text
821-
findExistingConstraints message =
822-
if message =~ ("from the context:" :: String)
823-
then fmap (T.strip . head) $ matchRegexUnifySpaces message "\\. ([^=]+)"
824-
else Nothing
825-
826-
buildNewConstraints :: T.Text -> Maybe T.Text -> T.Text
827-
buildNewConstraints constraint mExistingConstraints =
828-
case mExistingConstraints of
829-
Just existingConstraints -> normalizeConstraints existingConstraints constraint
830-
Nothing -> constraint <> " => "
831-
832827
actionTitle :: T.Text -> T.Text -> T.Text
833828
actionTitle constraint typeSignatureName = "Add `" <> constraint
834829
<> "` to the context of the type signature for `" <> typeSignatureName <> "`"

ghcide/test/exe/Main.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -2028,7 +2028,7 @@ addFunctionConstraintTests = let
20282028
, ""
20292029
, "data Pair a b = Pair a b"
20302030
, ""
2031-
, "eq :: " <> constraint <> " => Pair a b -> Pair a b -> Bool"
2031+
, "eq :: ( " <> constraint <> " ) => Pair a b -> Pair a b -> Bool"
20322032
, "eq (Pair x y) (Pair x' y') = x == x' && y == y'"
20332033
]
20342034

@@ -2038,7 +2038,7 @@ addFunctionConstraintTests = let
20382038
[ "module Testing where"
20392039
, "data Pair a b = Pair a b"
20402040
, "eq "
2041-
, " :: " <> constraint
2041+
, " :: (" <> constraint <> ")"
20422042
, " => Pair a b -> Pair a b -> Bool"
20432043
, "eq (Pair x y) (Pair x' y') = x == x' && y == y'"
20442044
]
@@ -2082,13 +2082,13 @@ addFunctionConstraintTests = let
20822082
, check
20832083
"preexisting constraint, with extra spaces in context"
20842084
"Add `Eq b` to the context of the type signature for `eq`"
2085-
(incompleteConstraintSourceCodeWithExtraCharsInContext "( Eq a )")
2086-
(incompleteConstraintSourceCodeWithExtraCharsInContext "(Eq a, Eq b)")
2085+
(incompleteConstraintSourceCodeWithExtraCharsInContext "Eq a")
2086+
(incompleteConstraintSourceCodeWithExtraCharsInContext "Eq a, Eq b")
20872087
, check
20882088
"preexisting constraint, with newlines in type signature"
20892089
"Add `Eq b` to the context of the type signature for `eq`"
2090-
(incompleteConstraintSourceCodeWithNewlinesInTypeSignature "(Eq a)")
2091-
(incompleteConstraintSourceCodeWithNewlinesInTypeSignature "(Eq a, Eq b)")
2090+
(incompleteConstraintSourceCodeWithNewlinesInTypeSignature "Eq a")
2091+
(incompleteConstraintSourceCodeWithNewlinesInTypeSignature "Eq a, Eq b")
20922092
]
20932093

20942094
removeRedundantConstraintsTests :: TestTree

0 commit comments

Comments
 (0)