Skip to content

Commit 35927c8

Browse files
kdermeberberman
andauthored
Fix remove constraint (#1578)
* Fix code actions which remove constraints * Fix remove constraint for signatures with forall * Find signatures which are deeply nested * Test remove constraint for signature with spaces * Fix annotations * Fix also signatures in do statements * Use Maybe instead of Either Co-authored-by: Potato Hatsue <[email protected]>
1 parent 54737e9 commit 35927c8

File tree

3 files changed

+179
-47
lines changed

3 files changed

+179
-47
lines changed

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

+63-39
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,8 @@ module Development.IDE.Plugin.CodeAction
1414
, matchRegExMultipleImports
1515
) where
1616

17-
import Bag (isEmptyBag)
17+
import Bag (bagToList,
18+
isEmptyBag)
1819
import Control.Applicative ((<|>))
1920
import Control.Arrow (second,
2021
(>>>))
@@ -72,7 +73,6 @@ import Outputable (Outputable,
7273
showSDocUnsafe)
7374
import RdrName (GlobalRdrElt (..),
7475
lookupGlobalRdrEnv)
75-
import Safe (atMay)
7676
import SrcLoc (realSrcSpanEnd,
7777
realSrcSpanStart)
7878
import TcRnTypes (ImportAvails (..),
@@ -162,6 +162,57 @@ findSigOfDecl pred decls =
162162
any (pred . unLoc) idsSig
163163
]
164164

165+
findSigOfDeclRanged :: Range -> [LHsDecl p] -> Maybe (Sig p)
166+
findSigOfDeclRanged range decls = do
167+
dec <- findDeclContainingLoc (_start range) decls
168+
case dec of
169+
L _ (SigD _ sig@TypeSig {}) -> Just sig
170+
L _ (ValD _ (bind :: HsBind p)) -> findSigOfBind range bind
171+
_ -> Nothing
172+
173+
findSigOfBind :: Range -> HsBind p -> Maybe (Sig p)
174+
findSigOfBind range bind =
175+
case bind of
176+
FunBind {} -> findSigOfLMatch (unLoc $ mg_alts (fun_matches bind))
177+
_ -> Nothing
178+
where
179+
findSigOfLMatch :: [LMatch p (LHsExpr p)] -> Maybe (Sig p)
180+
findSigOfLMatch ls = do
181+
match <- findDeclContainingLoc (_start range) ls
182+
findSigOfGRHSs (m_grhss (unLoc match))
183+
184+
findSigOfGRHSs :: GRHSs p (LHsExpr p) -> Maybe (Sig p)
185+
findSigOfGRHSs grhs = do
186+
if _start range `isInsideSrcSpan` (getLoc $ grhssLocalBinds grhs)
187+
then findSigOfBinds range (unLoc (grhssLocalBinds grhs)) -- where clause
188+
else do
189+
grhs <- findDeclContainingLoc (_start range) (grhssGRHSs grhs)
190+
case unLoc grhs of
191+
GRHS _ _ bd -> findSigOfExpr (unLoc bd)
192+
_ -> Nothing
193+
194+
findSigOfExpr :: HsExpr p -> Maybe (Sig p)
195+
findSigOfExpr = go
196+
where
197+
go (HsLet _ binds _) = findSigOfBinds range (unLoc binds)
198+
go (HsDo _ _ stmts) = do
199+
stmtlr <- unLoc <$> findDeclContainingLoc (_start range) (unLoc stmts)
200+
case stmtlr of
201+
LetStmt _ lhsLocalBindsLR -> findSigOfBinds range $ unLoc lhsLocalBindsLR
202+
_ -> Nothing
203+
go _ = Nothing
204+
205+
findSigOfBinds :: Range -> HsLocalBinds p -> Maybe (Sig p)
206+
findSigOfBinds range = go
207+
where
208+
go (HsValBinds _ (ValBinds _ binds lsigs)) =
209+
case unLoc <$> findDeclContainingLoc (_start range) lsigs of
210+
Just sig' -> Just sig'
211+
Nothing -> do
212+
lHsBindLR <- findDeclContainingLoc (_start range) (bagToList binds)
213+
findSigOfBind range (unLoc lHsBindLR)
214+
go _ = Nothing
215+
165216
findInstanceHead :: (Outputable (HsType p)) => DynFlags -> String -> [LHsDecl p] -> Maybe (LHsType p)
166217
findInstanceHead df instanceHead decls =
167218
listToMaybe
@@ -173,6 +224,7 @@ findInstanceHead df instanceHead decls =
173224
findDeclContainingLoc :: Position -> [Located a] -> Maybe (Located a)
174225
findDeclContainingLoc loc = find (\(L l _) -> loc `isInsideSrcSpan` l)
175226

