X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FReal.lhs;h=51d7db404cab4e09ca432662484dcafe941d47f6;hb=7a97ec4b12e1fbec5505f82032cf4dc435b5a60c;hp=8b4615b2b6a5800eefaec3a57a6fdc3e3bd7ab83;hpb=aea2507724ff9ee46fe7d49dab05e532a56cf487;p=ghc-base.git diff --git a/GHC/Real.lhs b/GHC/Real.lhs index 8b4615b..51d7db4 100644 --- a/GHC/Real.lhs +++ b/GHC/Real.lhs @@ -1,5 +1,5 @@ \begin{code} -{-# OPTIONS_GHC -XNoImplicitPrelude #-} +{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples #-} {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- -- | @@ -43,7 +43,7 @@ default () -- Double isn't available yet, \begin{code} -- | Rational numbers, with numerator and denominator of some 'Integral' type. -data (Integral a) => Ratio a = !a :% !a deriving (Eq) +data Ratio a = !a :% !a deriving (Eq) -- | Arbitrary-precision rational numbers, represented as a ratio of -- two 'Integer' values. A rational number may be constructed using @@ -245,32 +245,38 @@ instance Integral Int where a `quot` b | b == 0 = divZeroError - | a == minBound && b == (-1) = overflowError + | b == (-1) && a == minBound = overflowError -- Note [Order of tests] + -- in GHC.Int | otherwise = a `quotInt` b a `rem` b | b == 0 = divZeroError - | a == minBound && b == (-1) = overflowError + | b == (-1) && a == minBound = overflowError -- Note [Order of tests] + -- in GHC.Int | otherwise = a `remInt` b a `div` b | b == 0 = divZeroError - | a == minBound && b == (-1) = overflowError + | b == (-1) && a == minBound = overflowError -- Note [Order of tests] + -- in GHC.Int | otherwise = a `divInt` b a `mod` b | b == 0 = divZeroError - | a == minBound && b == (-1) = overflowError + | b == (-1) && a == minBound = overflowError -- Note [Order of tests] + -- in GHC.Int | otherwise = a `modInt` b a `quotRem` b | b == 0 = divZeroError - | a == minBound && b == (-1) = overflowError + | b == (-1) && a == minBound = overflowError -- Note [Order of tests] + -- in GHC.Int | otherwise = a `quotRemInt` b a `divMod` b | b == 0 = divZeroError - | a == minBound && b == (-1) = overflowError + | b == (-1) && a == minBound = overflowError -- Note [Order of tests] + -- in GHC.Int | otherwise = a `divModInt` b \end{code} @@ -328,6 +334,7 @@ instance (Integral a) => Num (Ratio a) where signum (x:%_) = signum x :% 1 fromInteger x = fromInteger x :% 1 +{-# RULES "fromRational/id" fromRational = id :: Rational -> Rational #-} instance (Integral a) => Fractional (Ratio a) where {-# SPECIALIZE instance Fractional Rational #-} (x:%y) / (x':%y') = (x*y') % (y*x') @@ -335,7 +342,7 @@ instance (Integral a) => Fractional (Ratio a) where recip (x:%y) | x < 0 = negate y :% negate x | otherwise = y :% x - fromRational (x:%y) = fromInteger x :% fromInteger y + fromRational (x:%y) = fromInteger x % fromInteger y instance (Integral a) => Real (Ratio a) where {-# SPECIALIZE instance Real Rational #-} @@ -423,6 +430,7 @@ odd = not . even Integer -> Integer -> Integer, Integer -> Int -> Integer, Int -> Int -> Int #-} +{-# INLINABLE (^) #-} -- See Note [Inlining (^)] (^) :: (Num a, Integral b) => a -> b -> a x0 ^ y0 | y0 < 0 = error "Negative exponent" | y0 == 0 = 1 @@ -438,8 +446,20 @@ x0 ^ y0 | y0 < 0 = error "Negative exponent" -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a +{-# INLINABLE (^^) #-} -- See Note [Inlining (^) x ^^ n = if n >= 0 then x^n else recip (x^(negate n)) +{- Note [Inlining (^) + ~~~~~~~~~~~~~~~~~~~~~ + The INLINABLE pragma allows (^) to be specialised at its call sites. + If it is called repeatedly at the same type, that can make a huge + difference, because of those constants which can be repeatedly + calculated. + + Currently the fromInteger calls are not floated because we get + \d1 d2 x y -> blah + after the gentle round of simplification. -} + ------------------------------------------------------- -- Special power functions for Rational -- @@ -500,11 +520,10 @@ x ^^ n = if n >= 0 then x^n else recip (x^(negate n)) in if even e then (nn :% dd) else (negate nn :% dd) ------------------------------------------------------- --- | @'gcd' x y@ is the greatest (positive) integer that divides both @x@ +-- | @'gcd' x y@ is the greatest (nonnegative) integer that divides both @x@ -- and @y@; for example @'gcd' (-3) 6@ = @3@, @'gcd' (-3) (-6)@ = @3@, --- @'gcd' 0 4@ = @4@. @'gcd' 0 0@ raises a runtime error. +-- @'gcd' 0 4@ = @4@. @'gcd' 0 0@ = @0@. gcd :: (Integral a) => a -> a -> a -gcd 0 0 = error "Prelude.gcd: gcd 0 0 is undefined" gcd x y = gcd' (abs x) (abs y) where gcd' a 0 = a gcd' a b = gcd' b (a `rem` b) @@ -519,16 +538,11 @@ lcm x y = abs ((x `quot` (gcd x y)) * y) #ifdef OPTIMISE_INTEGER_GCD_LCM {-# RULES "gcd/Int->Int->Int" gcd = gcdInt -"gcd/Integer->Integer->Integer" gcd = gcdInteger' +"gcd/Integer->Integer->Integer" gcd = gcdInteger "lcm/Integer->Integer->Integer" lcm = lcmInteger #-} -gcdInteger' :: Integer -> Integer -> Integer -gcdInteger' 0 0 = error "GHC.Real.gcdInteger': gcd 0 0 is undefined" -gcdInteger' a b = gcdInteger a b - gcdInt :: Int -> Int -> Int -gcdInt 0 0 = error "GHC.Real.gcdInt: gcd 0 0 is undefined" gcdInt a b = fromIntegral (gcdInteger (fromIntegral a) (fromIntegral b)) #endif