Repository : ssh://darcs.haskell.org//srv/darcs/testsuite

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/1657f583f4dbdb9d21f8bbd5f3e63c65c75b4c75

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

commit 1657f583f4dbdb9d21f8bbd5f3e63c65c75b4c75
Author: Dimitrios Vytiniotis <[email protected]>
Date:   Wed Jun 8 18:26:40 2011 +0100

    Adding test T5236 from Trac

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

 tests/ghc-regress/typecheck/should_fail/T5236.hs   |   21 ++++++++++++++++++++
 .../ghc-regress/typecheck/should_fail/T5236.stderr |   20 +++++++++++++++++++
 tests/ghc-regress/typecheck/should_fail/all.T      |    1 +
 3 files changed, 42 insertions(+), 0 deletions(-)

diff --git a/tests/ghc-regress/typecheck/should_fail/T5236.hs 
b/tests/ghc-regress/typecheck/should_fail/T5236.hs
new file mode 100644
index 0000000..07b31c3
--- /dev/null
+++ b/tests/ghc-regress/typecheck/should_fail/T5236.hs
@@ -0,0 +1,21 @@
+{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleContexts  
#-}
+
+module Main where 
+
+data A
+data B
+
+class Id a b | a -> b, b -> a
+
+instance Id A A
+instance Id B B
+
+loop :: Id A B => Bool
+loop = True
+
+f :: Bool 
+f = loop
+
+
+main :: IO () 
+main = return ()
\ No newline at end of file
diff --git a/tests/ghc-regress/typecheck/should_fail/T5236.stderr 
b/tests/ghc-regress/typecheck/should_fail/T5236.stderr
new file mode 100644
index 0000000..8ec3544
--- /dev/null
+++ b/tests/ghc-regress/typecheck/should_fail/T5236.stderr
@@ -0,0 +1,20 @@
+
+T5236.hs:17:5:
+    Couldn't match type `B' with `A'
+    When using functional dependencies to combine
+      Id B B,
+        arising from the dependency `b -> a'
+        in the instance declaration at T5236.hs:11:10
+      Id A B, arising from a use of `loop' at T5236.hs:17:5-8
+    In the expression: loop
+    In an equation for `f': f = loop
+
+T5236.hs:17:5:
+    Couldn't match type `A' with `B'
+    When using functional dependencies to combine
+      Id A A,
+        arising from the dependency `a -> b'
+        in the instance declaration at T5236.hs:10:10
+      Id A B, arising from a use of `loop' at T5236.hs:17:5-8
+    In the expression: loop
+    In an equation for `f': f = loop
diff --git a/tests/ghc-regress/typecheck/should_fail/all.T 
b/tests/ghc-regress/typecheck/should_fail/all.T
index d8485b5..1d81185 100644
--- a/tests/ghc-regress/typecheck/should_fail/all.T
+++ b/tests/ghc-regress/typecheck/should_fail/all.T
@@ -239,3 +239,4 @@ test('tcfail208', normal, compile_fail, [''])
 
 test('FailDueToGivenOverlapping', normal, compile_fail, [''])
 test('LongWayOverlapping', normal, compile_fail, [''])
+test('T5236',normal,compile_fail,[''])
\ No newline at end of file



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to