227+
176228
-- Single:
177229
-- This binding for ‘mod’ shadows the existing binding
178230
-- imported from ‘Prelude’ at haskell-language-server/ghcide/src/Development/IDE/Plugin/CodeAction.hs:10:8-40
@@ -1048,10 +1100,6 @@ suggestImplicitParameter (L _ HsModule {hsmodDecls}) Diagnostic {_message, _rang
10481100
findTypeSignatureName :: T.Text -> Maybe T.Text
10491101
findTypeSignatureName t = matchRegexUnifySpaces t "([^ ]+) :: " <&> head
10501102

1051-
findTypeSignatureLine :: T.Text -> T.Text -> Int
1052-
findTypeSignatureLine contents typeSignatureName =
1053-
T.splitOn (typeSignatureName <> " :: ") contents & head & T.lines & length
1054-
10551103
-- | Suggests a constraint for a type signature with any number of existing constraints.
10561104
suggestFunctionConstraint :: DynFlags -> ParsedSource -> Diagnostic -> T.Text -> [(T.Text, Rewrite)]
10571105

@@ -1090,31 +1138,26 @@ suggestFunctionConstraint df (L _ HsModule {hsmodDecls}) Diagnostic {..} missing
10901138
<> "` to the context of the type signature for `" <> typeSignatureName <> "`"
10911139

10921140
-- | Suggests the removal of a redundant constraint for a type signature.
1093-
removeRedundantConstraints :: Maybe T.Text -> Diagnostic -> [(T.Text, TextEdit)]
1094-
removeRedundantConstraints mContents Diagnostic{..}
1141+
removeRedundantConstraints :: DynFlags -> ParsedSource -> Diagnostic -> [(T.Text, Rewrite)]
1142+
removeRedundantConstraints df (L _ HsModule {hsmodDecls}) Diagnostic{..}
10951143
-- • Redundant constraint: Eq a
10961144
-- • In the type signature for:
10971145
-- foo :: forall a. Eq a => a -> a
10981146
-- • Redundant constraints: (Monoid a, Show a)
10991147
-- • In the type signature for:
11001148
-- foo :: forall a. (Num a, Monoid a, Eq a, Show a) => a -> Bool
1101-
| Just contents <- mContents
11021149
-- Account for both "Redundant constraint" and "Redundant constraints".
1103-
, True <- "Redundant constraint" `T.isInfixOf` _message
1150+
| "Redundant constraint" `T.isInfixOf` _message
11041151
, Just typeSignatureName <- findTypeSignatureName _message
1152+
, Just (TypeSig _ _ HsWC{hswc_body = HsIB {hsib_body = sig}})
1153+
<- findSigOfDeclRanged _range hsmodDecls
11051154
, Just redundantConstraintList <- findRedundantConstraints _message
1106-
, Just constraints <- findConstraints contents typeSignatureName
1107-
= let constraintList = parseConstraints constraints
1108-
newConstraints = buildNewConstraints constraintList redundantConstraintList
1109-
typeSignatureLine = findTypeSignatureLine contents typeSignatureName
1110-
typeSignatureFirstChar = T.length $ typeSignatureName <> " :: "
1111-
startOfConstraint = Position typeSignatureLine typeSignatureFirstChar
1112-
endOfConstraint = Position typeSignatureLine $
1113-
typeSignatureFirstChar + T.length (constraints <> " => ")
1114-
range = Range startOfConstraint endOfConstraint
1115-
in [(actionTitle redundantConstraintList typeSignatureName, TextEdit range newConstraints)]
1155+
, rewrite <- removeConstraint (toRemove df redundantConstraintList) sig
1156+
= [(actionTitle redundantConstraintList typeSignatureName, rewrite)]
11161157
| otherwise = []
11171158
where
1159+
toRemove df list a = showSDoc df (ppr a) `elem` (T.unpack <$> list)
1160+
11181161
parseConstraints :: T.Text -> [T.Text]
11191162
parseConstraints t = t
11201163
& (T.strip >>> stripConstraintsParens >>> T.splitOn ",")
@@ -1134,32 +1177,13 @@ removeRedundantConstraints mContents Diagnostic{..}
11341177
& (`matchRegexUnifySpaces` "Redundant constraints?: (.+)")
11351178
<&> (head >>> parseConstraints)
11361179

1137-
-- If the type signature is not formatted as expected (arbitrary number of spaces,
1138-
-- line feeds...), just fail.
1139-
findConstraints :: T.Text -> T.Text -> Maybe T.Text
1140-
findConstraints contents typeSignatureName = do
1141-
constraints <- contents
1142-
& T.splitOn (typeSignatureName <> " :: ")
1143-
& (`atMay` 1)
1144-
>>= (T.splitOn " => " >>> (`atMay` 0))
1145-
guard $ not $ "\n" `T.isInfixOf` constraints || T.strip constraints /= constraints
1146-
return constraints
1147-
11481180
formatConstraints :: [T.Text] -> T.Text
11491181
formatConstraints [] = ""
11501182
formatConstraints [constraint] = constraint
11511183
formatConstraints constraintList = constraintList
11521184
& T.intercalate ", "
11531185
& \cs -> "(" <> cs <> ")"
11541186

1155-
formatConstraintsWithArrow :: [T.Text] -> T.Text
1156-
formatConstraintsWithArrow [] = ""
1157-
formatConstraintsWithArrow cs = cs & formatConstraints & (<> " => ")
1158-
1159-
buildNewConstraints :: [T.Text] -> [T.Text] -> T.Text
1160-
buildNewConstraints constraintList redundantConstraintList =
1161-
formatConstraintsWithArrow $ constraintList \\ redundantConstraintList
1162-
11631187
actionTitle :: [T.Text] -> T.Text -> T.Text
11641188
actionTitle constraintList typeSignatureName =
11651189
"Remove redundant constraint" <> (if length constraintList == 1 then "" else "s") <> " `"

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

+17
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
hideSymbol,
1617
liftParseAST,
@@ -119,6 +120,22 @@ fixParens openDP closeDP ctxt@(L _ elems) = do
119120
dropHsParTy (L _ (HsParTy _ ty)) = ty
120121
dropHsParTy other = other
121122

123+
removeConstraint ::
124+
-- | Predicate: Which context to drop.
125+
(LHsType GhcPs -> Bool) ->
126+
LHsType GhcPs ->
127+
Rewrite
128+
removeConstraint toRemove = go
129+
where
130+
go (L l it@HsQualTy{hst_ctxt = L l' ctxt, hst_body}) = Rewrite l $ \_ -> do
131+
let ctxt' = L l' $ filter (not . toRemove) ctxt
132+
when ((toRemove <$> headMaybe ctxt) == Just True) $
133+
setEntryDPT hst_body (DP (0, 0))
134+
return $ L l $ it{hst_ctxt = ctxt'}
135+
go (L _ (HsParTy _ ty)) = go ty
136+
go (L _ HsForAllTy{hst_body}) = go hst_body
137+
go (L l other) = Rewrite l $ \_ -> return $ L l other
138+
122139
-- | Append a constraint at the end of a type context.
123140
-- If no context is present, a new one will be created.
124141
appendConstraint ::

ghcide/test/exe/Main.hs

+99-8
Original file line numberDiff line numberDiff line change
@@ -2685,6 +2685,7 @@ addImplicitParamsConstraintTests =
26852685
"fCaller :: " <> mkContext contextCaller <> "()",
26862686
"fCaller = fBase"
26872687
]
2688+
26882689
removeRedundantConstraintsTests :: TestTree
26892690
removeRedundantConstraintsTests = let
26902691
header =
@@ -2693,6 +2694,13 @@ removeRedundantConstraintsTests = let
26932694
, ""
26942695
]
26952696

2697+
headerExt :: [T.Text] -> [T.Text]
2698+
headerExt exts =
2699+
redunt : extTxt ++ ["module Testing where"]
2700+
where
2701+
redunt = "{-# OPTIONS_GHC -Wredundant-constraints #-}"
2702+
extTxt = map (\ext -> "{-# LANGUAGE " <> ext <> " #-}") exts
2703+
26962704
redundantConstraintsCode :: Maybe T.Text -> T.Text
26972705
redundantConstraintsCode mConstraint =
26982706
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
@@ -2709,11 +2717,73 @@ removeRedundantConstraintsTests = let
27092717
, "foo x = x == 1"
27102718
]
27112719

2712-
typeSignatureSpaces :: T.Text
2713-
typeSignatureSpaces = T.unlines $ header <>
2714-
[ "foo :: (Num a, Eq a, Monoid a) => a -> Bool"
2715-
, "foo x = x == 1"
2716-
]
2720+
typeSignatureSpaces :: Maybe T.Text -> T.Text
2721+
typeSignatureSpaces mConstraint =
2722+
let constraint = maybe "(Num a, Eq a)" (\c -> "(Num a, Eq a, " <> c <> ")") mConstraint
2723+
in T.unlines $ header <>
2724+
[ "foo :: " <> constraint <> " => a -> Bool"
2725+
, "foo x = x == 1"
2726+
]
2727+
2728+
redundantConstraintsForall :: Maybe T.Text -> T.Text
2729+
redundantConstraintsForall mConstraint =
2730+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2731+
in T.unlines $ headerExt ["RankNTypes"] <>
2732+
[ "foo :: forall a. " <> constraint <> "a -> a"
2733+
, "foo = id"
2734+
]
2735+
2736+
typeSignatureDo :: Maybe T.Text -> T.Text
2737+
typeSignatureDo mConstraint =
2738+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2739+
in T.unlines $ header <>
2740+
[ "f :: Int -> IO ()"
2741+
, "f n = do"
2742+
, " let foo :: " <> constraint <> "a -> IO ()"
2743+
, " foo _ = return ()"
2744+
, " r n"
2745+
]
2746+
2747+
typeSignatureNested :: Maybe T.Text -> T.Text
2748+
typeSignatureNested mConstraint =
2749+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2750+
in T.unlines $ header <>
2751+
[ "f :: Int -> ()"
2752+
, "f = g"
2753+
, " where"
2754+
, " g :: " <> constraint <> "a -> ()"
2755+
, " g _ = ()"
2756+
]
2757+
2758+
typeSignatureNested' :: Maybe T.Text -> T.Text
2759+
typeSignatureNested' mConstraint =
2760+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2761+
in T.unlines $ header <>
2762+
[ "f :: Int -> ()"
2763+
, "f ="
2764+
, " let"
2765+
, " g :: Int -> ()"
2766+
, " g = h"
2767+
, " where"
2768+
, " h :: " <> constraint <> "a -> ()"
2769+
, " h _ = ()"
2770+
, " in g"
2771+
]
2772+
2773+
typeSignatureNested'' :: Maybe T.Text -> T.Text
2774+
typeSignatureNested'' mConstraint =
2775+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2776+
in T.unlines $ header <>
2777+
[ "f :: Int -> ()"
2778+
, "f = g"
2779+
, " where"
2780+
, " g :: Int -> ()"
2781+
, " g = "
2782+
, " let"
2783+
, " h :: " <> constraint <> "a -> ()"
2784+
, " h _ = ()"
2785+
, " in h"
2786+
]
27172787

27182788
typeSignatureMultipleLines :: T.Text
27192789
typeSignatureMultipleLines = T.unlines $ header <>
@@ -2752,9 +2822,30 @@ removeRedundantConstraintsTests = let
27522822
"Remove redundant constraints `(Monoid a, Show a)` from the context of the type signature for `foo`"
27532823
(redundantMixedConstraintsCode $ Just "Monoid a, Show a")
27542824
(redundantMixedConstraintsCode Nothing)
2755-
, checkPeculiarFormatting
2756-
"should do nothing when constraints contain an arbitrary number of spaces"
2757-
typeSignatureSpaces
2825+
, check
2826+
"Remove redundant constraint `Eq a` from the context of the type signature for `g`"
2827+
(typeSignatureNested $ Just "Eq a")
2828+
(typeSignatureNested Nothing)
2829+
, check
2830+
"Remove redundant constraint `Eq a` from the context of the type signature for `h`"
2831+
(typeSignatureNested' $ Just "Eq a")
2832+
(typeSignatureNested' Nothing)
2833+
, check
2834+
"Remove redundant constraint `Eq a` from the context of the type signature for `h`"
2835+
(typeSignatureNested'' $ Just "Eq a")
2836+
(typeSignatureNested'' Nothing)
2837+
, check
2838+
"Remove redundant constraint `Eq a` from the context of the type signature for `foo`"
2839+
(redundantConstraintsForall $ Just "Eq a")
2840+
(redundantConstraintsForall Nothing)
2841+
, check
2842+
"Remove redundant constraint `Eq a` from the context of the type signature for `foo`"
2843+
(typeSignatureDo $ Just "Eq a")
2844+
(typeSignatureDo Nothing)
2845+
, check
2846+
"Remove redundant constraints `(Monoid a, Show a)` from the context of the type signature for `foo`"
2847+
(typeSignatureSpaces $ Just "Monoid a, Show a")
2848+
(typeSignatureSpaces Nothing)
27582849
, checkPeculiarFormatting
27592850
"should do nothing when constraints contain line feeds"
27602851
typeSignatureMultipleLines

0 commit comments

Comments
 (0)