[commit: testsuite] wip/T8541: Test case for undersaturated newtype in Coercions (90554a8)
git at git.haskell.org
git at git.haskell.org
Tue Nov 19 12:01:36 UTC 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : wip/T8541
Link : http://ghc.haskell.org/trac/ghc/changeset/90554a88bee5b492b4d4625ef30b23b9a7915347/testsuite
>---------------------------------------------------------------
commit 90554a88bee5b492b4d4625ef30b23b9a7915347
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Tue Nov 19 12:01:27 2013 +0000
Test case for undersaturated newtype in Coercions
This is related to #8541.
>---------------------------------------------------------------
90554a88bee5b492b4d4625ef30b23b9a7915347
tests/typecheck/should_fail/TcCoercibleFail3.hs | 14 ++++++++++++++
tests/typecheck/should_fail/TcCoercibleFail3.stderr | 7 +++++++
tests/typecheck/should_fail/all.T | 1 +
3 files changed, 22 insertions(+)
diff --git a/tests/typecheck/should_fail/TcCoercibleFail3.hs b/tests/typecheck/should_fail/TcCoercibleFail3.hs
new file mode 100644
index 0000000..4caf1c2
--- /dev/null
+++ b/tests/typecheck/should_fail/TcCoercibleFail3.hs
@@ -0,0 +1,14 @@
+{-# LANGUAGE RoleAnnotations, RankNTypes, ScopedTypeVariables #-}
+
+import GHC.Prim (coerce, Coercible)
+
+newtype List a = List [a]
+data T f = T (f Int)
+
+newtype NT1 a = NT1 (a -> Int)
+newtype NT2 a = NT2 (a -> Int)
+
+foo :: T NT1 -> T NT2
+foo = coerce
+
+main = return ()
diff --git a/tests/typecheck/should_fail/TcCoercibleFail3.stderr b/tests/typecheck/should_fail/TcCoercibleFail3.stderr
new file mode 100644
index 0000000..d3d71e1
--- /dev/null
+++ b/tests/typecheck/should_fail/TcCoercibleFail3.stderr
@@ -0,0 +1,7 @@
+
+TcCoercibleFail3.hs:12:7:
+ No instance for (Coercible NT1 NT2)
+ because ‛NT1’ and ‛NT2’ are different types.
+ arising from a use of ‛coerce’
+ In the expression: coerce
+ In an equation for ‛foo’: foo = coerce
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index f14bb5f..749ea32 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -319,6 +319,7 @@ test('T8262', normal, compile_fail, [''])
test('TcCoercibleFail', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
test('TcCoercibleFailSafe', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
test('TcCoercibleFail2', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
+test('TcCoercibleFail3', when(compiler_lt('ghc', '7.7'), skip), compile_fail, [''])
test('T8306', normal, compile_fail, [''])
test('T8392a', normal, compile_fail, [''])
test('T8428', normal, compile_fail, [''])
More information about the ghc-commits
mailing list