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

On branch  : master

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

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

commit a87f1f0829d08bd389cff4cc2672af94f9809bb5
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Fri Oct 5 16:33:07 2012 +0100

    Test Trac #7293

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

 tests/gadt/T7293.hs                                |   24 ++++++++++++++++++++
 .../should_run/T5472.stdout => gadt/T7293.stderr}  |    0 
 tests/gadt/all.T                                   |    1 +
 3 files changed, 25 insertions(+), 0 deletions(-)

diff --git a/tests/gadt/T7293.hs b/tests/gadt/T7293.hs
new file mode 100644
index 0000000..26d9188
--- /dev/null
+++ b/tests/gadt/T7293.hs
@@ -0,0 +1,24 @@
+{-# LANGUAGE GADTs, DataKinds, KindSignatures, TypeFamilies,
+             TypeOperators, RankNTypes #-}
+
+module T7294 where
+
+data Nat = Zero | Succ Nat
+
+data Vec :: * -> Nat -> * where
+  Nil :: Vec a Zero
+  Cons :: a -> Vec a n -> Vec a (Succ n)
+
+type family (m :: Nat) :< (n :: Nat) :: Bool
+type instance m :< Zero = False
+type instance Zero :< Succ n = True
+type instance Succ n :< Succ m = n :< m
+
+data SNat :: Nat -> * where
+  SZero :: SNat Zero
+  SSucc :: forall (n :: Nat). SNat n -> SNat (Succ n)
+
+nth :: ((k :< n) ~ True) => Vec a n -> SNat k -> a
+nth (Cons x _) SZero = x
+nth (Cons _ xs) (SSucc k) = nth xs k
+nth Nil _ = undefined
diff --git a/tests/deSugar/should_run/T5472.stdout b/tests/gadt/T7293.stderr
similarity index 100%
copy from tests/deSugar/should_run/T5472.stdout
copy to tests/gadt/T7293.stderr
diff --git a/tests/gadt/all.T b/tests/gadt/all.T
index ac56021..566afcb 100644
--- a/tests/gadt/all.T
+++ b/tests/gadt/all.T
@@ -114,3 +114,4 @@ test('T5424',
 
 test('FloatEq', normal, compile, [''])
 test('T7205', normal, compile, [''])
+test('T7293', normal, compile_fail, [''])



_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to