[commit: testsuite] master: Add new test for #8020. (ccd0054)

Richard Eisenberg eir at ghc.haskell.org
Fri Aug 2 13:56:36 CEST 2013


Repository : http://darcs.haskell.org/ghc.git/

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ccd0054decd13df681116b3ccbd8f4ad0a1ae033

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

commit ccd0054decd13df681116b3ccbd8f4ad0a1ae033
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Fri Aug 2 12:56:18 2013 +0100

    Add new test for #8020.

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

 tests/indexed-types/should_compile/T8020.hs |   17 +++++++++++++++++
 tests/indexed-types/should_compile/all.T    |    1 +
 2 files changed, 18 insertions(+)

diff --git a/tests/indexed-types/should_compile/T8020.hs b/tests/indexed-types/should_compile/T8020.hs
new file mode 100644
index 0000000..61331c8
--- /dev/null
+++ b/tests/indexed-types/should_compile/T8020.hs
@@ -0,0 +1,17 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module T8020 where
+
+type family F a b where
+  F (Maybe a) [a] = Int
+  F b c           = Bool
+
+data Proxy a = P
+
+type family G
+
+foo :: Proxy d -> F d d -> Bool
+foo _ = not
+
+bar :: Bool -> Bool
+bar = foo (P :: Proxy G)
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index f8f455f..a64c19b 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -227,3 +227,4 @@ test('T8011',
      ['$MAKE -s --no-print-directory T8011'])
 
 test('T8018', normal, compile, [''])
+test('T8020', normal, compile, [''])
\ No newline at end of file






More information about the ghc-commits mailing list