Skip to content
Snippets Groups Projects
Commit 43f63a6b authored by Tao He's avatar Tao He Committed by Ben Gamari
Browse files

UnboxedTuples can't be used as constraints

Fixes #14740.

Test Plan: make test TEST="14740"

Reviewers: bgamari, simonpj

Reviewed By: simonpj

Subscribers: simonpj, rwbarton, thomie, carter

GHC Trac Issues: #14740

Differential Revision: https://phabricator.haskell.org/D4359

(cherry picked from commit ced9fbd3)
parent e04aaf75
No related branches found
No related tags found
No related merge requests found
......@@ -779,11 +779,22 @@ checkTyClHdr is_cls ty
= parseErrorSDoc l (text "Malformed head of type or class declaration:"
<+> ppr ty)
-- | 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
......
{-# LANGUAGE UnboxedTuples #-}
module T14740 where
x :: ((##)) => ()
x = ()
T14740.hs:5:7:
Expecting a lifted type, but ‘(# #)’ is unlifted
In the type signature: x :: ((# #)) => ()
......@@ -103,3 +103,4 @@ test('T8501b', normal, compile_fail, [''])
test('T8501c', normal, compile_fail, [''])
test('T12610', normal, compile_fail, [''])
test('InfixAppPatErr', normal, compile_fail, [''])
test('T14740', normal, compile_fail, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment