[commit: testsuite] master: Add new test case T7585. (3c0c3d9)

Richard Eisenberg eir at cis.upenn.edu
Wed Jan 16 05:05:40 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/3c0c3d9c8cf9ea17d003c6629ae978f8dec05989

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

commit 3c0c3d9c8cf9ea17d003c6629ae978f8dec05989
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Tue Jan 15 17:17:46 2013 -0500

    Add new test case T7585.

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

 tests/indexed-types/should_compile/T7585.hs |   21 +++++++++++++++++++++
 tests/indexed-types/should_compile/all.T    |    2 +-
 2 files changed, 22 insertions(+), 1 deletions(-)

diff --git a/tests/indexed-types/should_compile/T7585.hs b/tests/indexed-types/should_compile/T7585.hs
new file mode 100644
index 0000000..475269c
--- /dev/null
+++ b/tests/indexed-types/should_compile/T7585.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE GADTs, RankNTypes, KindSignatures, PolyKinds, TypeOperators, DataKinds,
+             TypeFamilies #-}
+
+module Bug where
+
+data SBool :: Bool -> * where
+  SFalse :: SBool False
+  STrue :: SBool True
+
+data SList :: [Bool] -> * where
+  SNil :: SList '[]
+  SCons :: SBool h -> SList t -> SList (h ': t)
+
+type family (a :: k) :==: (b :: k) :: Bool
+type instance where
+  '[] :==: '[] = True
+  (h1 ': t1) :==: (h2 ': t2) = True
+  a :==: b = False
+
+(%==%) :: SList ls1 -> SList ls2 -> SBool (ls1 :==: ls2)
+SNil %==% (SCons _ _) = SFalse
\ No newline at end of file
diff --git a/tests/indexed-types/should_compile/all.T b/tests/indexed-types/should_compile/all.T
index d785e82..b8edf95 100644
--- a/tests/indexed-types/should_compile/all.T
+++ b/tests/indexed-types/should_compile/all.T
@@ -206,5 +206,5 @@ test('T5591b', normal, compile, [''])
 test('T7280', normal, compile, [''])
 test('T7474', normal, compile, [''])
 test('T7489', normal, compile, [''])
-
+test('T7585', normal, compile, [''])
 





More information about the ghc-commits mailing list