summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/parser/RdrHsSyn.hs13
-rw-r--r--testsuite/tests/parser/should_fail/T14740.hs6
-rw-r--r--testsuite/tests/parser/should_fail/T14740.stderr4
-rw-r--r--testsuite/tests/parser/should_fail/all.T1
4 files changed, 23 insertions, 1 deletions
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index fcb1fede20..357d22438a 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -849,11 +849,22 @@ checkBlockArguments expr = case unLoc expr of
$$ text "You could write it with parentheses"
$$ text "Or perhaps you meant to enable BlockArguments?"
+-- | Validate the context constraints and break up a context into a list
+-- of predicates.
+--
+-- @
+-- (Eq a, Ord b) --> [Eq a, Ord b]
+-- Eq a --> [Eq a]
+-- (Eq a) --> [Eq a]
+-- (((Eq a))) --> [Eq a]
+-- @
checkContext :: LHsType GhcPs -> P ([AddAnn],LHsContext GhcPs)
checkContext (L l orig_t)
= check [] (L l orig_t)
where
- check anns (L lp (HsTupleTy _ ts)) -- (Eq a, Ord b) shows up as a tuple type
+ check anns (L lp (HsTupleTy HsBoxedOrConstraintTuple ts))
+ -- (Eq a, Ord b) shows up as a tuple type. Only boxed tuples can
+ -- be used as context constraints.
= return (anns ++ mkParensApiAnn lp,L l ts) -- Ditto ()
-- don't let HsAppsTy get in the way
diff --git a/testsuite/tests/parser/should_fail/T14740.hs b/testsuite/tests/parser/should_fail/T14740.hs
new file mode 100644
index 0000000000..b56687f051
--- /dev/null
+++ b/testsuite/tests/parser/should_fail/T14740.hs
@@ -0,0 +1,6 @@
+{-# LANGUAGE UnboxedTuples #-}
+
+module T14740 where
+
+x :: ((##)) => ()
+x = ()
diff --git a/testsuite/tests/parser/should_fail/T14740.stderr b/testsuite/tests/parser/should_fail/T14740.stderr
new file mode 100644
index 0000000000..8827873e25
--- /dev/null
+++ b/testsuite/tests/parser/should_fail/T14740.stderr
@@ -0,0 +1,4 @@
+
+T14740.hs:5:7:
+ Expecting a lifted type, but ‘(# #)’ is unlifted
+ In the type signature: x :: ((# #)) => ()
diff --git a/testsuite/tests/parser/should_fail/all.T b/testsuite/tests/parser/should_fail/all.T
index 6f6331ff06..ef47ed3394 100644
--- a/testsuite/tests/parser/should_fail/all.T
+++ b/testsuite/tests/parser/should_fail/all.T
@@ -106,6 +106,7 @@ test('T8501b', normal, compile_fail, [''])
test('T8501c', normal, compile_fail, [''])
test('T12610', normal, compile_fail, [''])
test('T14588', normal, compile_fail, [''])
+test('T14740', normal, compile_fail, [''])
test('NoNumericUnderscores0', normal, compile_fail, [''])
test('NoNumericUnderscores1', normal, compile_fail, [''])