[commit: ghc] master: Test #9017 in polykinds/T9017 (779dfea)
git at git.haskell.org
git at git.haskell.org
Sat Dec 12 03:07:00 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/779dfea1d9cc713d9b1e26bb559e8da309b2aeec/ghc
>---------------------------------------------------------------
commit 779dfea1d9cc713d9b1e26bb559e8da309b2aeec
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date: Fri Dec 11 22:07:06 2015 -0500
Test #9017 in polykinds/T9017
>---------------------------------------------------------------
779dfea1d9cc713d9b1e26bb559e8da309b2aeec
testsuite/tests/polykinds/T9017.hs | 8 ++++++++
testsuite/tests/polykinds/T9017.stderr | 26 ++++++++++++++++++++++++++
testsuite/tests/polykinds/all.T | 1 +
3 files changed, 35 insertions(+)
diff --git a/testsuite/tests/polykinds/T9017.hs b/testsuite/tests/polykinds/T9017.hs
new file mode 100644
index 0000000..7f93f54
--- /dev/null
+++ b/testsuite/tests/polykinds/T9017.hs
@@ -0,0 +1,8 @@
+{-# LANGUAGE PolyKinds #-}
+
+module T9017 where
+
+import Control.Arrow
+
+foo :: a b (m b)
+foo = arr return
diff --git a/testsuite/tests/polykinds/T9017.stderr b/testsuite/tests/polykinds/T9017.stderr
new file mode 100644
index 0000000..857d11a
--- /dev/null
+++ b/testsuite/tests/polykinds/T9017.stderr
@@ -0,0 +1,26 @@
+
+T9017.hs:8:7: error:
+ • Couldn't match kind ‘k’ with ‘*’
+ ‘k’ is a rigid type variable bound by
+ the type signature for:
+ foo :: forall k k1 (a :: k1 -> k -> *) (b :: k1) (m :: k1 -> k).
+ a b (m b)
+ at T9017.hs:7:8
+ When matching the kind of ‘a’
+ • In the expression: arr return
+ In an equation for ‘foo’: foo = arr return
+ • Relevant bindings include
+ foo :: a b (m b) (bound at T9017.hs:8:1)
+
+T9017.hs:8:7: error:
+ • Couldn't match kind ‘k1’ with ‘*’
+ ‘k1’ is a rigid type variable bound by
+ the type signature for:
+ foo :: forall k k1 (a :: k1 -> k -> *) (b :: k1) (m :: k1 -> k).
+ a b (m b)
+ at T9017.hs:7:8
+ When matching the kind of ‘a’
+ • In the expression: arr return
+ In an equation for ‘foo’: foo = arr return
+ • Relevant bindings include
+ foo :: a b (m b) (bound at T9017.hs:8:1)
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index a93ad8b..0005abc 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -126,3 +126,4 @@ test('T10934', normal, compile, [''])
test('T11142', normal, compile_fail, [''])
test('SigTvKinds', expect_broken(11203), compile, [''])
test('SigTvKinds2', expect_broken(11203), compile_fail, [''])
+test('T9017', normal, compile_fail, [''])
More information about the ghc-commits
mailing list