Skip to content

Commit a04bb85

Browse files
committed
Fix code actions which remove constraints
1 parent af257c3 commit a04bb85

File tree

2 files changed

+51
-38
lines changed

2 files changed

+51
-38
lines changed

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

Lines changed: 37 additions & 38 deletions
Original file line numberDiff line numberDiff line change
@@ -71,7 +71,6 @@ import Outputable (Outputable,
7171
showSDocUnsafe)
7272
import RdrName (GlobalRdrElt (..),
7373
lookupGlobalRdrEnv)
74-
import Safe (atMay)
7574
import SrcLoc (realSrcSpanStart)
7675
import TcRnTypes (ImportAvails (..),
7776
TcGblEnv (..))
@@ -158,7 +157,7 @@ suggestAction packageExports ideOptions parsedModule text df annSource tcM har d
158157
, suggestFixConstructorImport text diag
159158
, suggestModuleTypo diag
160159
, suggestReplaceIdentifier text diag
161-
, removeRedundantConstraints text diag
160+
, rewrite df annSource $ \df _ps -> removeRedundantConstraints df parsedModule diag
162161
, suggestAddTypeAnnotationToSatisfyContraints text diag
163162
, rewrite df annSource $ \df ps -> suggestConstraint df ps diag
164163
, rewrite df annSource $ \_ ps -> suggestImplicitParameter ps diag
@@ -180,6 +179,32 @@ findSigOfDecl pred decls =
180179
any (pred . unLoc) idsSig
181180
]
182181

182+
findSigOfDecl' :: Range -> [LHsDecl p] -> Either String (Sig p)
183+
findSigOfDecl' range decls = do
184+
dec <- findDeclContainingLocE (_start range) decls
185+
case dec of
186+
L _ (SigD _ sig@(TypeSig {})) -> Right sig
187+
L _ (ValD _ (bind :: HsBind p)) -> findSigOfBind range bind
188+
_ -> Left "Other"
189+
190+
findSigOfBind :: Range -> HsBind p -> Either String (Sig p)
191+
findSigOfBind range bind =
192+
case bind of
193+
FunBind {} -> findSigOfLMatch (unLoc $ mg_alts (fun_matches bind))
194+
_ -> Left "Other findSigOfBind"
195+
where
196+
findSigOfLMatch :: [LMatch p (LHsExpr idR)] -> Either String (Sig p)
197+
findSigOfLMatch ls = do
198+
match <- findDeclContainingLocE (_start range) ls
199+
case unLoc (grhssLocalBinds (m_grhss (unLoc match))) of
200+
HsValBinds _ (ValBinds _ _ lsigs) ->
201+
unLoc <$> findDeclContainingLocE (_start range) lsigs
202+
_ -> Left "Other findSigOfLMatch"
203+
204+
findDeclContainingLocE :: Position -> [Located a] -> Either String (Located a)
205+
findDeclContainingLocE loc ls =
206+
maybe (Left "findDeclContainingLoc") Right $ findDeclContainingLoc loc ls
207+
183208
findInstanceHead :: (Outputable (HsType p)) => DynFlags -> String -> [LHsDecl p] -> Maybe (LHsType p)
184209
findInstanceHead df instanceHead decls =
185210
listToMaybe
@@ -191,6 +216,7 @@ findInstanceHead df instanceHead decls =
191216
findDeclContainingLoc :: Position -> [Located a] -> Maybe (Located a)
192217
findDeclContainingLoc loc = find (\(L l _) -> loc `isInsideSrcSpan` l)
193218

