[commit: testsuite] master: Test Trac #8651 (b662393)

git at git.haskell.org git at git.haskell.org
Fri Jan 10 09:28:25 UTC 2014


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

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

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

commit b662393ef802b80e211f494f7b22aa1964faaed5
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Jan 10 09:28:11 2014 +0000

    Test Trac #8651


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

b662393ef802b80e211f494f7b22aa1964faaed5
 tests/indexed-types/should_compile/T8651.hs |   14 ++++++++++++++
 tests/indexed-types/should_compile/all.T    |    1 +
 2 files changed, 15 insertions(+)

diff --git a/tests/indexed-types/should_compile/T8651.hs b/tests/indexed-types/should_compile/T8651.hs
new file mode 100644
index 0000000..a13c91b
--- /dev/null
+++ b/tests/indexed-types/should_compile/T8651.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE RankNTypes, FlexibleContexts, TypeFamilies #-}
+module T8651 where
+
+import Data.Monoid
+
+type family Id a
+
+type instance Id a = a
+ --type instance Id [a] = [Id a]
+
+foo :: (Monoid (Id String) => r) -> r
+foo x = x
+
+bar = foo "Hello"
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index 66e30b2..3b69ec9 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -238,3 +238,4 @@ test('ClosedFam1', extra_clean(['ClosedFam1.o-boot', 'ClosedFam1.hi-boot']),
      multimod_compile, ['ClosedFam1', '-v0'])
 test('ClosedFam2', extra_clean(['ClosedFam2.o-boot', 'ClosedFam2.hi-boot']),
      multimod_compile, ['ClosedFam2', '-v0'])
+test('T8651', normal, compile, [''])



More information about the ghc-commits mailing list