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

On branch  : master

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

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

commit a6102f8c754b3931c2d9766a61893966052ce0c3
Author: Ian Lynagh <[email protected]>
Date:   Wed Oct 12 17:58:45 2011 +0100

    Fix more tests following the removal of Num's superclasses

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

 tests/perf/should_run/T2902_A_PairingSum.hs  |   14 +++++++-------
 tests/perf/should_run/T2902_B_PairingSum.hs  |    2 +-
 tests/simplCore/should_compile/T4203.hs      |    4 ++--
 tests/th/T1835.hs                            |    2 +-
 tests/th/T1835.stdout                        |    2 +-
 tests/typecheck/should_compile/tc087.hs      |    2 +-
 tests/typecheck/should_fail/tcfail067.hs     |    2 +-
 tests/typecheck/should_fail/tcfail067.stderr |   15 +++------------
 8 files changed, 17 insertions(+), 26 deletions(-)

diff --git a/tests/perf/should_run/T2902_A_PairingSum.hs 
b/tests/perf/should_run/T2902_A_PairingSum.hs
index a5dd0e7..6dc5fb4 100644
--- a/tests/perf/should_run/T2902_A_PairingSum.hs
+++ b/tests/perf/should_run/T2902_A_PairingSum.hs
@@ -7,7 +7,7 @@ import T2902_Sum
 
 data PSum a b = Empty | Tree a b [(PSum a b)]
 
-instance (Ord a, Num b) ⇒ Sum PSum a b where
+instance (Ord a, Eq b, Num b) ⇒ Sum PSum a b where
   insert     = insertX
   union      = unionX
   unions     = unionsX
@@ -15,10 +15,10 @@ instance (Ord a, Num b) ⇒ Sum PSum a b where
   fromList   = fromListX
   toList     = toListX
 
-insertX ∷ (Ord a, Num b) ⇒ a → b → PSum a b → PSum a b
+insertX ∷ (Ord a, Eq b, Num b) ⇒ a → b → PSum a b → PSum a b
 insertX v r = unionX $ Tree v r []
 
-unionX ∷ (Ord a, Num b) ⇒ PSum a b → PSum a b → PSum a b
+unionX ∷ (Ord a, Eq b, Num b) ⇒ PSum a b → PSum a b → PSum a b
 unionX x Empty = x
 unionX Empty x = x
 unionX x@(Tree v r xs) y@(Tree w s ys) =
@@ -30,20 +30,20 @@ unionX x@(Tree v r xs) y@(Tree w s ys) =
       t → insertX v t z
   where z = unionX (unionsX xs) (unionsX ys)
 
-unionsX ∷ (Ord a, Num b) ⇒ [PSum a b] → PSum a b
+unionsX ∷ (Ord a, Eq b, Num b) ⇒ [PSum a b] → PSum a b
 unionsX [] = Empty
 unionsX [x] = x
 unionsX (x : y : zs) = unionX (unionX x y) (unionsX zs)
 
-extractMinX ∷ (Ord a, Num b) ⇒ PSum a b → ((a,b), PSum a b)
+extractMinX ∷ (Ord a, Eq b, Num b) ⇒ PSum a b → ((a,b), PSum a b)
 extractMinX Empty = undefined
 extractMinX (Tree v r xs) = ((v,r), unionsX xs)
 
-fromListX ∷ (Ord a, Num b) ⇒ [(a,b)] → PSum a b
+fromListX ∷ (Ord a, Eq b, Num b) ⇒ [(a,b)] → PSum a b
 fromListX [] = Empty
 fromListX ((v,r):xs) = insertX v r $ fromListX xs
 
-toListX ∷ (Ord a, Num b) ⇒ PSum a b → [(a,b)]
+toListX ∷ (Ord a, Eq b, Num b) ⇒ PSum a b → [(a,b)]
 toListX Empty = []
 toListX x = let (y, z) = extractMinX x in y : toListX z
 
diff --git a/tests/perf/should_run/T2902_B_PairingSum.hs 
b/tests/perf/should_run/T2902_B_PairingSum.hs
index 5276da8..baf5885 100644
--- a/tests/perf/should_run/T2902_B_PairingSum.hs
+++ b/tests/perf/should_run/T2902_B_PairingSum.hs
@@ -7,7 +7,7 @@ import T2902_Sum
 
 data PSum a b = Empty | Tree a b [PSum a b]
 
-instance (Ord a, Num b) ⇒ Sum PSum a b where
+instance (Ord a, Eq b, Num b) ⇒ Sum PSum a b where
 
   insert v r = union $ Tree v r []
 
diff --git a/tests/simplCore/should_compile/T4203.hs 
b/tests/simplCore/should_compile/T4203.hs
index 9423de7..89591f0 100644
--- a/tests/simplCore/should_compile/T4203.hs
+++ b/tests/simplCore/should_compile/T4203.hs
@@ -8,11 +8,11 @@ module T4203 where
 newtype NonNegative a = NonNegative a
  deriving (Eq, Num, Show)
 
