[commit: ghc] master: Test Trac #8030 (53cc9af)

git at git.haskell.org git at git.haskell.org
Wed Apr 8 08:44:22 UTC 2015


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

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

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

commit 53cc9af94122866aaae751f94f83ce7b940e5494
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Wed Apr 8 09:43:20 2015 +0100

    Test Trac #8030


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

53cc9af94122866aaae751f94f83ce7b940e5494
 testsuite/tests/typecheck/should_fail/T8030.hs     | 11 ++++++++++
 testsuite/tests/typecheck/should_fail/T8030.stderr | 24 ++++++++++++++++++++++
 testsuite/tests/typecheck/should_fail/all.T        |  1 +
 3 files changed, 36 insertions(+)

diff --git a/testsuite/tests/typecheck/should_fail/T8030.hs b/testsuite/tests/typecheck/should_fail/T8030.hs
new file mode 100644
index 0000000..970ae9b
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T8030.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE PolyKinds, FlexibleContexts, TypeFamilies #-}
+module T8030 where
+
+-- The types of op1 and op2 are both ambiguous
+-- and should be reported as such
+
+class C (a :: k) where
+  type Pr a :: *
+  op1 :: Pr a
+  op2 :: Pr a -> Pr a -> Pr a
+
diff --git a/testsuite/tests/typecheck/should_fail/T8030.stderr b/testsuite/tests/typecheck/should_fail/T8030.stderr
new file mode 100644
index 0000000..8dd752e
--- /dev/null
+++ b/testsuite/tests/typecheck/should_fail/T8030.stderr
@@ -0,0 +1,24 @@
+
+T8030.hs:9:3:
+    Couldn't match expected type ‘Pr a’ with actual type ‘Pr a0’
+    NB: ‘Pr’ is a type function, and may not be injective
+    The type variable ‘a0’ is ambiguous
+    In the ambiguity check for the type signature for ‘op1’:
+      op1 :: forall (k :: BOX) (a :: k). C a => Pr a
+    To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+    When checking the class method:
+      op1 :: forall (k :: BOX) (a :: k). C a => Pr a
+    In the class declaration for ‘C’
+
+T8030.hs:10:3:
+    Couldn't match type ‘Pr a0’ with ‘Pr a’
+    NB: ‘Pr’ is a type function, and may not be injective
+    The type variable ‘a0’ is ambiguous
+    Expected type: Pr a -> Pr a -> Pr a
+      Actual type: Pr a0 -> Pr a0 -> Pr a0
+    In the ambiguity check for the type signature for ‘op2’:
+      op2 :: forall (k :: BOX) (a :: k). C a => Pr a -> Pr a -> Pr a
+    To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
+    When checking the class method:
+      op2 :: forall (k :: BOX) (a :: k). C a => Pr a -> Pr a -> Pr a
+    In the class declaration for ‘C’
diff --git a/testsuite/tests/typecheck/should_fail/all.T b/testsuite/tests/typecheck/should_fail/all.T
index 9b71388..5d31bcd 100644
--- a/testsuite/tests/typecheck/should_fail/all.T
+++ b/testsuite/tests/typecheck/should_fail/all.T
@@ -355,3 +355,4 @@ test('T4921', normal, compile_fail, [''])
 test('T9605', normal, compile_fail, [''])
 test('T9999', normal, compile_fail, [''])
 test('T10194', normal, compile_fail, [''])
+test('T8030', normal, compile_fail, [''])



More information about the ghc-commits mailing list