[commit: ghc] master: Fix up tests for Trac #7220; the old test really was ambiguous (7b1a856)

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


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

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

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

commit 7b1a8562d9b92547251d0dff23bb3a2de25d4b6f
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Nov 21 11:29:47 2014 +0000

    Fix up tests for Trac #7220; the old test really was ambiguous


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

7b1a8562d9b92547251d0dff23bb3a2de25d4b6f
 testsuite/tests/typecheck/should_compile/T7220.hs  |  9 ++++----
 testsuite/tests/typecheck/should_compile/T7220a.hs | 27 ++++++++++++++++++++++
 testsuite/tests/typecheck/should_compile/all.T     |  1 +
 3 files changed, 33 insertions(+), 4 deletions(-)

diff --git a/testsuite/tests/typecheck/should_compile/T7220.hs b/testsuite/tests/typecheck/should_compile/T7220.hs
index 36ae54a..bf4df87 100644
--- a/testsuite/tests/typecheck/should_compile/T7220.hs
+++ b/testsuite/tests/typecheck/should_compile/T7220.hs
@@ -3,25 +3,26 @@
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE ScopedTypeVariables #-}
 
 module Test2 where
 
 class C a b | b -> a
 
 data A = A
-data X = X
+data X a = X
 data Y = Y
 
 type family TF b
 
-f :: (forall b. (C a b, TF b ~ Y) => b) -> X
+f :: (forall b. (C a b, TF b ~ Y) => b) -> X a
 f _ = undefined
 
 u :: (C A b, TF b ~ Y) => b
 u = undefined
 
-v :: X
-v = (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u -- This line causes an error (see below)
+v :: X A
+v = (f :: (forall b. (C A b, TF b ~ Y) => b) -> X A) u -- This line causes an error (see below)
 
 {-
 GHC 7.6.1-rc1 (7.6.0.20120810) rejects this code with the following error message.
diff --git a/testsuite/tests/typecheck/should_compile/T7220a.hs b/testsuite/tests/typecheck/should_compile/T7220a.hs
new file mode 100644
index 0000000..4739626
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T7220a.hs
@@ -0,0 +1,27 @@
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FunctionalDependencies #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+
+module T7220a where
+
+class C a b | b -> a
+
+data X = X
+data Y = Y
+
+type family TF b
+
+f :: (forall b. (C a b, TF b ~ Y) => b) -> X
+-- This type is really ambiguous
+-- GHC 7.8 didn't detect that, and accepted the type, but would fail
+-- when given    g :: <the same type>
+--               g x = f x
+-- But it would succeed if you said just
+--               g = f
+-- Now we fail in all ways!
+
+f _ = undefined
+
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 7e825d9..8acfa4a 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -426,4 +426,5 @@ test('T9708', normal, compile_fail, [''])
 test('T9404', normal, compile, [''])
 test('T9404b', normal, compile, [''])
 test('T7220', normal, compile, [''])
+test('T7220a', normal, compile_fail, [''])
 test('T9151', normal, compile, [''])



More information about the ghc-commits mailing list