X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FReal.lhs;h=bc63aebc58f504659ab647e53ee94e3c812ceaff;hb=8aca076f0de902842f6c5df7322ba42d4664fce4;hp=da6053eb73c2e69db43f9c141c7fa2373b88cb66;hpb=8827985d7ce902bfc916e4168049c9a46a1d7fe8;p=ghc-base.git diff --git a/GHC/Real.lhs b/GHC/Real.lhs index da6053e..bc63aeb 100644 --- a/GHC/Real.lhs +++ b/GHC/Real.lhs @@ -4,9 +4,9 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Real --- Copyright : (c) The FFI Task Force, 1994-2002 +-- Copyright : (c) The University of Glasgow, 1994-2002 -- License : see libraries/base/LICENSE --- +-- -- Maintainer : cvs-ghc@haskell.org -- Stability : internal -- Portability : non-portable (GHC Extensions) @@ -24,12 +24,13 @@ import GHC.Num import GHC.List import GHC.Enum import GHC.Show +import GHC.Err infixr 8 ^, ^^ infixl 7 /, `quot`, `rem`, `div`, `mod` infixl 7 % -default () -- Double isn't available yet, +default () -- Double isn't available yet, -- and we shouldn't be using defaults anyway \end{code} @@ -57,8 +58,8 @@ infinity, notANumber :: Rational infinity = 1 :% 0 notANumber = 0 :% 0 --- Use :%, not % for Inf/NaN; the latter would --- immediately lead to a runtime error, because it normalises. +-- Use :%, not % for Inf/NaN; the latter would +-- immediately lead to a runtime error, because it normalises. \end{code} @@ -132,10 +133,15 @@ class (Real a, Enum a) => Integral a where -- | conversion to 'Integer' toInteger :: a -> Integer + {-# INLINE quot #-} + {-# INLINE rem #-} + {-# INLINE div #-} + {-# INLINE mod #-} n `quot` d = q where (q,_) = quotRem n d n `rem` d = r where (_,r) = quotRem n d n `div` d = q where (q,_) = divMod n d n `mod` d = r where (_,r) = divMod n d + divMod n d = if signum r == negate (signum d) then (q-1, r+d) else qr where qr@(q,r) = quotRem n d @@ -153,6 +159,8 @@ class (Num a) => Fractional a where -- @('Fractional' a) => a@. fromRational :: Rational -> a + {-# INLINE recip #-} + {-# INLINE (/) #-} recip x = 1 / x x / y = x * recip y @@ -173,15 +181,17 @@ 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 -- | @'floor' x@ returns the greatest integer not greater than @x@ floor :: (Integral b) => a -> b + {-# INLINE truncate #-} truncate x = m where (m,_) = properFraction x - + round x = let (n,r) = properFraction x m = if r < 0 then n - 1 else n + 1 in case signum (abs r - 0.5) of @@ -189,10 +199,10 @@ class (Real a, Fractional a) => RealFrac a where 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 - + floor x = if r < 0 then n - 1 else n where (n,r) = properFraction x \end{code} @@ -321,7 +331,10 @@ instance (Integral a) => Num (Ratio a) where instance (Integral a) => Fractional (Ratio a) where {-# SPECIALIZE instance Fractional Rational #-} (x:%y) / (x':%y') = (x*y') % (y*x') - recip (x:%y) = y % x + recip (0:%_) = error "Ratio.%: zero denominator" + recip (x:%y) + | x < 0 = negate y :% negate x + | otherwise = y :% x fromRational (x:%y) = fromInteger x :% fromInteger y instance (Integral a) => Real (Ratio a) where @@ -336,7 +349,7 @@ instance (Integral a) => RealFrac (Ratio a) where instance (Integral a) => Show (Ratio a) where {-# SPECIALIZE instance Show Rational #-} showsPrec p (x:%y) = showParen (p > ratioPrec) $ - showsPrec ratioPrec1 x . + showsPrec ratioPrec1 x . showString " % " . -- H98 report has spaces round the % -- but we removed them [May 04] @@ -396,7 +409,7 @@ showSigned :: (Real a) -> Int -- ^ the precedence of the enclosing context -> a -- ^ the value to show -> ShowS -showSigned showPos p x +showSigned showPos p x | x < 0 = showParen (p > 6) (showChar '-' . showPos (-x)) | otherwise = showPos x @@ -447,19 +460,22 @@ lcm _ 0 = 0 lcm 0 _ = 0 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' "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)) +#endif + integralEnumFrom :: (Integral a, Bounded a) => a -> [a] integralEnumFrom n = map fromInteger [toInteger n .. toInteger (maxBound `asTypeOf` n)]