[commit: ghc] master: Test case for #10698 (e343c0a)

git at git.haskell.org git at git.haskell.org
Tue Jul 28 11:23:03 UTC 2015


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

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

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

commit e343c0a7fbaca4285a89008e5e23d35a50603763
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Tue Jul 28 13:19:34 2015 +0200

    Test case for #10698
    
    the expected error message is from an older version of GHC; I don’t know
    the exact error message that we should get here until the bug is
    fixed...


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

e343c0a7fbaca4285a89008e5e23d35a50603763
 testsuite/tests/typecheck/should_fail/T10698.hs    | 23 ++++++++++++++++++++++
 .../tests/typecheck/should_fail/T10698.stderr      | 10 ++++++++++
 testsuite/tests/typecheck/should_fail/all.T        |  1 +
 3 files changed, 34 insertions(+)

diff --git a/testsuite/tests/typecheck/should_fail/T10698.hs b/testsuite/tests/typecheck/should_fail/T10698.hs
new file mode 100644
index 0000000..512a882
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T10698.hs
@@ -0,0 +1,23 @@
+{-# LANGUAGE RoleAnnotations #-}
+
+module T10698 where
+import Data.Coerce
+
+data Map k a  = Map k a
+type role Map nominal representational
+
+map1 :: (k1->k2) -> Map k1 a -> Map k2 a
+map1 f (Map a b) = Map (f a) b
+{-# NOINLINE  [1] map1 #-}
+{-# RULES
+"map1/coerce" map1 coerce = coerce
+ #-}
+
+
+map2 :: (a -> b) -> Map k a -> Map k b
+map2 f (Map a b) = Map a (f b)
+{-# NOINLINE [1] map2 #-}
+
+{-# RULES
+"map2/coerce" map2 coerce = coerce
+ #-}
diff --git a/testsuite/tests/typecheck/should_fail/T10698.stderr b/testsuite/tests/typecheck/should_fail/T10698.stderr
new file mode 100644
index 0000000..fa3aa5f
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T10698.stderr
@@ -0,0 +1,10 @@
+
+T10698.hs:13:29:
+    Could not coerce from ‘Map k1 a’ to ‘Map k2 a’
+      because the first type argument of ‘Map’ has role Nominal,
+      but the arguments ‘k1’ and ‘k2’ differ
+      arising from a use of ‘coerce’
+    from the context (Coercible k1 k2)
+      bound by the RULE "map1/coerce" at T10698.hs:13:1-34
+    In the expression: coerce
+    When checking the transformation rule "map1/coerce"
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index fbbeddb..bc2b3c9 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -374,3 +374,4 @@ test('ExpandSynsFail1', normal, compile_fail, ['-fprint-expanded-synonyms'])
 test('ExpandSynsFail2', normal, compile_fail, ['-fprint-expanded-synonyms'])
 test('ExpandSynsFail3', normal, compile_fail, ['-fprint-expanded-synonyms'])
 test('ExpandSynsFail4', normal, compile_fail, ['-fprint-expanded-synonyms'])
+test('T10698', expect_broken(10698), compile_fail, [''])



More information about the ghc-commits mailing list