diff --git a/testsuite/tests/indexed-types/should_compile/T10806.hs b/testsuite/tests/indexed-types/should_compile/T10806.hs new file mode 100644 index 0000000000000000000000000000000000000000..149cd0f20335be82f0c17c8ff3ce25fa9c707e0d --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T10806.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE GADTs, ExplicitNamespaces, TypeOperators, DataKinds #-} + +module T10806 where + +import GHC.TypeLits (Nat, type (<=)) + +data Q a where + Q :: (a <= b, b <= c) => proxy a -> proxy b -> Q c + +triggersLoop :: Q b -> Q b -> Bool +triggersLoop (Q _ _) (Q _ _) = print 'x' 'y' diff --git a/testsuite/tests/indexed-types/should_compile/T10806.stderr b/testsuite/tests/indexed-types/should_compile/T10806.stderr new file mode 100644 index 0000000000000000000000000000000000000000..350310549861784d9585af3a461c743814bb733d --- /dev/null +++ b/testsuite/tests/indexed-types/should_compile/T10806.stderr @@ -0,0 +1,9 @@ + +T10806.hs:11:32: error: + Couldn't match expected type ‘Char -> Bool’ + with actual type ‘IO ()’ + The function ‘print’ is applied to two arguments, + but its type ‘Char -> IO ()’ has only one + In the expression: print 'x' 'y' + In an equation for ‘triggersLoop’: + triggersLoop (Q _ _) (Q _ _) = print 'x' 'y' diff --git a/testsuite/tests/indexed-types/should_compile/all.T b/testsuite/tests/indexed-types/should_compile/all.T index 7bbb04b7fc6b4e8c3011596f604fcd92ceb42b82..5e7e4687663f230a8c0c31bf4ebbb02992efeb05 100644 --- a/testsuite/tests/indexed-types/should_compile/all.T +++ b/testsuite/tests/indexed-types/should_compile/all.T @@ -262,4 +262,4 @@ test('T10507', normal, compile, ['']) test('T10634', normal, compile, ['']) test('T10713', normal, compile, ['']) test('T10753', normal, compile, ['']) - +test('T10806', normal, compile_fail, [''])