[commit: ghc] master: Trac #9222 is actually an ambiguous type, now detected (b82410a)

git at git.haskell.org git at git.haskell.org
Fri Nov 21 13:03:16 UTC 2014


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

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

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

commit b82410ab8908f1ec2a6aa14cce62948c92bcbce9
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Nov 21 11:16:19 2014 +0000

    Trac #9222 is actually an ambiguous type, now detected


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

b82410ab8908f1ec2a6aa14cce62948c92bcbce9
 testsuite/tests/polykinds/T9222.hs     |  6 ++++++
 testsuite/tests/polykinds/T9222.stderr | 24 ++++++++++++++++++++++++
 testsuite/tests/polykinds/all.T        |  2 +-
 3 files changed, 31 insertions(+), 1 deletion(-)

diff --git a/testsuite/tests/polykinds/T9222.hs b/testsuite/tests/polykinds/T9222.hs
index df11251..8e46ccb 100644
--- a/testsuite/tests/polykinds/T9222.hs
+++ b/testsuite/tests/polykinds/T9222.hs
@@ -3,5 +3,11 @@ module T9222 where
 
 import Data.Proxy
 
+-- Nov 2014: actually the type of Want is ambiguous if we
+--           do the full co/contra thing for subtyping,
+--           which we now do
+-- So this program is erroneous.  (But the original ticket was
+-- a crash, and that's still fixed!)
+
 data Want :: (i,j) -> * where
   Want :: (a ~ '(b,c) => Proxy b) -> Want a
diff --git a/testsuite/tests/polykinds/T9222.stderr b/testsuite/tests/polykinds/T9222.stderr
new file mode 100644
index 0000000..8e838e7
--- /dev/null
+++ b/testsuite/tests/polykinds/T9222.stderr
@@ -0,0 +1,24 @@
+
+T9222.hs:13:3:
+    Couldn't match type ‘b0’ with ‘b’
+      ‘b0’ is untouchable
+        inside the constraints (a ~ '(b0, c0))
+        bound by the type of the constructor ‘Want’:
+                   (a ~ '(b0, c0)) => Proxy b0
+        at T9222.hs:13:3
+      ‘b’ is a rigid type variable bound by
+          the type of the constructor ‘Want’:
+            ((a ~ '(b, c)) => Proxy b) -> Want a
+          at T9222.hs:13:3
+    Expected type: '(b, c)
+      Actual type: a
+    In the ambiguity check for the type of the constructor ‘Want’:
+      Want :: forall (k :: BOX)
+                     (k1 :: BOX)
+                     (a :: (,) k k1)
+                     (b :: k)
+                     (c :: k1).
+              ((a ~ '(b, c)) => Proxy b) -> Want a
+    To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+    In the definition of data constructor ‘Want’
+    In the data declaration for ‘Want’
diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T
index 48b0e61..74718ab 100644
--- a/testsuite/tests/polykinds/all.T
+++ b/testsuite/tests/polykinds/all.T
@@ -102,7 +102,7 @@ test('T8705', normal, compile, [''])
 test('T8985', normal, compile, [''])
 test('T9106', normal, compile_fail, [''])
 test('T9144', normal, compile_fail, [''])
-test('T9222', normal, compile, [''])
+test('T9222', normal, compile_fail, [''])
 test('T9264', normal, compile, [''])
 test('T9263', normal, run_command, ['$MAKE -s --no-print-directory T9263'])
 test('T9063', normal, compile, [''])



More information about the ghc-commits mailing list