@@ -71,7 +71,6 @@ import Outputable (Outputable,
71
71
showSDocUnsafe )
72
72
import RdrName (GlobalRdrElt (.. ),
73
73
lookupGlobalRdrEnv )
74
- import Safe (atMay )
75
74
import SrcLoc (realSrcSpanStart )
76
75
import TcRnTypes (ImportAvails (.. ),
77
76
TcGblEnv (.. ))
@@ -158,7 +157,7 @@ suggestAction packageExports ideOptions parsedModule text df annSource tcM har d
158
157
, suggestFixConstructorImport text diag
159
158
, suggestModuleTypo diag
160
159
, suggestReplaceIdentifier text diag
161
- , removeRedundantConstraints text diag
160
+ , rewrite df annSource $ \ df _ps -> removeRedundantConstraints df parsedModule diag
162
161
, suggestAddTypeAnnotationToSatisfyContraints text diag
163
162
, rewrite df annSource $ \ df ps -> suggestConstraint df ps diag
164
163
, rewrite df annSource $ \ _ ps -> suggestImplicitParameter ps diag
@@ -180,6 +179,32 @@ findSigOfDecl pred decls =
180
179
any (pred . unLoc) idsSig
181
180
]
182
181
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
+
183
208
findInstanceHead :: (Outputable (HsType p )) => DynFlags -> String -> [LHsDecl p ] -> Maybe (LHsType p )
184
209
findInstanceHead df instanceHead decls =
185
210
listToMaybe
@@ -191,6 +216,7 @@ findInstanceHead df instanceHead decls =
191
216
findDeclContainingLoc :: Position -> [Located a ] -> Maybe (Located a )
192
217
findDeclContainingLoc loc = find (\ (L l _) -> loc `isInsideSrcSpan` l)
193
218
219
+
194
220
-- Single:
195
221
-- This binding for ‘mod’ shadows the existing binding
196
222
-- 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
1037
1063
findTypeSignatureName :: T. Text -> Maybe T. Text
1038
1064
findTypeSignatureName t = matchRegexUnifySpaces t " ([^ ]+) :: " <&> head
1039
1065
1040
- findTypeSignatureLine :: T. Text -> T. Text -> Int
1041
- findTypeSignatureLine contents typeSignatureName =
1042
- T. splitOn (typeSignatureName <> " :: " ) contents & head & T. lines & length
1043
-
1044
1066
-- | Suggests a constraint for a type signature with any number of existing constraints.
1045
1067
suggestFunctionConstraint :: DynFlags -> ParsedSource -> Diagnostic -> T. Text -> [(T. Text , Rewrite )]
1046
1068
@@ -1079,31 +1101,27 @@ suggestFunctionConstraint df (L _ HsModule {hsmodDecls}) Diagnostic {..} missing
1079
1101
<> " ` to the context of the type signature for `" <> typeSignatureName <> " `"
1080
1102
1081
1103
-- | 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 {.. }
1084
1106
-- • Redundant constraint: Eq a
1085
1107
-- • In the type signature for:
1086
1108
-- foo :: forall a. Eq a => a -> a
1087
1109
-- • Redundant constraints: (Monoid a, Show a)
1088
1110
-- • In the type signature for:
1089
1111
-- 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
1091
1113
-- Account for both "Redundant constraint" and "Redundant constraints".
1092
1114
, True <- " Redundant constraint" `T.isInfixOf` _message
1093
1115
, Just typeSignatureName <- findTypeSignatureName _message
1116
+ , Right (TypeSig _ _ HsWC {hswc_body = HsIB {hsib_body = sig}})
1117
+ <- findSigOfDecl' _range hsmodDecls
1094
1118
, 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'])]
1105
1121
| otherwise = []
1106
1122
where
1123
+ pred df list a = elem (showSDoc df (ppr a)) (T. unpack <$> list)
1124
+
1107
1125
parseConstraints :: T. Text -> [T. Text ]
1108
1126
parseConstraints t = t
1109
1127
& (T. strip >>> stripConstraintsParens >>> T. splitOn " ," )
@@ -1123,32 +1141,13 @@ removeRedundantConstraints mContents Diagnostic{..}
1123
1141
& (`matchRegexUnifySpaces` " Redundant constraints?: (.+)" )
1124
1142
<&> (head >>> parseConstraints)
1125
1143
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
-
1137
1144
formatConstraints :: [T. Text ] -> T. Text
1138
1145
formatConstraints [] = " "
1139
1146
formatConstraints [constraint] = constraint
1140
1147
formatConstraints constraintList = constraintList
1141
1148
& T. intercalate " , "
1142
1149
& \ cs -> " (" <> cs <> " )"
1143
1150
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
-
1152
1151
actionTitle :: [T. Text ] -> T. Text -> T. Text
1153
1152
actionTitle constraintList typeSignatureName =
1154
1153
" Remove redundant constraint" <> (if length constraintList == 1 then " " else " s" ) <> " `"
0 commit comments