X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FReal.lhs;h=0115409acb28d4647191c7f1caf0bdcc325c96f6;hb=3a7e8de77666fab3f6d2a7fc5c813cbca77ad57d;hp=bc63aebc58f504659ab647e53ee94e3c812ceaff;hpb=8aca076f0de902842f6c5df7322ba42d4664fce4;p=ghc-base.git diff --git a/GHC/Real.lhs b/GHC/Real.lhs index bc63aeb..0115409 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 @@ -437,11 +445,79 @@ x0 ^ y0 | y0 < 0 = error "Negative exponent" | otherwise = g (x * x) ((y - 1) `quot` 2) (x * z) -- | raise a number to an integral power -{-# SPECIALISE (^^) :: - Rational -> Int -> Rational #-} (^^) :: (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 +-- +-- see #4337 +-- +-- Rationale: +-- For a legitimate Rational (n :% d), the numerator and denominator are +-- coprime, i.e. they have no common prime factor. +-- Therefore all powers (n ^ a) and (d ^ b) are also coprime, so it is +-- not necessary to compute the greatest common divisor, which would be +-- done in the default implementation at each multiplication step. +-- Since exponentiation quickly leads to very large numbers and +-- calculation of gcds is generally very slow for large numbers, +-- avoiding the gcd leads to an order of magnitude speedup relatively +-- soon (and an asymptotic improvement overall). +-- +-- Note: +-- We cannot use these functions for general Ratio a because that would +-- change results in a multitude of cases. +-- The cause is that if a and b are coprime, their remainders by any +-- positive modulus generally aren't, so in the default implementation +-- reduction occurs. +-- +-- Example: +-- (17 % 3) ^ 3 :: Ratio Word8 +-- Default: +-- (17 % 3) ^ 3 = ((17 % 3) ^ 2) * (17 % 3) +-- = ((289 `mod` 256) % 9) * (17 % 3) +-- = (33 % 9) * (17 % 3) +-- = (11 % 3) * (17 % 3) +-- = (187 % 9) +-- But: +-- ((17^3) `mod` 256) % (3^3) = (4913 `mod` 256) % 27 +-- = 49 % 27 +-- +-- TODO: +-- Find out whether special-casing for numerator, denominator or +-- exponent = 1 (or -1, where that may apply) gains something. + +-- Special version of (^) for Rational base +{-# RULES "(^)/Rational" (^) = (^%^) #-} +(^%^) :: Integral a => Rational -> a -> Rational +(n :% d) ^%^ e + | e < 0 = error "Negative exponent" + | e == 0 = 1 :% 1 + | otherwise = (n ^ e) :% (d ^ e) + +-- Special version of (^^) for Rational base +{-# RULES "(^^)/Rational" (^^) = (^^%^^) #-} +(^^%^^) :: Integral a => Rational -> a -> Rational +(n :% d) ^^%^^ e + | e > 0 = (n ^ e) :% (d ^ e) + | e == 0 = 1 :% 1 + | n > 0 = (d ^ (negate e)) :% (n ^ (negate e)) + | n == 0 = error "Ratio.%: zero denominator" + | otherwise = let nn = d ^ (negate e) + dd = (negate n) ^ (negate e) + in if even e then (nn :% dd) else (negate nn :% dd) ------------------------------------------------------- -- | @'gcd' x y@ is the greatest (positive) integer that divides both @x@