Export Unicode and newline functionality from System.IO; update Haddock docs
[ghc-base.git] / GHC / Real.lhs
index f7e2eb2..6a3f335 100644 (file)
@@ -1,5 +1,5 @@
 \begin{code}
-{-# OPTIONS_GHC -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -XNoImplicitPrelude #-}
 {-# OPTIONS_HADDOCK hide #-}
 -----------------------------------------------------------------------------
 -- |
@@ -24,6 +24,7 @@ import GHC.Num
 import GHC.List
 import GHC.Enum
 import GHC.Show
+import GHC.Err
 
 infixr 8  ^, ^^
 infixl 7  /, `quot`, `rem`, `div`, `mod`
@@ -173,7 +174,8 @@ class  (Real a, Fractional a) => RealFrac a  where
     properFraction      :: (Integral b) => a -> (b,a)
     -- | @'truncate' x@ returns the integer nearest @x@ between zero and @x@
     truncate            :: (Integral b) => a -> b
-    -- | @'round' x@ returns the nearest integer to @x@
+    -- | @'round' x@ returns the nearest integer to @x@;
+    --   the even integer if @x@ is equidistant between two integers
     round               :: (Integral b) => a -> b
     -- | @'ceiling' x@ returns the least integer not less than @x@
     ceiling             :: (Integral b) => a -> b
@@ -188,6 +190,7 @@ class  (Real a, Fractional a) => RealFrac a  where
                                 -1 -> n
                                 0  -> if even n then n else m
                                 1  -> m
+                                _  -> error "round default defn: Bad value"
     
     ceiling x           =  if r > 0 then n + 1 else n
                            where (n,r) = properFraction x
@@ -201,20 +204,21 @@ These 'numeric' enumerations come straight from the Report
 
 \begin{code}
 numericEnumFrom         :: (Fractional a) => a -> [a]
-numericEnumFrom         =  iterate (+1)
+numericEnumFrom n      =  n `seq` (n : numericEnumFrom (n + 1))
 
 numericEnumFromThen     :: (Fractional a) => a -> a -> [a]
-numericEnumFromThen n m =  iterate (+(m-n)) n
+numericEnumFromThen n m        = n `seq` m `seq` (n : numericEnumFromThen m (m+m-n))
 
 numericEnumFromTo       :: (Ord a, Fractional a) => a -> a -> [a]
 numericEnumFromTo n m   = takeWhile (<= m + 1/2) (numericEnumFrom n)
 
 numericEnumFromThenTo   :: (Ord a, Fractional a) => a -> a -> a -> [a]
-numericEnumFromThenTo e1 e2 e3 = takeWhile pred (numericEnumFromThen e1 e2)
+numericEnumFromThenTo e1 e2 e3
+    = takeWhile predicate (numericEnumFromThen e1 e2)
                                 where
                                  mid = (e2 - e1) / 2
-                                 pred | e2 >= e1  = (<= e3 + mid)
-                                      | otherwise = (>= e3 + mid)
+                                 predicate | e2 >= e1  = (<= e3 + mid)
+                                           | otherwise = (>= e3 + mid)
 \end{code}
 
 
@@ -229,7 +233,7 @@ instance  Real Int  where
     toRational x        =  toInteger x % 1
 
 instance  Integral Int  where
-    toInteger i = int2Integer i  -- give back a full-blown Integer
+    toInteger (I# i) = smallInteger i
 
     a `quot` b
      | b == 0                     = divZeroError
@@ -276,17 +280,19 @@ instance  Real Integer  where
 instance  Integral Integer where
     toInteger n      = n
 
-    a `quot` 0 = divZeroError
+    _ `quot` 0 = divZeroError
     n `quot` d = n `quotInteger` d
 
-    a `rem` 0 = divZeroError
+    _ `rem` 0 = divZeroError
     n `rem`  d = n `remInteger`  d
 
-    a `divMod` 0 = divZeroError
-    a `divMod` b = a `divModInteger` b
+    _ `divMod` 0 = divZeroError
+    a `divMod` b = case a `divModInteger` b of
+                   (# x, y #) -> (x, y)
 
-    a `quotRem` 0 = divZeroError
-    a `quotRem` b = a `quotRemInteger` b
+    _ `quotRem` 0 = divZeroError
+    a `quotRem` b = case a `quotRemInteger` b of
+                    (# q, r #) -> (q, r)
 
     -- use the defaults for div & mod
 \end{code}
@@ -333,8 +339,11 @@ instance  (Integral a)  => Show (Ratio a)  where
     {-# SPECIALIZE instance Show Rational #-}
     showsPrec p (x:%y)  =  showParen (p > ratioPrec) $
                            showsPrec ratioPrec1 x . 
-                           showString "%" .     -- H98 report has spaces round the %
-                                                -- but we removed them [May 04]
+                           showString " % " .
+                           -- H98 report has spaces round the %
+                           -- but we removed them [May 04]
+                           -- and added them again for consistency with
+                           -- Haskell 98 [Sep 08, #1920]
                            showsPrec ratioPrec1 y
 
 instance  (Integral a)  => Enum (Ratio a)  where
@@ -342,7 +351,7 @@ instance  (Integral a)  => Enum (Ratio a)  where
     succ x              =  x + 1
     pred x              =  x - 1
 
-    toEnum n            =  fromInteger (int2Integer n) :% 1
+    toEnum n            =  fromIntegral n :% 1
     fromEnum            =  fromInteger . truncate
 
     enumFrom            =  numericEnumFrom
@@ -403,14 +412,18 @@ odd             =  not . even
         Integer -> Integer -> Integer,
         Integer -> Int -> Integer,
         Int -> Int -> Int #-}
-(^)             :: (Num a, Integral b) => a -> b -> a
-_ ^ 0           =  1
-x ^ n | n > 0   =  f x (n-1) x
-                   where f _ 0 y = y
-                         f a d y = g a d  where
-                                   g b i | even i  = g (b*b) (i `quot` 2)
-                                         | otherwise = f b (i-1) (b*y)
-_ ^ _           = error "Prelude.^: negative exponent"
+(^) :: (Num a, Integral b) => a -> b -> a
+x0 ^ y0 | y0 < 0    = error "Negative exponent"
+        | y0 == 0   = 1
+        | otherwise = f x0 y0
+    where -- f : x0 ^ y0 = x ^ y
+          f x y | even y    = f (x * x) (y `quot` 2)
+                | y == 1    = x
+                | otherwise = g (x * x) ((y - 1) `quot` 2) x
+          -- g : x0 ^ y0 = (x ^ y) * z
+          g x y z | even y = g (x * x) (y `quot` 2) z
+                  | y == 1 = x * z
+                  | otherwise = g (x * x) ((y - 1) `quot` 2) (x * z)
 
 -- | raise a number to an integral power
 {-# SPECIALISE (^^) ::
@@ -436,13 +449,23 @@ lcm _ 0         =  0
 lcm 0 _         =  0
 lcm x y         =  abs ((x `quot` (gcd x y)) * y)
 
-
 {-# 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
  #-}
 
+-- XXX to use another Integer implementation, you might need to disable
+-- the gcd/Integer and lcm/Integer RULES above
+--
+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))
+
 integralEnumFrom :: (Integral a, Bounded a) => a -> [a]
 integralEnumFrom n = map fromInteger [toInteger n .. toInteger (maxBound `asTypeOf` n)]