[commit: ghc] ghc-8.0: Add (failing) test case for #11347 (3deb446)

git at git.haskell.org git at git.haskell.org
Sat Jan 9 17:48:38 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/3deb446e9cf96eba3f2de092449e1ac88923fb19/ghc

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

commit 3deb446e9cf96eba3f2de092449e1ac88923fb19
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Tue Jan 5 10:56:47 2016 +0100

    Add (failing) test case for #11347
    
    Unfortunately, I could not add the expected error message, so if someone
    accidentally fixes this bug, this test will still be failing (no harm).
    But maybe someone stumbles over it then and can update the expected
    output.
    
    (cherry picked from commit 1a8b752d8b03266aca3e83f79c311056d6c43e00)


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

3deb446e9cf96eba3f2de092449e1ac88923fb19
 testsuite/tests/typecheck/should_fail/T11347.hs     | 19 +++++++++++++++++++
 testsuite/tests/typecheck/should_fail/T11347.stderr |  2 ++
 testsuite/tests/typecheck/should_fail/all.T         |  1 +
 3 files changed, 22 insertions(+)

diff --git a/testsuite/tests/typecheck/should_fail/T11347.hs b/testsuite/tests/typecheck/should_fail/T11347.hs
new file mode 100644
index 0000000..eaffdfd
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T11347.hs
@@ -0,0 +1,19 @@
+-- Should AllowAmbiguousTypes relaly be needed here?
+{-# LANGUAGE TypeFamilies, GeneralizedNewtypeDeriving, MultiParamTypeClasses, FlexibleInstances, AllowAmbiguousTypes #-}
+module T11347 where
+
+newtype Id1 a = MkId1 a
+newtype Id2 a = MkId2 (Id1 a) deriving (UnsafeCast b)
+
+type family Discern a b
+type instance Discern (Id1 a) b = a
+type instance Discern (Id2 a) b = b
+
+class UnsafeCast to from where
+  unsafe :: from -> Discern from to
+
+instance UnsafeCast b (Id1 a) where
+  unsafe (MkId1 x) = x
+
+unsafeCoerce :: a -> b
+unsafeCoerce x = unsafe (MkId2 (MkId1 x))
diff --git a/testsuite/tests/typecheck/should_fail/T11347.stderr b/testsuite/tests/typecheck/should_fail/T11347.stderr
new file mode 100644
index 0000000..1de61cd
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T11347.stderr
@@ -0,0 +1,2 @@
+dummy stderr:
+here should be something about roles _not_ "No skolem info"
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 4279950..93dd0c7 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -398,3 +398,4 @@ test('T11112', normal, compile_fail, [''])
 test('ClassOperator', normal, compile_fail, [''])
 test('T11274', normal, compile_fail, [''])
 test('T10619', normal, compile_fail, [''])
+test('T11347', expect_broken(11347), compile_fail, [''])



More information about the ghc-commits mailing list