[commit: ghc] master: testsuite: Add testcase for #13248 (c22cd7c)

git at git.haskell.org git at git.haskell.org
Thu Feb 9 21:34:16 UTC 2017


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/c22cd7cc28238cf84f90dda9961064f5ea44761d/ghc

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

commit c22cd7cc28238cf84f90dda9961064f5ea44761d
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Wed Feb 8 23:31:04 2017 -0500

    testsuite: Add testcase for #13248


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

c22cd7cc28238cf84f90dda9961064f5ea44761d
 testsuite/tests/typecheck/should_compile/T13248.hs | 12 ++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 2 files changed, 13 insertions(+)

diff --git a/testsuite/tests/typecheck/should_compile/T13248.hs b/testsuite/tests/typecheck/should_compile/T13248.hs
new file mode 100644
index 0000000..b2eebc7
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T13248.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE TypeFamilies, TypeFamilyDependencies, UndecidableInstances #-}
+
+type family Foo a = r | r -> a where
+        Foo Int = Char
+        Foo Integer = String
+
+type family Bar a = r | r -> a where
+        Bar Char = Double
+        Bar String = Float
+
+type family Baz a = r | r -> a where
+        Baz x = Bar (Foo x)
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index ccebf75..7d2e3c6 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -535,3 +535,4 @@ test('T13083', normal, compile, [''])
 test('T11723', normal, compile, [''])
 test('T12987', normal, compile, [''])
 test('T11736', normal, compile, [''])
+test('T13248', expect_broken(13248), compile, [''])



More information about the ghc-commits mailing list