[commit: ghc] ghc-8.6: testsuite: Add (broken) test for #15473 (7c819cb)

git at git.haskell.org git at git.haskell.org
Thu Aug 23 22:50:45 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : ghc-8.6
Link       : http://ghc.haskell.org/trac/ghc/changeset/7c819cbed9677e840d8233aed1f88f27579545b4/ghc

>---------------------------------------------------------------

commit 7c819cbed9677e840d8233aed1f88f27579545b4
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Aug 7 13:59:31 2018 -0400

    testsuite: Add (broken) test for #15473
    
    (cherry picked from commit 5487f305d9dea298f0822082389d8a0225956c55)


>---------------------------------------------------------------

7c819cbed9677e840d8233aed1f88f27579545b4
 testsuite/tests/typecheck/should_compile/T15473.hs | 12 ++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  2 +-
 2 files changed, 13 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/typecheck/should_compile/T15473.hs b/testsuite/tests/typecheck/should_compile/T15473.hs
new file mode 100644
index 0000000..d6bf57b
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T15473.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE TypeOperators #-}
+-- {-# LANGUAGE UndecidableInstances #-}
+module Bug where
+
+type family Undefined :: k where {}
+
+type family LetInterleave xs t ts is (a_ahkO :: [a]) (a_ahkP :: [[a]]) :: [[a]] where
+  LetInterleave xs t ts is y z = Undefined y z
+
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index a7b283d..6e0398d 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -646,4 +646,4 @@ test('T15428', normal, compile, [''])
 test('T15431', normal, compile, [''])
 test('T15431a', normal, compile, [''])
 test('T15412', normal, compile, [''])
-test('T15499', normal, compile, [''])
+test('T15473', expect_broken(15473), compile, [''])



More information about the ghc-commits mailing list