final revision to GArrow classes
[ghc-base.git] / GHC / Real.lhs
index b3316d1..0115409 100644 (file)
@@ -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}
 
@@ -424,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
@@ -439,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
 --