[commit: ghc] master: Test Trac #13490 (eb6ccb7)

git at git.haskell.org git at git.haskell.org
Tue Mar 28 07:50:30 UTC 2017


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

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

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

commit eb6ccb7cd8751cd027ee9913e47f1371bfa62289
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Mar 28 08:44:11 2017 +0100

    Test Trac #13490


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

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

diff --git a/testsuite/tests/typecheck/should_compile/T13490.hs b/testsuite/tests/typecheck/should_compile/T13490.hs
new file mode 100644
index 0000000..72e0ede
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T13490.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
+
+module T13490 where
+
+import Data.Typeable
+
+type family Foo a
+
+data C a
+
+foo :: (Typeable (C z), z ~ Foo zp) => C zp
+foo = undefined
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 97a5350..cfc4eff 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -547,3 +547,4 @@ test('T13381', normal, compile_fail, [''])
 test('T13337', normal, compile, [''])
 test('T13343', normal, compile, [''])
 test('T13458', normal, compile, [''])
+test('T13490', normal, compile, [''])



More information about the ghc-commits mailing list