[commit: testsuite] master: Wibble to tests from improving comments about apartness. (0ba2b5f)
git at git.haskell.org
git at git.haskell.org
Wed Aug 28 19:14:05 CEST 2013
Repository : ssh://git@git.haskell.org/testsuite
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/0ba2b5fadf73bae5518752c71d7b97e2f196bc5a/testsuite
>---------------------------------------------------------------
commit 0ba2b5fadf73bae5518752c71d7b97e2f196bc5a
Author: Richard Eisenberg <eir at seas.upenn.edu>
Date: Wed Aug 28 12:05:03 2013 -0400
Wibble to tests from improving comments about apartness.
>---------------------------------------------------------------
0ba2b5fadf73bae5518752c71d7b97e2f196bc5a
tests/indexed-types/should_compile/Overlap14.hs | 12 ++++++------
tests/indexed-types/should_fail/Overlap15.hs | 16 ++++++++++++++++
tests/indexed-types/should_fail/Overlap15.stderr | 7 +++++++
tests/indexed-types/should_fail/all.T | 1 +
4 files changed, 30 insertions(+), 6 deletions(-)
diff --git a/tests/indexed-types/should_compile/Overlap14.hs b/tests/indexed-types/should_compile/Overlap14.hs
index 49af37c..96ed37e 100644
--- a/tests/indexed-types/should_compile/Overlap14.hs
+++ b/tests/indexed-types/should_compile/Overlap14.hs
@@ -2,11 +2,11 @@
module Overlap14 where
-type family F a b c where
- F a a a = Int
- F Int b c = Bool
+import Data.Proxy
-type family G x
+type family F a b c where
+ F a a Int = Int
+ F b c d = Bool
-foo :: F Int (G Bool) Bool
-foo = False
+foo :: Proxy b -> F b [b] Bool
+foo _ = False
diff --git a/tests/indexed-types/should_fail/Overlap15.hs b/tests/indexed-types/should_fail/Overlap15.hs
new file mode 100644
index 0000000..c150a40
--- /dev/null
+++ b/tests/indexed-types/should_fail/Overlap15.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE TypeFamilies #-}
+
+-- In an ideal world, this would work. But, GHC doesn't implement
+-- a full infinite-type unifier, so it can't figure out that F b [b] Bool
+-- can safely reduce to Bool.
+
+module Overlap15 where
+
+import Data.Proxy
+
+type family F a b c where
+ F a a a = Int
+ F b c Bool = Bool
+
+foo :: Proxy b -> F b [b] Bool
+foo _ = False
diff --git a/tests/indexed-types/should_fail/Overlap15.stderr b/tests/indexed-types/should_fail/Overlap15.stderr
new file mode 100644
index 0000000..474bfd7
--- /dev/null
+++ b/tests/indexed-types/should_fail/Overlap15.stderr
@@ -0,0 +1,7 @@
+
+Overlap15.hs:16:9:
+ Couldn't match expected type ‛F b [b] Bool’ with actual type ‛Bool’
+ Relevant bindings include
+ foo :: Proxy * b -> F b [b] Bool (bound at Overlap15.hs:16:1)
+ In the expression: False
+ In an equation for ‛foo’: foo _ = False
diff --git a/tests/indexed-types/should_fail/all.T b/tests/indexed-types/should_fail/all.T
index 04d19ab..14344da 100644
--- a/tests/indexed-types/should_fail/all.T
+++ b/tests/indexed-types/should_fail/all.T
@@ -85,6 +85,7 @@ test('Overlap7', normal, compile_fail, [''])
test('Overlap9', normal, compile_fail, [''])
test('Overlap10', normal, compile_fail, [''])
test('Overlap11', normal, compile_fail, [''])
+test('Overlap15', normal, compile_fail, [''])
test('T7194', normal, compile_fail, [''])
test('T7354', normal, compile_fail, [''])
test('T7354a',
More information about the ghc-commits
mailing list