-instance Num a => Arbitrary (NonNegative a) where
+instance (Eq a, Num a) => Arbitrary (NonNegative a) where
   arbitrary = return (rubble (rubble 0))
   coarbitrary = error "urk"
 
-rubble :: Num a => a -> a
+rubble :: (Eq a, Num a) => a -> a
 rubble 0 = 1
 rubble n = n * rubble (n-1)
 
diff --git a/tests/th/T1835.hs b/tests/th/T1835.hs
index e9bda36..e2029fa 100644
--- a/tests/th/T1835.hs
+++ b/tests/th/T1835.hs
@@ -19,7 +19,7 @@ instance MyClass Baz
 data Quux a  = Quux a   deriving Eq
 data Quux2 a = Quux2 a  deriving Eq
 instance Eq a  => MyClass (Quux a)
-instance Num a => MyClass (Quux2 a)
+instance Ord a => MyClass (Quux2 a)
 
 class MyClass2 a b
 instance MyClass2 Int Bool
diff --git a/tests/th/T1835.stdout b/tests/th/T1835.stdout
index dcb42a2..ba8e65f 100644
--- a/tests/th/T1835.stdout
+++ b/tests/th/T1835.stdout
@@ -2,7 +2,7 @@ class GHC.Classes.Eq a_0 => Main.MyClass a_0
 instance Main.MyClass Main.Foo
 instance Main.MyClass Main.Baz
 instance GHC.Classes.Eq a_1 => Main.MyClass (Main.Quux a_1)
-instance GHC.Num.Num a_2 => Main.MyClass (Main.Quux2 a_2)
+instance GHC.Classes.Ord a_2 => Main.MyClass (Main.Quux2 a_2)
 True
 True
 True
diff --git a/tests/typecheck/should_compile/tc087.hs 
b/tests/typecheck/should_compile/tc087.hs
index 88317ba..f70472b 100644
--- a/tests/typecheck/should_compile/tc087.hs
+++ b/tests/typecheck/should_compile/tc087.hs
@@ -26,7 +26,7 @@ check empty           =  do
     out (pqSort empty [1 .. 99])
     out (pqSort empty [1.0, 1.1 ..99.9])
 
-out                            :: (Num a) => [a] -> IO ()
+out                            :: (Eq a, Num a) => [a] -> IO ()
 out x | sum x == 0             =  putStr "ok\n"
       | otherwise              =  putStr "ok\n"
 
diff --git a/tests/typecheck/should_fail/tcfail067.hs 
b/tests/typecheck/should_fail/tcfail067.hs
index bcdb0c7..cefe1c4 100644
--- a/tests/typecheck/should_fail/tcfail067.hs
+++ b/tests/typecheck/should_fail/tcfail067.hs
@@ -64,7 +64,7 @@ instance Num a => Num (SubRange a) where
   (*) = numSubRangeMultiply
   fromInteger a = SubRange (fromInteger a, fromInteger a) (fromInteger a)
 
-numSubRangeNegate :: (Ord a, Num a) => SubRange a -> SubRange a
+numSubRangeNegate :: (Ord a, Show a, Num a) => SubRange a -> SubRange a
 numSubRangeNegate (SubRange (lower, upper) value)
   = checkRange (SubRange (lower, upper) (-value))
 
diff --git a/tests/typecheck/should_fail/tcfail067.stderr 
b/tests/typecheck/should_fail/tcfail067.stderr
index 4c69c67..039a4e6 100644
--- a/tests/typecheck/should_fail/tcfail067.stderr
+++ b/tests/typecheck/should_fail/tcfail067.stderr
@@ -29,22 +29,13 @@ tcfail067.hs:46:12:
         showRange (SubRange (lower, upper) value)
           = show value ++ " :" ++ show lower ++ ".." ++ show upper
 
-tcfail067.hs:60:10:
-    Could not deduce (Show (SubRange a))
-      arising from the superclasses of an instance declaration
-    from the context (Num a)
-      bound by the instance declaration at tcfail067.hs:60:10-34
-    Possible fix:
-      add (Show (SubRange a)) to the context of the instance declaration
-      or add an instance declaration for (Show (SubRange a))
-    In the instance declaration for `Num (SubRange a)'
-
 tcfail067.hs:61:12:
-    Could not deduce (Ord a) arising from a use of `numSubRangeNegate'
+    Could not deduce (Ord a, Show a)
+      arising from a use of `numSubRangeNegate'
     from the context (Num a)
       bound by the instance declaration at tcfail067.hs:60:10-34
     Possible fix:
-      add (Ord a) to the context of the instance declaration
+      add (Ord a, Show a) to the context of the instance declaration
     In the expression: numSubRangeNegate
     In an equation for `negate': negate = numSubRangeNegate
     In the instance declaration for `Num (SubRange a)'



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

Reply via email to