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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/d8047dc7f037050e419ab99fdffcfe6c787d0263

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

commit d8047dc7f037050e419ab99fdffcfe6c787d0263
Author: Daniel Fischer <[email protected]>
Date:   Sat Oct 15 12:32:12 2011 +0200

    Follow removal of Eq and Show superclasses from Num

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

 tests/deSugar/should_run/dsrun011.hs |    2 +-
 tests/lib/Numeric/num009.hs          |    2 +-
 2 files changed, 2 insertions(+), 2 deletions(-)

diff --git a/tests/deSugar/should_run/dsrun011.hs 
b/tests/deSugar/should_run/dsrun011.hs
index b7e518c..d1eecf6 100644
--- a/tests/deSugar/should_run/dsrun011.hs
+++ b/tests/deSugar/should_run/dsrun011.hs
@@ -4,7 +4,7 @@
 module Main where
 
 
-a1 :: Num a => a -> a
+a1 :: (Num a, Eq a) => a -> a
 
 a1 x | x==0 = x
 a1 x = 1 + k8 (x-1)
diff --git a/tests/lib/Numeric/num009.hs b/tests/lib/Numeric/num009.hs
index 6910f2f..58ab586 100644
--- a/tests/lib/Numeric/num009.hs
+++ b/tests/lib/Numeric/num009.hs
@@ -17,7 +17,7 @@ main = do let d = 1e20 :: Double
           test "tanf" tanf tan f
           putStrLn "Done"
 
-test :: (RealFloat a, Floating a, RealFloat b, Floating b)
+test :: (RealFloat a, Floating a, RealFloat b, Floating b, Show b)
      => String -> (a -> a) -> (b -> b) -> b -> IO ()
 test s f g x = do let y = realToFrac (f (realToFrac x))
                       z = g x



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

Reply via email to