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

On branch  : master

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

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

commit a5bae4fda2cd9d3af95711fc6e8653ed6c52f199
Author: Jose Pedro Magalhaes <[email protected]>
Date:   Mon Nov 21 09:51:14 2011 +0000

    Simple test for PolyKinds inference

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

 tests/polykinds/{PolyKinds01.hs => PolyKinds11.hs} |    9 ++++-----
 tests/polykinds/all.T                              |    1 +
 2 files changed, 5 insertions(+), 5 deletions(-)

diff --git a/tests/polykinds/PolyKinds01.hs b/tests/polykinds/PolyKinds11.hs
similarity index 63%
copy from tests/polykinds/PolyKinds01.hs
copy to tests/polykinds/PolyKinds11.hs
index 2f5f1e8..c7eea5b 100644
--- a/tests/polykinds/PolyKinds01.hs
+++ b/tests/polykinds/PolyKinds11.hs
@@ -1,13 +1,12 @@
 {-# LANGUAGE PolyKinds                  #-}
 {-# LANGUAGE GADTs                      #-}
 
-module PolyKinds01 where
+module PolyKinds11 where
+
+-- Test inference
 
 data Nat = Ze | Su Nat
 
-data Vec :: * -> Nat -> * where
+data Vec a n where -- Vec :: * -> Nat -> *
   VNil  :: Vec a Ze
   VCons :: a -> Vec a n -> Vec a (Su n)
-
-vec :: Vec Nat (Su Ze)
-vec = VCons Ze VNil
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index dddedaf..9af577a 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -7,6 +7,7 @@ test('PolyKinds01', normal, compile, [''])
 test('PolyKinds03', normal, compile, [''])
 test('PolyKinds05', normal, compile, [''])
 test('PolyKinds08', normal, compile, [''])
+test('PolyKinds11', normal, compile, [''])
 
 test('PolyKinds02', normal, compile_fail, [''])
 test('PolyKinds04', normal, compile_fail, [''])



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to