X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=GHC%2FReal.lhs;h=edee3501b4b474beae2a6ad9fecfbc8d2cd7ba35;hb=9da2d4c92821be09b27afa5b8bc1368b305a1496;hp=0c27ce38bf72cdebc70da9c9816d18fc8f3b35ff;hpb=260e7f2ed9a43c6ecf5a556d77817f39ed2893ab;p=ghc-base.git diff --git a/GHC/Real.lhs b/GHC/Real.lhs index 0c27ce3..edee350 100644 --- a/GHC/Real.lhs +++ b/GHC/Real.lhs @@ -1,25 +1,19 @@ -% ------------------------------------------------------------------------------ -% $Id: Real.lhs,v 1.2 2001/12/21 15:07:25 simonmar Exp $ -% -% (c) The University of Glasgow, 1994-2000 -% - -\section[GHC.Real]{Module @GHC.Real@} - -The types - - Ratio, Rational - -and the classes - - Real - Integral - Fractional - RealFrac - - \begin{code} {-# OPTIONS -fno-implicit-prelude #-} +----------------------------------------------------------------------------- +-- | +-- Module : GHC.Real +-- Copyright : (c) The FFI Task Force, 1994-2002 +-- License : see libraries/base/LICENSE +-- +-- Maintainer : cvs-ghc@haskell.org +-- Stability : internal +-- Portability : non-portable (GHC Extensions) +-- +-- The types 'Ratio' and 'Rational', and the classes 'Real', 'Fractional', +-- 'Integral', and 'RealFrac'. +-- +----------------------------------------------------------------------------- module GHC.Real where @@ -32,6 +26,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 @@ -46,7 +41,22 @@ default () -- Double isn't available yet, \begin{code} data (Integral a) => 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 +-- 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 + +-- Use :%, not % for Inf/NaN; the latter would +-- immediately lead to a runtime error, because it normalises. \end{code} @@ -144,7 +154,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} @@ -162,18 +172,22 @@ 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" + a `quot` 0 = divZeroError + a `quot` b = a `quotInt` b - x `div` y = x `divInt` y - x `mod` y = x `modInt` y + a `rem` 0 = divZeroError + a `rem` b = a `remInt` b + a `div` 0 = divZeroError + a `div` b = a `divInt` b + + a `mod` 0 = divZeroError + a `mod` b = a `modInt` b + + a `quotRem` 0 = divZeroError a `quotRem` b = a `quotRemInt` b + + a `divMod` 0 = divZeroError a `divMod` b = a `divModInt` b \end{code} @@ -191,14 +205,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} @@ -241,11 +260,10 @@ 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 " % " . + showsPrec ratioPrec1 y instance (Integral a) => Enum (Ratio a) where {-# SPECIALIZE instance Enum Rational #-} @@ -282,16 +300,6 @@ realToFrac = fromRational . toRational {-# RULES "realToFrac/Int->Int" realToFrac = id :: Int -> Int #-} - --- For backward compatibility -{-# DEPRECATED fromInt "use fromIntegral instead" #-} -fromInt :: Num a => Int -> a -fromInt = fromIntegral - --- For backward compatibility -{-# DEPRECATED toInt "use fromIntegral instead" #-} -toInt :: Integral a => a -> Int -toInt = fromIntegral \end{code} %*********************************************************