Repository : ssh://darcs.haskell.org//srv/darcs/testsuite On branch : master
http://hackage.haskell.org/trac/ghc/changeset/83c16e4fd54b0754a7198d791f610dacb8698be5 >--------------------------------------------------------------- commit 83c16e4fd54b0754a7198d791f610dacb8698be5 Author: Ian Lynagh <[email protected]> Date: Thu Oct 11 20:45:04 2012 +0100 Add a test for T6161 >--------------------------------------------------------------- tests/typecheck/should_fail/T6161.hs | 29 +++++++++++++++++++++++++++++ tests/typecheck/should_fail/T6161.stderr | 5 +++++ tests/typecheck/should_fail/all.T | 1 + 3 files changed, 35 insertions(+), 0 deletions(-) diff --git a/tests/typecheck/should_fail/T6161.hs b/tests/typecheck/should_fail/T6161.hs new file mode 100644 index 0000000..1f19e67 --- /dev/null +++ b/tests/typecheck/should_fail/T6161.hs @@ -0,0 +1,29 @@ +{-# LANGUAGE TypeFamilies, FlexibleContexts, FlexibleInstances #-} + +module T6161 where + +data family Fam a + +data instance Fam Float = FamFloat Float + +class Super a where + testSup :: a -> Float + +class Super a => Duper a where + testDup :: a -> Float + +--class ( Super (Fam a) ) => Foo a where +class Duper (Fam a) => Foo a where + testFoo :: Fam a -> Float + +instance Foo a => Duper (Fam a) where + testDup x = testFoo x + testSup x + +--instance Super (Fam Float) where +-- testSup (FamFloat x) = x + +instance Foo Float where + testFoo (FamFloat _) = 5.0 + +testProg :: Float +testProg = testDup (FamFloat 3.0) diff --git a/tests/typecheck/should_fail/T6161.stderr b/tests/typecheck/should_fail/T6161.stderr new file mode 100644 index 0000000..089da39 --- /dev/null +++ b/tests/typecheck/should_fail/T6161.stderr @@ -0,0 +1,5 @@ + +T6161.hs:29:12: + No instance for (Super (Fam Float)) arising from a use of `testDup' + In the expression: testDup (FamFloat 3.0) + In an equation for `testProg': testProg = testDup (FamFloat 3.0) diff --git a/tests/typecheck/should_fail/all.T b/tests/typecheck/should_fail/all.T index a84942f..42737d4 100644 --- a/tests/typecheck/should_fail/all.T +++ b/tests/typecheck/should_fail/all.T @@ -282,3 +282,4 @@ test('TcMultiWayIfFail', if_compiler_lt('ghc', '7.5', skip), compile_fail, ['']) test('T2534', normal, compile_fail, ['']) test('T7175', normal, compile_fail, ['']) test('T7210', normal, compile_fail, ['']) +test('T6161', normal, compile_fail, ['']) _______________________________________________ Cvs-ghc mailing list [email protected] http://www.haskell.org/mailman/listinfo/cvs-ghc
