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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/212867924cc3e4731a1542984e354f9eb5095c87

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

commit 212867924cc3e4731a1542984e354f9eb5095c87
Author: Simon Peyton Jones <[email protected]>
Date:   Tue Jan 10 08:09:51 2012 +0000

    Test Trac #5759

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

 tests/typecheck/should_run/T5759.hs     |   19 +++++++++++++++++++
 tests/typecheck/should_run/T5759.stdout |    1 +
 tests/typecheck/should_run/all.T        |    1 +
 3 files changed, 21 insertions(+), 0 deletions(-)

diff --git a/tests/typecheck/should_run/T5759.hs 
b/tests/typecheck/should_run/T5759.hs
new file mode 100644
index 0000000..a15b3b6
--- /dev/null
+++ b/tests/typecheck/should_run/T5759.hs
@@ -0,0 +1,19 @@
+{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, OverlappingInstances,
+    UndecidableInstances, FunctionalDependencies #-}
+
+module Main where
+
+class Container a b | a -> b where
+    make :: b -> a
+
+data Cont a = Cont a deriving (Show, Eq)
+
+instance Container (Cont a) a where
+    make x = Cont x
+
+instance (Container a b, Show a, Eq a, Num b) => Num a where
+    fromInteger x = make (fromInteger x)
+
+d = fromInteger 3 :: Cont Integer
+
+main = print d
\ No newline at end of file
diff --git a/tests/typecheck/should_run/T5759.stdout 
b/tests/typecheck/should_run/T5759.stdout
new file mode 100644
index 0000000..5a74c5f
--- /dev/null
+++ b/tests/typecheck/should_run/T5759.stdout
@@ -0,0 +1 @@
+Cont 3
diff --git a/tests/typecheck/should_run/all.T b/tests/typecheck/should_run/all.T
index aacdc7d..fa99ed9 100644
--- a/tests/typecheck/should_run/all.T
+++ b/tests/typecheck/should_run/all.T
@@ -85,3 +85,4 @@ test('T3500b', normal, compile_and_run, [''])
 test('T4809', reqlib('mtl'), compile_and_run, [''])
 test('T2722', normal, compile_and_run, [''])
 test('mc17', normal, compile_and_run, [''])
+test('T5759', normal, compile_and_run, [''])



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

Reply via email to