Skip to content

Commit

Permalink
Remove the Show superclass of Num
Browse files Browse the repository at this point in the history
  • Loading branch information
igfoo committed Oct 12, 2011
1 parent 4d47404 commit 817c4e1
Show file tree
Hide file tree
Showing 4 changed files with 7 additions and 7 deletions.
4 changes: 2 additions & 2 deletions libraries/base/Data/Data.hs
Original file line number Diff line number Diff line change
Expand Up @@ -767,7 +767,7 @@ mkPrimCon dt str cr = Constr
mkIntConstr :: DataType -> Integer -> Constr
mkIntConstr = mkIntegralConstr

mkIntegralConstr :: (Integral a) => DataType -> a -> Constr
mkIntegralConstr :: (Integral a, Show a) => DataType -> a -> Constr
mkIntegralConstr dt i = case datarep dt of
IntRep -> mkPrimCon dt (show i) (IntConstr (toInteger i))
_ -> error "Data.Data.mkIntegralConstr"
Expand All @@ -777,7 +777,7 @@ mkIntegralConstr dt i = case datarep dt of
mkFloatConstr :: DataType -> Double -> Constr
mkFloatConstr dt = mkRealConstr dt . toRational

mkRealConstr :: (Real a) => DataType -> a -> Constr
mkRealConstr :: (Real a, Show a) => DataType -> a -> Constr
mkRealConstr dt f = case datarep dt of
FloatRep -> mkPrimCon dt (show f) (FloatConstr (toRational f))
_ -> error "Data.Data.mkRealConstr"
Expand Down
2 changes: 1 addition & 1 deletion libraries/base/GHC/Num.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ default () -- Double isn't available yet,
-- | Basic numeric class.
--
-- Minimal complete definition: all except 'negate' or @(-)@
class (Eq a, Show a) => Num a where
class (Eq a) => Num a where
(+), (-), (*) :: a -> a -> a
-- | Unary negation.
negate :: a -> a
Expand Down
2 changes: 1 addition & 1 deletion libraries/base/GHC/Real.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -362,7 +362,7 @@ instance (Integral a) => RealFrac (Ratio a) where
properFraction (x:%y) = (fromInteger (toInteger q), r:%y)
where (q,r) = quotRem x y
instance (Integral a) => Show (Ratio a) where
instance (Integral a, Show a) => Show (Ratio a) where
{-# SPECIALIZE instance Show Rational #-}
showsPrec p (x:%y) = showParen (p > ratioPrec) $
showsPrec ratioPrec1 x .
Expand Down
6 changes: 3 additions & 3 deletions libraries/base/Numeric.hs
Original file line number Diff line number Diff line change
Expand Up @@ -198,7 +198,7 @@ showGFloat d x = showString (formatRealFloat FFGeneric d x)

-- | Shows a /non-negative/ 'Integral' number using the base specified by the
-- first argument, and the character representation specified by the second.
showIntAtBase :: Integral a => a -> (Int -> Char) -> a -> ShowS
showIntAtBase :: (Integral a, Show a) => a -> (Int -> Char) -> a -> ShowS
showIntAtBase base toChr n0 r0
| base <= 1 = error ("Numeric.showIntAtBase: applied to unsupported base " ++ show base)
| n0 < 0 = error ("Numeric.showIntAtBase: applied to negative number " ++ show n0)
Expand All @@ -213,9 +213,9 @@ showIntAtBase base toChr n0 r0
r' = c : r

-- | Show /non-negative/ 'Integral' numbers in base 16.
showHex :: Integral a => a -> ShowS
showHex :: (Integral a,Show a) => a -> ShowS
showHex = showIntAtBase 16 intToDigit

-- | Show /non-negative/ 'Integral' numbers in base 8.
showOct :: Integral a => a -> ShowS
showOct :: (Integral a, Show a) => a -> ShowS
showOct = showIntAtBase 8 intToDigit

0 comments on commit 817c4e1

Please sign in to comment.