[commit: testsuite] master: Test cases for new IncoherentInstances behaviour (f9fb338)
git at git.haskell.org
git at git.haskell.org
Fri Aug 30 05:15:52 CEST 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/f9fb338d46cb9c4462d58b7527da547683341c61/testsuite
>---------------------------------------------------------------
commit f9fb338d46cb9c4462d58b7527da547683341c61
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Mon Aug 19 09:51:31 2013 +0200
Test cases for new IncoherentInstances behaviour
(related to #8141)
Signed-off-by: Austin Seipp <aseipp at pobox.com>
>---------------------------------------------------------------
f9fb338d46cb9c4462d58b7527da547683341c61
tests/typecheck/should_compile/Tc263_Help.hs | 7 +++++++
tests/typecheck/should_compile/all.T | 4 ++++
tests/typecheck/should_compile/tc262.hs | 13 +++++++++++++
tests/typecheck/should_compile/tc263.hs | 12 ++++++++++++
tests/typecheck/should_fail/Tcfail218_Help.hs | 7 +++++++
tests/typecheck/should_fail/all.T | 3 +++
tests/typecheck/should_fail/tcfail218.hs | 12 ++++++++++++
tests/typecheck/should_fail/tcfail218.stderr | 11 +++++++++++
8 files changed, 69 insertions(+)
diff --git a/tests/typecheck/should_compile/Tc263_Help.hs b/tests/typecheck/should_compile/Tc263_Help.hs
new file mode 100644
index 0000000..247d75a
--- /dev/null
+++ b/tests/typecheck/should_compile/Tc263_Help.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
+
+module Tc263_Help where
+
+class C a b where foo :: (a,b)
+
+instance C [Int] b where foo = undefined
diff --git a/tests/typecheck/should_compile/all.T b/tests/typecheck/should_compile/all.T
index 1fc81cb..e28e597 100644
--- a/tests/typecheck/should_compile/all.T
+++ b/tests/typecheck/should_compile/all.T
@@ -353,6 +353,10 @@ test('tc258', normal, compile, [''])
test('tc259', normal, compile, [''])
test('tc260', normal, compile, [''])
test('tc261', normal, compile, [''])
+test('tc262', normal, compile, [''])
+test('tc263',
+ extra_clean(['Tc263_Help.o','Tc263_Help.hi']),
+ multimod_compile, ['tc263','-v0'])
test('GivenOverlapping', normal, compile, [''])
test('GivenTypeSynonym', normal, compile, [''])
diff --git a/tests/typecheck/should_compile/tc262.hs b/tests/typecheck/should_compile/tc262.hs
new file mode 100644
index 0000000..b0fd129
--- /dev/null
+++ b/tests/typecheck/should_compile/tc262.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE IncoherentInstances, MultiParamTypeClasses, FlexibleInstances #-}
+
+-- Liberated IncoherentInstances behavior (#8141)
+
+class C a b where foo :: (a,b)
+
+instance C Int b where foo = undefined
+instance C a Int where foo = undefined
+
+x :: (Int, Int)
+x = foo
+
+main = return ()
diff --git a/tests/typecheck/should_compile/tc263.hs b/tests/typecheck/should_compile/tc263.hs
new file mode 100644
index 0000000..9440681
--- /dev/null
+++ b/tests/typecheck/should_compile/tc263.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE IncoherentInstances, MultiParamTypeClasses, FlexibleInstances #-}
+
+-- Get a non-incoherent instance from that file
+import Tc263_Help
+
+instance C [a] b where foo = undefined
+instance C a Int where foo = undefined
+
+y :: ([Int],Int)
+y = foo
+
+main = return ()
diff --git a/tests/typecheck/should_fail/Tcfail218_Help.hs b/tests/typecheck/should_fail/Tcfail218_Help.hs
new file mode 100644
index 0000000..e5ee76d
--- /dev/null
+++ b/tests/typecheck/should_fail/Tcfail218_Help.hs
@@ -0,0 +1,7 @@
+{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-}
+
+module Tcfail218_Help where
+
+class C a b where foo :: (a,b)
+
+instance C [Int] b where foo = undefined
diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T
index b2d9bf1..9006845 100644
--- a/tests/typecheck/should_fail/all.T
+++ b/tests/typecheck/should_fail/all.T
@@ -243,6 +243,9 @@ test('tcfail214', normal, compile_fail, [''])
test('tcfail215', normal, compile_fail, [''])
test('tcfail216', normal, compile_fail, [''])
test('tcfail217', normal, compile_fail, [''])
+test('tcfail218',
+ extra_clean(['Tcfail218_Help.o','Tcfail218_Help.hi']),
+ multimod_compile_fail, ['tcfail218','-v0'])
test('SilentParametersOverlapping', normal, compile_fail, [''])
test('FailDueToGivenOverlapping', normal, compile_fail, [''])
diff --git a/tests/typecheck/should_fail/tcfail218.hs b/tests/typecheck/should_fail/tcfail218.hs
new file mode 100644
index 0000000..ed05459
--- /dev/null
+++ b/tests/typecheck/should_fail/tcfail218.hs
@@ -0,0 +1,12 @@
+{-# LANGUAGE IncoherentInstances, MultiParamTypeClasses, FlexibleInstances #-}
+
+import Tcfail218_Help
+
+instance C [a] b where foo = undefined
+instance C a Int where foo = undefined
+
+-- Should fail, as a more specific, unifying but not matching, non-incoherent instance exists.
+x :: ([a],b)
+x = foo
+
+main = return ()
diff --git a/tests/typecheck/should_fail/tcfail218.stderr b/tests/typecheck/should_fail/tcfail218.stderr
new file mode 100644
index 0000000..66a8515
--- /dev/null
+++ b/tests/typecheck/should_fail/tcfail218.stderr
@@ -0,0 +1,11 @@
+
+tcfail218.hs:10:5:
+ Overlapping instances for C [a] b arising from a use of ‛foo’
+ Matching instances:
+ instance [incoherent] C [a] b -- Defined at tcfail218.hs:5:10
+ instance C [Int] b -- Defined at Tcfail218_Help.hs:7:10
+ (The choice depends on the instantiation of ‛a, b’
+ To pick the first instance above, use -XIncoherentInstances
+ when compiling the other instance declarations)
+ In the expression: foo
+ In an equation for ‛x’: x = foo
More information about the ghc-commits
mailing list