Skip to content
Snippets Groups Projects
Commit 83dce402 authored by Zubin's avatar Zubin Committed by Marge Bot
Browse files

Add regression test for #19921

parent eb39981a
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE
QuantifiedConstraints
, StandaloneKindSignatures
, TypeOperators
, GADTs
, ConstraintKinds
, RankNTypes
, UndecidableInstances
, ImpredicativeTypes
#-}
module Typelevel.Constraint.Repro where
import Data.Kind (Constraint, Type)
type Dict :: Constraint -> Type
data Dict c
where
Dict :: c => Dict c
type () :: Constraint -> Constraint -> Constraint
type c d = c => d
infixr 0
type (\/) :: Constraint -> Constraint -> Constraint
type a \/ b = (forall r. (a r, b r) r)
infixr 5 \/
dict :: Dict ((x \/ y) \/ z x \/ y \/ z)
dict = Dict
T19921.hs:29:8: error:
• Could not deduce: r arising from a use of ‘Dict’
from the context: (x \/ y) \/ z
bound by a quantified context at T19921.hs:1:1
or from: (x ⇒ r, (y \/ z) ⇒ r)
bound by a quantified context at T19921.hs:1:1
• In the expression: Dict
In an equation for ‘dict’: dict = Dict
......@@ -30,3 +30,4 @@ test('T17267d', normal, compile_and_run, [''])
test('T17267e', normal, compile_fail, [''])
test('T17458', normal, compile_fail, [''])
test('T18432', normal, compile, [''])
test('T19921', 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