@@ -14,7 +14,8 @@ module Development.IDE.Plugin.CodeAction
14
14
, matchRegExMultipleImports
15
15
) where
16
16
17
- import Bag (isEmptyBag )
17
+ import Bag (bagToList ,
18
+ isEmptyBag )
18
19
import Control.Applicative ((<|>) )
19
20
import Control.Arrow (second ,
20
21
(>>>) )
@@ -72,7 +73,6 @@ import Outputable (Outputable,
72
73
showSDocUnsafe )
73
74
import RdrName (GlobalRdrElt (.. ),
74
75
lookupGlobalRdrEnv )
75
- import Safe (atMay )
76
76
import SrcLoc (realSrcSpanEnd ,
77
77
realSrcSpanStart )
78
78
import TcRnTypes (ImportAvails (.. ),
@@ -162,6 +162,57 @@ findSigOfDecl pred decls =
162
162
any (pred . unLoc) idsSig
163
163
]
164
164
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
+
165
216
findInstanceHead :: (Outputable (HsType p )) => DynFlags -> String -> [LHsDecl p ] -> Maybe (LHsType p )
166
217
findInstanceHead df instanceHead decls =
167
218
listToMaybe
@@ -173,6 +224,7 @@ findInstanceHead df instanceHead decls =
173
224
findDeclContainingLoc :: Position -> [Located a ] -> Maybe (Located a )
174
225
findDeclContainingLoc loc = find (\ (L l _) -> loc `isInsideSrcSpan` l)
175
226
227
+
176
228
-- Single:
177
229
-- This binding for ‘mod’ shadows the existing binding
178
230
-- 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
1048
1100
findTypeSignatureName :: T. Text -> Maybe T. Text
1049
1101
findTypeSignatureName t = matchRegexUnifySpaces t " ([^ ]+) :: " <&> head
1050
1102
1051
- findTypeSignatureLine :: T. Text -> T. Text -> Int
1052
- findTypeSignatureLine contents typeSignatureName =
1053
- T. splitOn (typeSignatureName <> " :: " ) contents & head & T. lines & length
1054
-
1055
1103
-- | Suggests a constraint for a type signature with any number of existing constraints.
1056
1104
suggestFunctionConstraint :: DynFlags -> ParsedSource -> Diagnostic -> T. Text -> [(T. Text , Rewrite )]
1057
1105
@@ -1090,31 +1138,26 @@ suggestFunctionConstraint df (L _ HsModule {hsmodDecls}) Diagnostic {..} missing
1090
1138
<> " ` to the context of the type signature for `" <> typeSignatureName <> " `"
1091
1139
1092
1140
-- | 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 {.. }
1095
1143
-- • Redundant constraint: Eq a
1096
1144
-- • In the type signature for:
1097
1145
-- foo :: forall a. Eq a => a -> a
1098
1146
-- • Redundant constraints: (Monoid a, Show a)
1099
1147
-- • In the type signature for:
1100
1148
-- foo :: forall a. (Num a, Monoid a, Eq a, Show a) => a -> Bool
1101
- | Just contents <- mContents
1102
1149
-- Account for both "Redundant constraint" and "Redundant constraints".
1103
- , True <- " Redundant constraint" `T.isInfixOf` _message
1150
+ | " Redundant constraint" `T.isInfixOf` _message
1104
1151
, Just typeSignatureName <- findTypeSignatureName _message
1152
+ , Just (TypeSig _ _ HsWC {hswc_body = HsIB {hsib_body = sig}})
1153
+ <- findSigOfDeclRanged _range hsmodDecls
1105
1154
, 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)]
1116
1157
| otherwise = []
1117
1158
where
1159
+ toRemove df list a = showSDoc df (ppr a) `elem` (T. unpack <$> list)
1160
+
1118
1161
parseConstraints :: T. Text -> [T. Text ]
1119
1162
parseConstraints t = t
1120
1163
& (T. strip >>> stripConstraintsParens >>> T. splitOn " ," )
@@ -1134,32 +1177,13 @@ removeRedundantConstraints mContents Diagnostic{..}
1134
1177
& (`matchRegexUnifySpaces` " Redundant constraints?: (.+)" )
1135
1178
<&> (head >>> parseConstraints)
1136
1179
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
-
1148
1180
formatConstraints :: [T. Text ] -> T. Text
1149
1181
formatConstraints [] = " "
1150
1182
formatConstraints [constraint] = constraint
1151
1183
formatConstraints constraintList = constraintList
1152
1184
& T. intercalate " , "
1153
1185
& \ cs -> " (" <> cs <> " )"
1154
1186
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
-
1163
1187
actionTitle :: [T. Text ] -> T. Text -> T. Text
1164
1188
actionTitle constraintList typeSignatureName =
1165
1189
" Remove redundant constraint" <> (if length constraintList == 1 then " " else " s" ) <> " `"
0 commit comments