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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/68f8333d0b7c6d17ec6e46a920278ff4abdd2946

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

commit 68f8333d0b7c6d17ec6e46a920278ff4abdd2946
Author: Simon Peyton Jones <simo...@microsoft.com>
Date:   Fri Oct 19 09:23:27 2012 +0100

    Check that existential data constructors can't be promoted

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

 tests/polykinds/Holdermans.hs     |   11 +++++++++++
 tests/polykinds/Holdermans.stderr |    6 ++++++
 tests/polykinds/all.T             |    1 +
 3 files changed, 18 insertions(+), 0 deletions(-)

diff --git a/tests/polykinds/Holdermans.hs b/tests/polykinds/Holdermans.hs
new file mode 100644
index 0000000..59b1dae
--- /dev/null
+++ b/tests/polykinds/Holdermans.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE DataKinds                 #-}
+{-# LANGUAGE ExistentialQuantification #-}
+{-# LANGUAGE GADTs                     #-}
+{-# LANGUAGE KindSignatures            #-}
+
+module Holdermans where
+
+data K = forall a. T a  -- promotion gives 'T :: * -> K                        
  
+
+data G :: K -> * where
+  D :: G (T [])         -- kind error!
diff --git a/tests/polykinds/Holdermans.stderr 
b/tests/polykinds/Holdermans.stderr
new file mode 100644
index 0000000..a491ab7
--- /dev/null
+++ b/tests/polykinds/Holdermans.stderr
@@ -0,0 +1,6 @@
+
+Holdermans.hs:11:11:
+    `T' of type `forall a. a -> K' is not promotable
+    In the type `G (T [])'
+    In the definition of data constructor `D'
+    In the data declaration for `G'
diff --git a/tests/polykinds/all.T b/tests/polykinds/all.T
index 7e50bb5..33f8ffe 100644
--- a/tests/polykinds/all.T
+++ b/tests/polykinds/all.T
@@ -72,3 +72,4 @@ test('T7224', normal, compile_fail,[''])
 test('T7230', normal, compile_fail,[''])
 test('T7238', normal, compile,[''])
 test('T7278', normal, compile_fail,[''])
+test('Holdermans', normal, compile_fail,[''])



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

Reply via email to