Skip to content

Commit c20631b

Browse files
committed
Fix remove constraint for signatures with forall
1 parent a04bb85 commit c20631b

File tree

1 file changed

+36
-1
lines changed

1 file changed

+36
-1
lines changed

ghcide/test/exe/Main.hs

Lines changed: 36 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2594,6 +2594,7 @@ addImplicitParamsConstraintTests =
25942594
"fCaller :: " <> mkContext contextCaller <> "()",
25952595
"fCaller = fBase"
25962596
]
2597+
25972598
removeRedundantConstraintsTests :: TestTree
25982599
removeRedundantConstraintsTests = let
25992600
header =
@@ -2602,6 +2603,13 @@ removeRedundantConstraintsTests = let
26022603
, ""
26032604
]
26042605

2606+
headerExt :: [T.Text] -> [T.Text]
2607+
headerExt exts =
2608+
redunt : extTxt ++ ["module Testing where"]
2609+
where
2610+
redunt = "{-# OPTIONS_GHC -Wredundant-constraints #-}"
2611+
extTxt = map (\ext -> "{-# LANGUAGE " <> ext <> " #-}") exts
2612+
26052613
redundantConstraintsCode :: Maybe T.Text -> T.Text
26062614
redundantConstraintsCode mConstraint =
26072615
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
@@ -2624,6 +2632,25 @@ removeRedundantConstraintsTests = let
26242632
, "foo x = x == 1"
26252633
]
26262634

2635+
redundantConstraintsForall :: Maybe T.Text -> T.Text
2636+
redundantConstraintsForall mConstraint =
2637+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2638+
in T.unlines $ (headerExt ["RankNTypes"]) <>
2639+
[ "foo :: forall a. " <> constraint <> "a -> a"
2640+
, "foo = id"
2641+
]
2642+
2643+
typeSignatureNested :: Maybe T.Text -> T.Text
2644+
typeSignatureNested mConstraint =
2645+
let constraint = maybe "" (\c -> "" <> c <> " => ") mConstraint
2646+
in T.unlines $ header <>
2647+
[ "f :: Int -> ()"
2648+
, "f = g"
2649+
, " where"
2650+
, " g :: " <> constraint <> "a -> ()"
2651+
, " g _ = ()"
2652+
]
2653+
26272654
typeSignatureMultipleLines :: T.Text
26282655
typeSignatureMultipleLines = T.unlines $ header <>
26292656
[ "foo :: (Num a, Eq a, Monoid a)"
@@ -2635,7 +2662,7 @@ removeRedundantConstraintsTests = let
26352662
check actionTitle originalCode expectedCode = testSession (T.unpack actionTitle) $ do
26362663
doc <- createDoc "Testing.hs" "haskell" originalCode
26372664
_ <- waitForDiagnostics
2638-
actionsOrCommands <- getCodeActions doc (Range (Position 4 0) (Position 4 maxBound))
2665+
actionsOrCommands <- getAllCodeActions doc
26392666
chosenAction <- liftIO $ pickActionWithTitle actionTitle actionsOrCommands
26402667
executeCodeAction chosenAction
26412668
modifiedCode <- documentContents doc
@@ -2661,6 +2688,14 @@ removeRedundantConstraintsTests = let
26612688
"Remove redundant constraints `(Monoid a, Show a)` from the context of the type signature for `foo`"
26622689
(redundantMixedConstraintsCode $ Just "Monoid a, Show a")
26632690
(redundantMixedConstraintsCode Nothing)
2691+
, check
2692+
"Remove redundant constraint `Eq a` from the context of the type signature for `g`"
2693+
(typeSignatureNested $ Just "Eq a")
2694+
(typeSignatureNested Nothing)
2695+
, check
2696+
"Remove redundant constraint `Eq a` from the context of the type signature for `foo`"
2697+
(redundantConstraintsForall $ Just "Eq a")
2698+
(redundantConstraintsForall Nothing)
26642699
, checkPeculiarFormatting
26652700
"should do nothing when constraints contain an arbitrary number of spaces"
26662701
typeSignatureSpaces

0 commit comments

Comments
 (0)