219+
194220
-- Single:
195221
-- This binding for ‘mod’ shadows the existing binding
196222
-- imported from ‘Prelude’ at haskell-language-server/ghcide/src/Development/IDE/Plugin/CodeAction.hs:10:8-40
@@ -1037,10 +1063,6 @@ suggestImplicitParameter (L _ HsModule {hsmodDecls}) Diagnostic {_message, _rang
10371063
findTypeSignatureName :: T.Text -> Maybe T.Text
10381064
findTypeSignatureName t = matchRegexUnifySpaces t "([^ ]+) :: " <&> head
10391065

1040-
findTypeSignatureLine :: T.Text -> T.Text -> Int
1041-
findTypeSignatureLine contents typeSignatureName =
1042-
T.splitOn (typeSignatureName <> " :: ") contents & head & T.lines & length
1043-
10441066
-- | Suggests a constraint for a type signature with any number of existing constraints.
10451067
suggestFunctionConstraint :: DynFlags -> ParsedSource -> Diagnostic -> T.Text -> [(T.Text, Rewrite)]
10461068

@@ -1079,31 +1101,27 @@ suggestFunctionConstraint df (L _ HsModule {hsmodDecls}) Diagnostic {..} missing
10791101
<> "` to the context of the type signature for `" <> typeSignatureName <> "`"
10801102

10811103
-- | Suggests the removal of a redundant constraint for a type signature.
1082-
removeRedundantConstraints :: Maybe T.Text -> Diagnostic -> [(T.Text, [TextEdit])]
1083-
removeRedundantConstraints mContents Diagnostic{..}
1104+
removeRedundantConstraints :: DynFlags -> Maybe ParsedModule -> Diagnostic -> [(T.Text, [Rewrite])]
1105+
removeRedundantConstraints df m Diagnostic{..}
10841106
-- • Redundant constraint: Eq a
10851107
-- • In the type signature for:
10861108
-- foo :: forall a. Eq a => a -> a
10871109
-- • Redundant constraints: (Monoid a, Show a)
10881110
-- • In the type signature for:
10891111
-- foo :: forall a. (Num a, Monoid a, Eq a, Show a) => a -> Bool
1090-
| Just contents <- mContents
1112+
| Just (L _ HsModule {hsmodDecls}) <- pm_parsed_source <$> m
10911113
-- Account for both "Redundant constraint" and "Redundant constraints".
10921114
, True <- "Redundant constraint" `T.isInfixOf` _message
10931115
, Just typeSignatureName <- findTypeSignatureName _message
1116+
, Right (TypeSig _ _ HsWC{hswc_body = HsIB {hsib_body = sig}})
1117+
<- findSigOfDecl' _range hsmodDecls
10941118
, Just redundantConstraintList <- findRedundantConstraints _message
1095-
, Just constraints <- findConstraints contents typeSignatureName
1096-
= let constraintList = parseConstraints constraints
1097-
newConstraints = buildNewConstraints constraintList redundantConstraintList
1098-
typeSignatureLine = findTypeSignatureLine contents typeSignatureName
1099-
typeSignatureFirstChar = T.length $ typeSignatureName <> " :: "
1100-
startOfConstraint = Position typeSignatureLine typeSignatureFirstChar
1101-
endOfConstraint = Position typeSignatureLine $
1102-
typeSignatureFirstChar + T.length (constraints <> " => ")
1103-
range = Range startOfConstraint endOfConstraint
1104-
in [(actionTitle redundantConstraintList typeSignatureName, [TextEdit range newConstraints])]
1119+
, rewrite' <- removeConstraint (pred df redundantConstraintList) sig
1120+
= [(actionTitle redundantConstraintList typeSignatureName, [rewrite'])]
11051121
| otherwise = []
11061122
where
1123+
pred df list a = elem (showSDoc df (ppr a)) (T.unpack <$> list)
1124+
11071125
parseConstraints :: T.Text -> [T.Text]
11081126
parseConstraints t = t
11091127
& (T.strip >>> stripConstraintsParens >>> T.splitOn ",")
@@ -1123,32 +1141,13 @@ removeRedundantConstraints mContents Diagnostic{..}
11231141
& (`matchRegexUnifySpaces` "Redundant constraints?: (.+)")
11241142
<&> (head >>> parseConstraints)
11251143

1126-
-- If the type signature is not formatted as expected (arbitrary number of spaces,
1127-
-- line feeds...), just fail.
1128-
findConstraints :: T.Text -> T.Text -> Maybe T.Text
1129-
findConstraints contents typeSignatureName = do
1130-
constraints <- contents
1131-
& T.splitOn (typeSignatureName <> " :: ")
1132-
& (`atMay` 1)
1133-
>>= (T.splitOn " => " >>> (`atMay` 0))
1134-
guard $ not $ "\n" `T.isInfixOf` constraints || T.strip constraints /= constraints
1135-
return constraints
1136-
11371144
formatConstraints :: [T.Text] -> T.Text
11381145
formatConstraints [] = ""
11391146
formatConstraints [constraint] = constraint
11401147
formatConstraints constraintList = constraintList
11411148
& T.intercalate ", "
11421149
& \cs -> "(" <> cs <> ")"
11431150

1144-
formatConstraintsWithArrow :: [T.Text] -> T.Text
1145-
formatConstraintsWithArrow [] = ""
1146-
formatConstraintsWithArrow cs = cs & formatConstraints & (<> " => ")
1147-
1148-
buildNewConstraints :: [T.Text] -> [T.Text] -> T.Text
1149-
buildNewConstraints constraintList redundantConstraintList =
1150-
formatConstraintsWithArrow $ constraintList \\ redundantConstraintList
1151-
11521151
actionTitle :: [T.Text] -> T.Text -> T.Text
11531152
actionTitle constraintList typeSignatureName =
11541153
"Remove redundant constraint" <> (if length constraintList == 1 then "" else "s") <> " `"

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

Lines changed: 14 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module Development.IDE.Plugin.CodeAction.ExactPrint (
1111

1212
-- * Utilities
1313
appendConstraint,
14+
removeConstraint,
1415
extendImport,
1516
hideImplicitPreludeSymbol,
1617
hideSymbol,
@@ -128,6 +129,19 @@ fixParens openDP closeDP ctxt@(L _ elems) = do
128129
dropHsParTy (L _ (HsParTy _ ty)) = ty
129130
dropHsParTy other = other
130131

132+
removeConstraint ::
133+
-- | Predicate: Which contect to drop.
134+
(LHsType GhcPs -> Bool) ->
135+
LHsType GhcPs ->
136+
Rewrite
137+
removeConstraint pred = go
138+
where
139+
go (L l it@HsQualTy{hst_ctxt = L l' ctxt}) = Rewrite l $ \_ -> do
140+
return $ L l $ it{hst_ctxt = L l' $ filter (not . pred) ctxt}
141+
go (L _ (HsParTy _ ty)) = go ty
142+
go (L _ HsForAllTy{hst_body}) = go hst_body
143+
go (L l other) = Rewrite l $ \_ -> return $ L l other
144+
131145
-- | Append a constraint at the end of a type context.
132146
-- If no context is present, a new one will be created.
133147
appendConstraint ::

0 commit comments

Comments
 (0)