[commit: ghc] master: Test Trac #8616 (2d9be8c)

git at git.haskell.org git at git.haskell.org
Mon Jan 13 12:23:48 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/2d9be8cb1152e78ae2408202663b20bcd9cb8ec2/ghc

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

commit 2d9be8cb1152e78ae2408202663b20bcd9cb8ec2
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Jan 13 12:23:31 2014 +0000

    Test Trac #8616


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

2d9be8cb1152e78ae2408202663b20bcd9cb8ec2
 testsuite/tests/polykinds/T8616.hs     |   14 ++++++++++++++
 testsuite/tests/polykinds/T8616.stderr |    7 +++++++
 testsuite/tests/polykinds/all.T        |    1 +
 3 files changed, 22 insertions(+)

diff --git a/testsuite/tests/polykinds/T8616.hs b/testsuite/tests/polykinds/T8616.hs
new file mode 100644
index 0000000..47e31bc
--- /dev/null
+++ b/testsuite/tests/polykinds/T8616.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE PolyKinds, RankNTypes, ScopedTypeVariables #-}
+module T8616 where
+
+import Data.Proxy
+import GHC.Exts
+
+withSomeSing :: forall (kproxy :: k). Proxy kproxy
+withSomeSing = undefined :: (Any :: k)
+  -- The 'k' is bought into scope by the type signature
+  -- This is a type error, but should not crash GHC
+
+foo = (undefined :: Proxy (a :: k)) :: forall (a :: k). Proxy a
+  -- Again, the 'k' is bought into scope by the type signature
+  -- No type error though
\ No newline at end of file
diff --git a/testsuite/tests/polykinds/T8616.stderr b/testsuite/tests/polykinds/T8616.stderr
new file mode 100644
index 0000000..4e1b9ec
--- /dev/null
+++ b/testsuite/tests/polykinds/T8616.stderr
@@ -0,0 +1,7 @@
+
+T8616.hs:8:29:
+    Expected a type, but ‛Any’ has kind ‛k’
+    In an expression type signature: (Any :: k)
+    In the expression: undefined :: (Any :: k)
+    In an equation for ‛withSomeSing’:
+        withSomeSing = undefined :: (Any :: k)
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 2d53e04..6d942d3 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -95,3 +95,4 @@ test('T8391', normal, compile, [''])
 test('T8449', normal, run_command, ['$MAKE -s --no-print-directory T8449'])
 test('T8534', normal, compile, [''])
 test('T8566', normal, compile_fail,[''])
+test('T8616', normal, compile_fail,[''])



More information about the ghc-commits mailing list