[commit: ghc] master: Test Trac #12634 (13d3b53)
git at git.haskell.org
git at git.haskell.org
Thu Sep 29 08:23:55 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/13d3b531aa565b0fc602feb312f3054e4f1f380a/ghc
>---------------------------------------------------------------
commit 13d3b531aa565b0fc602feb312f3054e4f1f380a
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu Sep 29 09:23:11 2016 +0100
Test Trac #12634
>---------------------------------------------------------------
13d3b531aa565b0fc602feb312f3054e4f1f380a
testsuite/tests/partial-sigs/should_fail/T12634.hs | 15 +++++++++++++++
testsuite/tests/partial-sigs/should_fail/T12634.stderr | 10 ++++++++++
testsuite/tests/partial-sigs/should_fail/all.T | 2 +-
3 files changed, 26 insertions(+), 1 deletion(-)
diff --git a/testsuite/tests/partial-sigs/should_fail/T12634.hs b/testsuite/tests/partial-sigs/should_fail/T12634.hs
new file mode 100644
index 0000000..36865ed
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T12634.hs
@@ -0,0 +1,15 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+module T12634 where
+
+twacePowDec :: t m' r -> t m r
+twacePowDec = undefined
+
+data Bench a
+
+bench :: (a -> b) -> a -> Bench params
+bench f = undefined
+
+bench_twacePow :: forall t m m' r . _ => t m' r -> Bench '(t,m,m',r)
+bench_twacePow = bench (twacePowDec :: t m' r -> t m r)
diff --git a/testsuite/tests/partial-sigs/should_fail/T12634.stderr b/testsuite/tests/partial-sigs/should_fail/T12634.stderr
new file mode 100644
index 0000000..4287110
--- /dev/null
+++ b/testsuite/tests/partial-sigs/should_fail/T12634.stderr
@@ -0,0 +1,10 @@
+
+T12634.hs:14:58: error:
+ • Expected a type, but
+ ‘'(t, m, m', r)’ has kind
+ ‘(k1 -> k2 -> *, k0, k1, k2)’
+ • In the first argument of ‘Bench’, namely ‘'(t, m, m', r)’
+ In the type ‘t m' r -> Bench '(t, m, m', r)’
+ In the type signature:
+ bench_twacePow :: forall t m m' r.
+ _ => t m' r -> Bench '(t, m, m', r)
diff --git a/testsuite/tests/partial-sigs/should_fail/all.T b/testsuite/tests/partial-sigs/should_fail/all.T
index e8f5928..dca7f48 100644
--- a/testsuite/tests/partial-sigs/should_fail/all.T
+++ b/testsuite/tests/partial-sigs/should_fail/all.T
@@ -62,4 +62,4 @@ test('T11122', normal, compile, [''])
test('T11976', normal, compile_fail, [''])
test('PatBind3', normal, compile_fail, [''])
test('T12039', normal, compile_fail, [''])
-
+test('T12634', normal, compile_fail, [''])
More information about the ghc-commits
mailing list