[commit: ghc] ghc-7.10: Fix #10534 (3670f33)

git at git.haskell.org git at git.haskell.org
Tue Jun 16 21:43:13 UTC 2015


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

On branch  : ghc-7.10
Link       : http://ghc.haskell.org/trac/ghc/changeset/3670f338cef41aaa2c4c3585fd1aa1f81c65fef8/ghc

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

commit 3670f338cef41aaa2c4c3585fd1aa1f81c65fef8
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Mon Jun 15 21:55:52 2015 -0400

    Fix #10534
    
    Test case: typecheck/should_fail/T10534
    
    (cherry picked from commit 89c7168c150ccc38a2e6dd4a3aea555616722260)


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

3670f338cef41aaa2c4c3585fd1aa1f81c65fef8
 compiler/types/TyCon.hs                            |  2 +-
 testsuite/tests/typecheck/should_fail/T10534.hs    | 10 ++++++++++
 .../tests/typecheck/should_fail/T10534.stderr      | 22 ++++++++++++++++++++++
 testsuite/tests/typecheck/should_fail/T10534a.hs   | 10 ++++++++++
 testsuite/tests/typecheck/should_fail/all.T        |  2 ++
 5 files changed, 45 insertions(+), 1 deletion(-)

diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index 4283545..4b912f7 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -1237,7 +1237,7 @@ isDistinctTyCon _                           = False
 
 isDistinctAlgRhs :: AlgTyConRhs -> Bool
 isDistinctAlgRhs (DataTyCon {})           = True
-isDistinctAlgRhs (DataFamilyTyCon {})     = True
+isDistinctAlgRhs (DataFamilyTyCon {})     = False
 isDistinctAlgRhs (AbstractTyCon distinct) = distinct
 isDistinctAlgRhs (NewTyCon {})            = False
 
diff --git a/testsuite/tests/typecheck/should_fail/T10534.hs b/testsuite/tests/typecheck/should_fail/T10534.hs
new file mode 100644
index 0000000..ce694b4
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T10534.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE TypeFamilies #-}
+
+module T10534 where
+
+import T10534a
+
+newtype instance DF a = MkDF ()
+
+unsafeCoerce :: a -> b
+unsafeCoerce = silly
diff --git a/testsuite/tests/typecheck/should_fail/T10534.stderr b/testsuite/tests/typecheck/should_fail/T10534.stderr
new file mode 100644
index 0000000..5f44426
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T10534.stderr
@@ -0,0 +1,22 @@
+
+T10534a.hs:9:10: error:
+    Could not deduce: a ~ b
+    from the context: Coercible (DF a) (DF b)
+      bound by the type signature for:
+               silly :: Coercible (DF a) (DF b) => a -> b
+      at T10534a.hs:9:10-42
+      ‘a’ is a rigid type variable bound by
+          the type signature for: silly :: Coercible (DF a) (DF b) => a -> b
+          at T10534a.hs:9:10
+      ‘b’ is a rigid type variable bound by
+          the type signature for: silly :: Coercible (DF a) (DF b) => a -> b
+          at T10534a.hs:9:10
+    arising from trying to show that the representations of
+      ‘DF a’ and
+      ‘DF b’ are the same
+    Relevant role signatures: type role DF nominal
+    In the ambiguity check for the type signature for ‘silly’:
+      silly :: forall a b. Coercible (DF a) (DF b) => a -> b
+    To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+    In the type signature for ‘silly’:
+      silly :: Coercible (DF a) (DF b) => a -> b
diff --git a/testsuite/tests/typecheck/should_fail/T10534a.hs b/testsuite/tests/typecheck/should_fail/T10534a.hs
new file mode 100644
index 0000000..4f53ebe
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T10534a.hs
@@ -0,0 +1,10 @@
+{-# LANGUAGE TypeFamilies, FlexibleContexts #-}
+
+module T10534a where
+
+import Data.Coerce
+
+data family DF a
+
+silly :: Coercible (DF a) (DF b) => a -> b
+silly = coerce
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index ad036b3..31b6a5f 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -362,3 +362,5 @@ test('T10285',
 test('T9858a', normal, compile_fail, [''])
 test('T9858b', normal, compile_fail, [''])
 test('T9858e', normal, compile_fail, [''])
+test('T10534', extra_clean(['T10534a.hi', 'T10534a.o']),
+     multimod_compile_fail, ['T10534', '-v0'])



More information about the ghc-commits mailing list