Repository : ssh://g...@git.haskell.org/testsuite On branch : master Link : http://ghc.haskell.org/trac/ghc/changeset/41f708b6e0f4c73eb652045a1b9b4254eec97234/testsuite
>--------------------------------------------------------------- commit 41f708b6e0f4c73eb652045a1b9b4254eec97234 Author: Simon Peyton Jones <simo...@microsoft.com> Date: Thu Oct 3 09:25:25 2013 +0100 Test Trac #8392 >--------------------------------------------------------------- 41f708b6e0f4c73eb652045a1b9b4254eec97234 tests/typecheck/should_compile/T8392.hs | 17 +++++++++++++++++ tests/typecheck/should_compile/all.T | 1 + tests/typecheck/should_fail/T8392a.hs | 7 +++++++ tests/typecheck/should_fail/T8392a.stderr | 7 +++++++ tests/typecheck/should_fail/all.T | 2 ++ 5 files changed, 34 insertions(+) diff --git a/tests/typecheck/should_compile/T8392.hs b/tests/typecheck/should_compile/T8392.hs new file mode 100644 index 0000000..d86d29b --- /dev/null +++ b/tests/typecheck/should_compile/T8392.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, UndecidableInstances, AllowAmbiguousTypes #-} + +module T8392 where + +class Fun f a b where + fun :: f -> a -> b + +instance (b ~ Int, a ~ Int) => Fun F a b + where fun _ = (+1) + +data F = F + +data Compose a b = Compose a b + +-- ghc-7.6 version +instance (Fun f b c, Fun g a b) => Fun (Compose f g) a c where + fun (Compose f g) a = fun f (fun g a :: b) \ No newline at end of file diff --git a/tests/typecheck/should_compile/all.T b/tests/typecheck/should_compile/all.T index eb0e934..0ccd90a 100644 --- a/tests/typecheck/should_compile/all.T +++ b/tests/typecheck/should_compile/all.T @@ -410,3 +410,4 @@ test('T7891', normal, compile, ['']) test('T7903', normal, compile, ['']) test('TcTypeNatSimple', normal, compile, ['']) test('TcCoercibleCompile', when(compiler_lt('ghc', '7.7'), skip), compile, ['']) +test('T8392', normal, compile, ['']) diff --git a/tests/typecheck/should_fail/T8392a.hs b/tests/typecheck/should_fail/T8392a.hs new file mode 100644 index 0000000..6f47b4e --- /dev/null +++ b/tests/typecheck/should_fail/T8392a.hs @@ -0,0 +1,7 @@ +{-# LANGUAGE GADTs, AllowAmbiguousTypes #-} +module T8392a where + +-- Should complain even with AllowAmbiguousTypes + +foo :: (Int ~ Bool) => a -> a +foo x = x diff --git a/tests/typecheck/should_fail/T8392a.stderr b/tests/typecheck/should_fail/T8392a.stderr new file mode 100644 index 0000000..6e10222 --- /dev/null +++ b/tests/typecheck/should_fail/T8392a.stderr @@ -0,0 +1,7 @@ + +T8392a.hs:6:8: + Couldn't match type ‛Int’ with ‛Bool’ + Inaccessible code in + the type signature for foo :: Int ~ Bool => a -> a + In the ambiguity check for: forall a. Int ~ Bool => a -> a + In the type signature for ‛foo’: foo :: Int ~ Bool => a -> a diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T index cac7d92..bf11f6c 100644 --- a/tests/typecheck/should_fail/all.T +++ b/tests/typecheck/should_fail/all.T @@ -320,3 +320,5 @@ test('TcCoercibleFail', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['' test('TcCoercibleFailSafe', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) test('TcCoercibleFail2', when(compiler_lt('ghc', '7.7'), skip), compile_fail, ['']) test('T8306', normal, compile_fail, ['']) +test('T8392a', normal, compile_fail, ['']) + _______________________________________________ ghc-commits mailing list ghc-commits@haskell.org http://www.haskell.org/mailman/listinfo/ghc-commits