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

On branch  : master

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

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

commit c5ef31f004cc3b79b8d1d7266fa2ff91336d1982
Author: Ian Lynagh <[email protected]>
Date:   Wed Oct 12 17:40:00 2011 +0100

    Fix some tests following the removal of Num's superclasses

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

 tests/codeGen/should_run/cgrun044.hs |   12 ++++++------
 tests/codeGen/should_run/cgrun071.hs |    2 +-
 tests/ghci/scripts/ghci008.stdout    |    4 ++--
 tests/numeric/should_run/arith003.hs |    2 +-
 tests/numeric/should_run/arith011.hs |    2 +-
 tests/numeric/should_run/arith013.hs |    2 +-
 6 files changed, 12 insertions(+), 12 deletions(-)

diff --git a/tests/codeGen/should_run/cgrun044.hs 
b/tests/codeGen/should_run/cgrun044.hs
index b2509dd..1e7fb6f 100644
--- a/tests/codeGen/should_run/cgrun044.hs
+++ b/tests/codeGen/should_run/cgrun044.hs
@@ -98,7 +98,7 @@ float_numbers =
 
 -------------
 
-denorm :: RealFloat a => [a] -> String
+denorm :: (Show a, RealFloat a) => [a] -> String
 denorm numbers =
   unlines
      ( ""
@@ -109,7 +109,7 @@ denorm numbers =
  where
    showPerform = showAndPerform (isDenormalized) "isDenormalised"
 
-pos_inf :: RealFloat a => [a] -> String
+pos_inf :: (Show a, RealFloat a) => [a] -> String
 pos_inf numbers =
   unlines
      ( ""
@@ -120,7 +120,7 @@ pos_inf numbers =
  where
    showPerform = showAndPerform (isInfinite) "isInfinite"
 
-neg_inf :: RealFloat a => [a] -> String
+neg_inf :: (Show a, RealFloat a) => [a] -> String
 neg_inf numbers =
   unlines
      ( ""
@@ -131,7 +131,7 @@ neg_inf numbers =
  where
    showPerform = showAndPerform (\ x -> isInfinite x && x < 0) "isNegInfinite"
 
-nan :: RealFloat a => [a] -> String
+nan :: (Show a, RealFloat a) => [a] -> String
 nan numbers =
   unlines
      ( ""
@@ -142,7 +142,7 @@ nan numbers =
  where
    showPerform = showAndPerform (isNaN) "isNaN"
 
-pos_zero :: RealFloat a => [a] -> String
+pos_zero :: (Show a, RealFloat a) => [a] -> String
 pos_zero numbers =
   unlines
      ( ""
@@ -153,7 +153,7 @@ pos_zero numbers =
  where
    showPerform = showAndPerform (==0) "isPosZero"
 
-neg_zero :: RealFloat a => [a] -> String
+neg_zero :: (Show a, RealFloat a) => [a] -> String
 neg_zero numbers =
   unlines
      ( ""
diff --git a/tests/codeGen/should_run/cgrun071.hs 
b/tests/codeGen/should_run/cgrun071.hs
index 291a141..29bf03d 100644
--- a/tests/codeGen/should_run/cgrun071.hs
+++ b/tests/codeGen/should_run/cgrun071.hs
@@ -53,7 +53,7 @@ test_popCnt64 = test popcnt64 (slowPopcnt . fromIntegral . 
(mask 64 .&.))
 
 mask n = (2 ^ n) - 1
 
-test :: Num a => (a -> Word) -> (a -> Word) -> String
+test :: (Show a, Num a) => (a -> Word) -> (a -> Word) -> String
 test fast slow = case failing of
     [] -> "OK"
     ((_, e, a, i):xs) ->
diff --git a/tests/ghci/scripts/ghci008.stdout 
b/tests/ghci/scripts/ghci008.stdout
index d04dcec..cac9db2 100644
--- a/tests/ghci/scripts/ghci008.stdout
+++ b/tests/ghci/scripts/ghci008.stdout
@@ -1,9 +1,9 @@
-class (Eq a, Show a) => Num a where
+class Num a where
   (+) :: a -> a -> a
   ...
        -- Defined in `GHC.Num'
 infixl 6 +
-class (Eq a, Show a) => Num a where
+class Num a where
   (+) :: a -> a -> a
   ...
        -- Defined in `GHC.Num'
diff --git a/tests/numeric/should_run/arith003.hs 
b/tests/numeric/should_run/arith003.hs
index 46f0081..6bacbf1 100644
--- a/tests/numeric/should_run/arith003.hs
+++ b/tests/numeric/should_run/arith003.hs
@@ -10,7 +10,7 @@ main
        showit (do_ops integer_ops)
        )
 
-showit :: Integral a => [(String, a, a, a)] -> String
+showit :: (Show a, Integral a) => [(String, a, a, a)] -> String
 showit stuff = concat
        [ str ++ " " ++ show l ++ " " ++ show r ++ " = " ++ show result ++ "\n"
          | (str, l, r, result) <- stuff
diff --git a/tests/numeric/should_run/arith011.hs 
b/tests/numeric/should_run/arith011.hs
index 308cc82..d1b7c08 100644
--- a/tests/numeric/should_run/arith011.hs
+++ b/tests/numeric/should_run/arith011.hs
@@ -22,7 +22,7 @@ test = do
    testIntlike "Word64" (0::Word64)
    testInteger
 
-testIntlike :: (Bounded a, Integral a, Ix a, Read a, Bits a) => String -> a -> 
IO ()
+testIntlike :: (Bounded a, Integral a, Ix a, Show a, Read a, Bits a) => String 
-> a -> IO ()
 testIntlike name zero = do
   putStrLn $ "--------------------------------"
   putStrLn $ "--Testing " ++ name
diff --git a/tests/numeric/should_run/arith013.hs 
b/tests/numeric/should_run/arith013.hs
index 1ee1df2..40e95c3 100644
--- a/tests/numeric/should_run/arith013.hs
+++ b/tests/numeric/should_run/arith013.hs
@@ -9,5 +9,5 @@ main = do
    test gcdInteger [-12193263111263526900, -42, 0, 105, 1234567890 ]
 
 
-test :: Integral a => (a -> a -> a) -> [a] -> IO ()
+test :: (Show a, Integral a) => (a -> a -> a) -> [a] -> IO ()
 test f xs = mapM_ print [ (a, b, f a b) | a <- xs, b <- reverse xs, a /= 0  || 
b /= 0 ]



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

Reply via email to