Skip to content

Commit 1fc2ebf

Browse files
committed
Find signatures which are deeply nested
1 parent c20631b commit 1fc2ebf

File tree

2 files changed

+74
-11
lines changed

2 files changed

+74
-11
lines changed

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

Lines changed: 36 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,8 @@ module Development.IDE.Plugin.CodeAction
1515
, matchRegExMultipleImports
1616
) where
1717

18-
import Bag (isEmptyBag)
18+
import Bag (bagToList,
19+
isEmptyBag)
1920
import Control.Applicative ((<|>))
2021
import Control.Arrow (second,
2122
(>>>))
@@ -179,27 +180,51 @@ findSigOfDecl pred decls =
179180
any (pred . unLoc) idsSig
180181
]
181182

182-
findSigOfDecl' :: Range -> [LHsDecl p] -> Either String (Sig p)
183-
findSigOfDecl' range decls = do
183+
findSigOfDeclRanged :: Range -> [LHsDecl p] -> Either String (Sig p)
184+
findSigOfDeclRanged range decls = do
184185
dec <- findDeclContainingLocE (_start range) decls
185186
case dec of
186187
L _ (SigD _ sig@(TypeSig {})) -> Right sig
187188
L _ (ValD _ (bind :: HsBind p)) -> findSigOfBind range bind
188-
_ -> Left "Other"
189+
_ -> Left "findSigOfDeclRanged"
189190

190191
findSigOfBind :: Range -> HsBind p -> Either String (Sig p)
191192
findSigOfBind range bind =
192193
case bind of
193194
FunBind {} -> findSigOfLMatch (unLoc $ mg_alts (fun_matches bind))
194-
_ -> Left "Other findSigOfBind"
195+
_ -> Left "findSigOfBind"
195196
where
196-
findSigOfLMatch :: [LMatch p (LHsExpr idR)] -> Either String (Sig p)
197+
findSigOfLMatch :: [LMatch p (LHsExpr p)] -> Either String (Sig p)
197198
findSigOfLMatch ls = do
198199
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"
200+
findSigOfGRHSs (m_grhss (unLoc match))
201+
202+
findSigOfGRHSs :: GRHSs p (LHsExpr p) -> Either String (Sig p)
203+
findSigOfGRHSs grhs = do
204+
if (_start range) `isInsideSrcSpan` (getLoc $ grhssLocalBinds grhs)
205+
then findSigOfBinds range (unLoc (grhssLocalBinds grhs)) -- where clause
206+
else do
207+
grhs <- findDeclContainingLocE (_start range) (grhssGRHSs grhs)
208+
case unLoc grhs of
209+
GRHS _ _ bd -> findSigOfExpr (unLoc bd)
210+
_ -> Left "findSigOfGRHSs"
211+
212+
findSigOfExpr :: HsExpr p -> Either String (Sig p)
213+
findSigOfExpr = go
214+
where
215+
go (HsLet _ binds _) = findSigOfBinds range (unLoc binds)
216+
go _ = Left "findSigOfExpr"
217+
218+
findSigOfBinds :: Range -> HsLocalBinds p -> Either String (Sig p)
219+
findSigOfBinds range = go
220+
where
221+
go (HsValBinds _ (ValBinds _ binds lsigs)) =
222+
case unLoc <$> findDeclContainingLocE (_start range) lsigs of
223+
Right sig' -> Right sig'
224+
Left _ -> do
225+
lHsBindLR <- findDeclContainingLocE (_start range) (bagToList binds)
226+
findSigOfBind range (unLoc lHsBindLR)
227+
go _ = Left "findSigOfBinds"
203228

204229
findDeclContainingLocE :: Position -> [Located a] -> Either String (Located a)
205230
findDeclContainingLocE loc ls =
@@ -1114,7 +1139,7 @@ removeRedundantConstraints df m Diagnostic{..}
11141139
, True <- "Redundant constraint" `T.isInfixOf` _message
11151140
, Just typeSignatureName <- findTypeSignatureName _message
11161141
, Right (TypeSig _ _ HsWC{hswc_body = HsIB {hsib_body = sig}})
1117-
<- findSigOfDecl' _range hsmodDecls
1142+
<- findSigOfDeclRanged _range hsmodDecls
11181143
, Just redundantConstraintList <- findRedundantConstraints _message
11191144
, rewrite' <- removeConstraint (pred df redundantConstraintList) sig
11201145
= [(actionTitle redundantConstraintList typeSignatureName, [rewrite'])]

ghcide/test/exe/Main.hs

Lines changed: 38 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2651,6 +2651,36 @@ removeRedundantConstraintsTests = let
26512651
, " g _ = ()"
26522652
]
26532653

2654+
typeSignatureNested' :: Maybe T.Text -> T.Text
2655+
typeSignatureNested' mConstraint =
2656+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2657+
in T.unlines $ header <>
2658+
[ "f :: Int -> ()"
2659+
, "f ="
2660+
, " let"
2661+
, " g :: Int -> ()"
2662+
, " g = h"
2663+
, " where"
2664+
, " h :: " <> constraint <> "a -> ()"
2665+
, " h _ = ()"
2666+
, " in g"
2667+
]
2668+
2669+
typeSignatureNested'' :: Maybe T.Text -> T.Text
2670+
typeSignatureNested'' mConstraint =
2671+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2672+
in T.unlines $ header <>
2673+
[ "f :: Int -> ()"
2674+
, "f = g"
2675+
, " where"
2676+
, " g :: Int -> ()"
2677+
, " g = "
2678+
, " let"
2679+
, " h :: " <> constraint <> "a -> ()"
2680+
, " h _ = ()"
2681+
, " in h"
2682+
]
2683+
26542684
typeSignatureMultipleLines :: T.Text
26552685
typeSignatureMultipleLines = T.unlines $ header <>
26562686
[ "foo :: (Num a, Eq a, Monoid a)"
@@ -2692,6 +2722,14 @@ removeRedundantConstraintsTests = let
26922722
"Remove redundant constraint `Eq a` from the context of the type signature for `g`"
26932723
(typeSignatureNested $ Just "Eq a")
26942724
(typeSignatureNested Nothing)
2725+
, check
2726+
"Remove redundant constraint `Eq a` from the context of the type signature for `h`"
2727+
(typeSignatureNested' $ Just "Eq a")
2728+
(typeSignatureNested' Nothing)
2729+
, check
2730+
"Remove redundant constraint `Eq a` from the context of the type signature for `h`"
2731+
(typeSignatureNested'' $ Just "Eq a")
2732+
(typeSignatureNested'' Nothing)
26952733
, check
26962734
"Remove redundant constraint `Eq a` from the context of the type signature for `foo`"
26972735
(redundantConstraintsForall $ Just "Eq a")

0 commit comments

Comments
 (0)