Repository : ssh://darcs.haskell.org//srv/darcs/testsuite On branch : master
http://hackage.haskell.org/trac/ghc/changeset/487d3a1de84d61ba878aeed2c2914a4a1abcda9d >--------------------------------------------------------------- commit 487d3a1de84d61ba878aeed2c2914a4a1abcda9d Author: Simon Peyton Jones <simo...@microsoft.com> Date: Wed Oct 31 17:04:09 2012 +0000 Teat Trac #7220 >--------------------------------------------------------------- tests/typecheck/should_fail/T7220.hs | 48 ++++++++++++++++++++++++++++++ tests/typecheck/should_fail/T7220.stderr | 9 +++++ tests/typecheck/should_fail/all.T | 1 + 3 files changed, 58 insertions(+), 0 deletions(-) diff --git a/tests/typecheck/should_fail/T7220.hs b/tests/typecheck/should_fail/T7220.hs new file mode 100644 index 0000000..36ae54a --- /dev/null +++ b/tests/typecheck/should_fail/T7220.hs @@ -0,0 +1,48 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeFamilies #-} + +module Test2 where + +class C a b | b -> a + +data A = A +data X = X +data Y = Y + +type family TF b + +f :: (forall b. (C a b, TF b ~ Y) => b) -> X +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) + +{- +GHC 7.6.1-rc1 (7.6.0.20120810) rejects this code with the following error message. + +Test2.hs:24:52: + Couldn't match expected type `Y' + with actual type `TF (forall b. (C A b, TF b ~ Y) => b)' + In the first argument of `f :: + (forall b. (C A b, TF b ~ Y) => b) -> X', namely + `u' + In the expression: (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u + In an equation for `v': + v = (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u + +GHC 7.4.1 rejected this code with a different error message: + +Test2.hs:24:6: + Cannot deal with a type function under a forall type: + forall b. (C A b, TF b ~ Y) => b + In the expression: f :: (forall b. (C A b, TF b ~ Y) => b) -> X + In the expression: (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u + In an equation for `v': + v = (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u +-} \ No newline at end of file diff --git a/tests/typecheck/should_fail/T7220.stderr b/tests/typecheck/should_fail/T7220.stderr new file mode 100644 index 0000000..5086014 --- /dev/null +++ b/tests/typecheck/should_fail/T7220.stderr @@ -0,0 +1,9 @@ + +T7220.hs:24:6: + Cannot instantiate unification variable `b0' + with a type involving foralls: forall b. (C A b, TF b ~ Y) => b + Perhaps you want -XImpredicativeTypes + In the expression: f :: (forall b. (C A b, TF b ~ Y) => b) -> X + In the expression: (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u + In an equation for `v': + v = (f :: (forall b. (C A b, TF b ~ Y) => b) -> X) u diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T index 7e97f72..624dd5c 100644 --- a/tests/typecheck/should_fail/all.T +++ b/tests/typecheck/should_fail/all.T @@ -286,3 +286,4 @@ test('T6161', normal, compile_fail, ['']) test('T7368', normal, compile_fail, ['']) test('T7264', normal, compile_fail, ['']) test('T6069', normal, compile_fail, ['']) +test('T7220', normal, compile_fail, ['']) _______________________________________________ Cvs-ghc mailing list Cvs-ghc@haskell.org http://www.haskell.org/mailman/listinfo/cvs-ghc