X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FReal.lhs;h=575f1167b95732bc655b81307f8b7fe9319c757d;hb=7c0b04fd273621130062418bb764809c79488dd2;hp=c2e73c047e36040530fb44cfa288a3d78353f7e1;hpb=789216806265506d3b4637b3b22eb5a46eb5f8f8;p=haskell-directory.git diff --git a/GHC/Real.lhs b/GHC/Real.lhs index c2e73c0..575f116 100644 --- a/GHC/Real.lhs +++ b/GHC/Real.lhs @@ -1,5 +1,5 @@ \begin{code} -{-# OPTIONS -fno-implicit-prelude #-} +{-# OPTIONS_GHC -fno-implicit-prelude #-} ----------------------------------------------------------------------------- -- | -- Module : GHC.Real @@ -15,6 +15,7 @@ -- ----------------------------------------------------------------------------- +-- #hide module GHC.Real where import {-# SOURCE #-} GHC.Err @@ -26,6 +27,7 @@ import GHC.Show infixr 8 ^, ^^ infixl 7 /, `quot`, `rem`, `div`, `mod` +infixl 7 % default () -- Double isn't available yet, -- and we shouldn't be using defaults anyway @@ -39,6 +41,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) -- | Arbitrary-precision rational numbers, represented as a ratio of @@ -46,6 +49,10 @@ data (Integral a) => Ratio a = !a :% !a deriving (Eq) -- the '%' operator. type Rational = Ratio Integer +ratioPrec, ratioPrec1 :: Int +ratioPrec = 7 -- Precedence of ':%' constructor +ratioPrec1 = ratioPrec + 1 + infinity, notANumber :: Rational infinity = 1 :% 0 notANumber = 0 :% 0 @@ -56,9 +63,19 @@ notANumber = 0 :% 0 \begin{code} +-- | Forms the ratio of two integral numbers. {-# SPECIALISE (%) :: Integer -> Integer -> Rational #-} (%) :: (Integral a) => a -> a -> Ratio a -numerator, denominator :: (Integral a) => Ratio a -> a + +-- | Extract the numerator of the ratio in reduced form: +-- the numerator and denominator have no common factor and the denominator +-- is positive. +numerator :: (Integral a) => Ratio a -> a + +-- | Extract the denominator of the ratio in reduced form: +-- the numerator and denominator have no common factor and the denominator +-- is positive. +denominator :: (Integral a) => Ratio a -> a \end{code} \tr{reduce} is a subsidiary function used only in this module . @@ -89,11 +106,30 @@ denominator (_ :% y) = y \begin{code} class (Num a, Ord a) => Real a where + -- | the rational equivalent of its real argument with full precision toRational :: a -> Rational +-- | Integral numbers, supporting integer division. +-- +-- Minimal complete definition: 'quotRem' and 'toInteger' class (Real a, Enum a) => Integral a where - quot, rem, div, mod :: a -> a -> a - quotRem, divMod :: a -> a -> (a,a) + -- | integer division truncated toward zero + quot :: a -> a -> a + -- | integer remainder, satisfying + -- + -- > (x `quot` y)*y + (x `rem` y) == x + rem :: a -> a -> a + -- | integer division truncated toward negative infinity + div :: a -> a -> a + -- | integer modulus, satisfying + -- + -- > (x `div` y)*y + (x `mod` y) == x + mod :: a -> a -> a + -- | simultaneous 'quot' and 'rem' + quotRem :: a -> a -> (a,a) + -- | simultaneous 'div' and 'mod' + divMod :: a -> a -> (a,a) + -- | conversion to 'Integer' toInteger :: a -> Integer n `quot` d = q where (q,_) = quotRem n d @@ -103,18 +139,46 @@ class (Real a, Enum a) => Integral a where divMod n d = if signum r == negate (signum d) then (q-1, r+d) else qr where qr@(q,r) = quotRem n d +-- | Fractional numbers, supporting real division. +-- +-- Minimal complete definition: 'fromRational' and ('recip' or @('/')@) class (Num a) => Fractional a where + -- | fractional division (/) :: a -> a -> a + -- | reciprocal fraction recip :: a -> a + -- | Conversion from a 'Rational' (that is @'Ratio' 'Integer'@). + -- A floating literal stands for an application of 'fromRational' + -- to a value of type 'Rational', so such literals have type + -- @('Fractional' a) => a@. fromRational :: Rational -> a recip x = 1 / x x / y = x * recip y +-- | Extracting components of fractions. +-- +-- Minimal complete definition: 'properFraction' class (Real a, Fractional a) => RealFrac a where + -- | The function 'properFraction' takes a real fractional number @x@ + -- and returns a pair @(n,f)@ such that @x = n+f@, and: + -- + -- * @n@ is an integral number with the same sign as @x@; and + -- + -- * @f@ is a fraction with the same type and sign as @x@, + -- and with absolute value less than @1@. + -- + -- The default definitions of the 'ceiling', 'floor', 'truncate' + -- and 'round' functions are in terms of 'properFraction'. properFraction :: (Integral b) => a -> (b,a) - truncate, round :: (Integral b) => a -> b - ceiling, floor :: (Integral b) => a -> b + -- | @'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 :: (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 truncate x = m where (m,_) = properFraction x @@ -149,7 +213,7 @@ numericEnumFromThenTo :: (Ord a, Fractional a) => a -> a -> a -> [a] numericEnumFromThenTo e1 e2 e3 = takeWhile pred (numericEnumFromThen e1 e2) where mid = (e2 - e1) / 2 - pred | e2 > e1 = (<= e3 + mid) + pred | e2 >= e1 = (<= e3 + mid) | otherwise = (>= e3 + mid) \end{code} @@ -167,19 +231,35 @@ instance Real Int where instance Integral Int where toInteger i = int2Integer i -- give back a full-blown Integer - -- Following chks for zero divisor are non-standard (WDP) - a `quot` b = if b /= 0 - then a `quotInt` b - else error "Prelude.Integral.quot{Int}: divide by 0" - a `rem` b = if b /= 0 - then a `remInt` b - else error "Prelude.Integral.rem{Int}: divide by 0" - - x `div` y = x `divInt` y - x `mod` y = x `modInt` y - - a `quotRem` b = a `quotRemInt` b - a `divMod` b = a `divModInt` b + a `quot` b + | b == 0 = divZeroError + | a == minBound && b == (-1) = overflowError + | otherwise = a `quotInt` b + + a `rem` b + | b == 0 = divZeroError + | a == minBound && b == (-1) = overflowError + | otherwise = a `remInt` b + + a `div` b + | b == 0 = divZeroError + | a == minBound && b == (-1) = overflowError + | otherwise = a `divInt` b + + a `mod` b + | b == 0 = divZeroError + | a == minBound && b == (-1) = overflowError + | otherwise = a `modInt` b + + a `quotRem` b + | b == 0 = divZeroError + | a == minBound && b == (-1) = overflowError + | otherwise = a `quotRemInt` b + + a `divMod` b + | b == 0 = divZeroError + | a == minBound && b == (-1) = overflowError + | otherwise = a `divModInt` b \end{code} @@ -196,14 +276,19 @@ instance Real Integer where instance Integral Integer where toInteger n = n + a `quot` 0 = divZeroError n `quot` d = n `quotInteger` d - n `rem` d = n `remInteger` d - n `div` d = q where (q,_) = divMod n d - n `mod` d = r where (_,r) = divMod n d + a `rem` 0 = divZeroError + n `rem` d = n `remInteger` d + a `divMod` 0 = divZeroError a `divMod` b = a `divModInteger` b + + a `quotRem` 0 = divZeroError a `quotRem` b = a `quotRemInteger` b + + -- use the defaults for div & mod \end{code} @@ -246,11 +331,11 @@ instance (Integral a) => RealFrac (Ratio a) where instance (Integral a) => Show (Ratio a) where {-# SPECIALIZE instance Show Rational #-} - showsPrec p (x:%y) = showParen (p > ratio_prec) - (shows x . showString " % " . shows y) - -ratio_prec :: Int -ratio_prec = 7 + showsPrec p (x:%y) = showParen (p > ratioPrec) $ + showsPrec ratioPrec1 x . + showString "%" . -- H98 report has spaces round the % + -- but we removed them [May 04] + showsPrec ratioPrec1 y instance (Integral a) => Enum (Ratio a) where {-# SPECIALIZE instance Enum Rational #-} @@ -274,6 +359,7 @@ instance (Integral a) => Enum (Ratio a) where %********************************************************* \begin{code} +-- | general coercion from integral types fromIntegral :: (Integral a, Num b) => a -> b fromIntegral = fromInteger . toInteger @@ -281,6 +367,7 @@ fromIntegral = fromInteger . toInteger "fromIntegral/Int->Int" fromIntegral = id :: Int -> Int #-} +-- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b realToFrac = fromRational . toRational @@ -296,7 +383,12 @@ realToFrac = fromRational . toRational %********************************************************* \begin{code} -showSigned :: (Real a) => (a -> ShowS) -> Int -> a -> ShowS +-- | Converts a possibly-negative 'Real' value to a string. +showSigned :: (Real a) + => (a -> ShowS) -- ^ a function that can show unsigned values + -> Int -- ^ the precedence of the enclosing context + -> a -- ^ the value to show + -> ShowS showSigned showPos p x | x < 0 = showParen (p > 6) (showChar '-' . showPos (-x)) | otherwise = showPos x @@ -306,6 +398,7 @@ even n = n `rem` 2 == 0 odd = not . even ------------------------------------------------------- +-- | raise a number to a non-negative integral power {-# SPECIALISE (^) :: Integer -> Integer -> Integer, Integer -> Int -> Integer, @@ -319,6 +412,7 @@ x ^ n | n > 0 = f x (n-1) x | otherwise = f b (i-1) (b*y) _ ^ _ = error "Prelude.^: negative exponent" +-- | raise a number to an integral power {-# SPECIALISE (^^) :: Rational -> Int -> Rational #-} (^^) :: (Fractional a, Integral b) => a -> b -> a @@ -326,12 +420,16 @@ x ^^ n = if n >= 0 then x^n else recip (x^(negate n)) ------------------------------------------------------- +-- | @'gcd' x y@ is the greatest (positive) 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 :: (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) +-- | @'lcm' x y@ is the smallest positive integer that both @x@ and @y@ divide. lcm :: (Integral a) => a -> a -> a {-# SPECIALISE lcm :: Int -> Int -> Int #-} lcm _ 0 = 0