{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples, BangPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_HADDOCK hide #-}
module GHC.Real where
import GHC.Base
import GHC.Num
import GHC.List
import GHC.Enum
import GHC.Show
import {-# SOURCE #-} GHC.Exception( divZeroException, overflowException, ratioZeroDenomException )
#if defined(OPTIMISE_INTEGER_GCD_LCM)
# if defined(MIN_VERSION_integer_gmp)
import GHC.Integer.GMP.Internals
# else
# error unsupported OPTIMISE_INTEGER_GCD_LCM configuration
# endif
#endif
infixr 8 ^, ^^
infixl 7 /, `quot`, `rem`, `div`, `mod`
infixl 7 %
default ()
{-# NOINLINE divZeroError #-}
divZeroError :: a
divZeroError = raise# divZeroException
{-# NOINLINE ratioZeroDenominatorError #-}
ratioZeroDenominatorError :: a
ratioZeroDenominatorError = raise# ratioZeroDenomException
{-# NOINLINE overflowError #-}
overflowError :: a
overflowError = raise# overflowException
data Ratio a = !a :% !a deriving (Eq)
type Rational = Ratio Integer
ratioPrec, ratioPrec1 :: Int
ratioPrec = 7
ratioPrec1 = ratioPrec + 1
infinity, notANumber :: Rational
infinity = 1 :% 0
notANumber = 0 :% 0
{-# SPECIALISE (%) :: Integer -> Integer -> Rational #-}
(%) :: (Integral a) => a -> a -> Ratio a
numerator :: Ratio a -> a
denominator :: Ratio a -> a
reduce :: (Integral a) => a -> a -> Ratio a
{-# SPECIALISE reduce :: Integer -> Integer -> Rational #-}
reduce _ 0 = ratioZeroDenominatorError
reduce x y = (x `quot` d) :% (y `quot` d)
where d = gcd x y
x % y = reduce (x * signum y) (abs y)
numerator (x :% _) = x
denominator (_ :% y) = y
class (Num a, Ord a) => Real a where
toRational :: a -> Rational
class (Real a, Enum a) => Integral a where
quot :: a -> a -> a
rem :: a -> a -> a
div :: a -> a -> a
mod :: a -> a -> a
quotRem :: a -> a -> (a,a)
divMod :: a -> a -> (a,a)
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
class (Num a) => Fractional a where
{-# MINIMAL fromRational, (recip | (/)) #-}
(/) :: a -> a -> a
recip :: a -> a
fromRational :: Rational -> a
{-# INLINE recip #-}
{-# INLINE (/) #-}
recip x = 1 / x
x / y = x * recip y
class (Real a, Fractional a) => RealFrac a where
properFraction :: (Integral b) => a -> (b,a)
truncate :: (Integral b) => a -> b
round :: (Integral b) => a -> b
ceiling :: (Integral b) => a -> b
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
-1 -> n
0 -> if even n then n else m
1 -> m
_ -> errorWithoutStackTrace "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
numericEnumFrom :: (Fractional a) => a -> [a]
numericEnumFrom n = n `seq` (n : numericEnumFrom (n + 1))
numericEnumFromThen :: (Fractional a) => a -> a -> [a]
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 predicate (numericEnumFromThen e1 e2)
where
mid = (e2 - e1) / 2
predicate | e2 >= e1 = (<= e3 + mid)
| otherwise = (>= e3 + mid)
instance Real Int where
toRational x = toInteger x :% 1
instance Integral Int where
toInteger (I# i) = smallInteger i
a `quot` b
| b == 0 = divZeroError
| b == (-1) && a == minBound = overflowError
| otherwise = a `quotInt` b
a `rem` b
| b == 0 = divZeroError
| b == (-1) = 0
| otherwise = a `remInt` b
a `div` b
| b == 0 = divZeroError
| b == (-1) && a == minBound = overflowError
| otherwise = a `divInt` b
a `mod` b
| b == 0 = divZeroError
| b == (-1) = 0
| otherwise = a `modInt` b
a `quotRem` b
| b == 0 = divZeroError
| b == (-1) && a == minBound = (overflowError, 0)
| otherwise = a `quotRemInt` b
a `divMod` b
| b == 0 = divZeroError
| b == (-1) && a == minBound = (overflowError, 0)
| otherwise = a `divModInt` b
instance Real Word where
toRational x = toInteger x % 1
instance Integral Word where
quot (W# x#) y@(W# y#)
| y /= 0 = W# (x# `quotWord#` y#)
| otherwise = divZeroError
rem (W# x#) y@(W# y#)
| y /= 0 = W# (x# `remWord#` y#)
| otherwise = divZeroError
div (W# x#) y@(W# y#)
| y /= 0 = W# (x# `quotWord#` y#)
| otherwise = divZeroError
mod (W# x#) y@(W# y#)
| y /= 0 = W# (x# `remWord#` y#)
| otherwise = divZeroError
quotRem (W# x#) y@(W# y#)
| y /= 0 = case x# `quotRemWord#` y# of
(# q, r #) ->
(W# q, W# r)
| otherwise = divZeroError
divMod (W# x#) y@(W# y#)
| y /= 0 = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#))
| otherwise = divZeroError
toInteger (W# x#) = wordToInteger x#
instance Real Integer where
toRational x = x :% 1
instance Integral Integer where
toInteger n = n
{-# INLINE quot #-}
_ `quot` 0 = divZeroError
n `quot` d = n `quotInteger` d
{-# INLINE rem #-}
_ `rem` 0 = divZeroError
n `rem` d = n `remInteger` d
{-# INLINE div #-}
_ `div` 0 = divZeroError
n `div` d = n `divInteger` d
{-# INLINE mod #-}
_ `mod` 0 = divZeroError
n `mod` d = n `modInteger` d
{-# INLINE divMod #-}
_ `divMod` 0 = divZeroError
n `divMod` d = case n `divModInteger` d of
(# x, y #) -> (x, y)
{-# INLINE quotRem #-}
_ `quotRem` 0 = divZeroError
n `quotRem` d = case n `quotRemInteger` d of
(# q, r #) -> (q, r)
instance (Integral a) => Ord (Ratio a) where
{-# SPECIALIZE instance Ord Rational #-}
(x:%y) <= (x':%y') = x * y' <= x' * y
(x:%y) < (x':%y') = x * y' < x' * y
instance (Integral a) => Num (Ratio a) where
{-# SPECIALIZE instance Num Rational #-}
(x:%y) + (x':%y') = reduce (x*y' + x'*y) (y*y')
(x:%y) - (x':%y') = reduce (x*y' - x'*y) (y*y')
(x:%y) * (x':%y') = reduce (x * x') (y * y')
negate (x:%y) = (-x) :% y
abs (x:%y) = abs x :% y
signum (x:%_) = signum x :% 1
fromInteger x = fromInteger x :% 1
{-# RULES "fromRational/id" fromRational = id :: Rational -> Rational #-}
instance (Integral a) => Fractional (Ratio a) where
{-# SPECIALIZE instance Fractional Rational #-}
(x:%y) / (x':%y') = (x*y') % (y*x')
recip (0:%_) = ratioZeroDenominatorError
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
{-# SPECIALIZE instance Real Rational #-}
toRational (x:%y) = toInteger x :% toInteger y
instance (Integral a) => RealFrac (Ratio a) where
{-# SPECIALIZE instance RealFrac Rational #-}
properFraction (x:%y) = (fromInteger (toInteger q), r:%y)
where (q,r) = quotRem x y
instance (Show a) => Show (Ratio a) where
{-# SPECIALIZE instance Show Rational #-}
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 #-}
succ x = x + 1
pred x = x - 1
toEnum n = fromIntegral n :% 1
fromEnum = fromInteger . truncate
enumFrom = numericEnumFrom
enumFromThen = numericEnumFromThen
enumFromTo = numericEnumFromTo
enumFromThenTo = numericEnumFromThenTo
{-# NOINLINE [1] fromIntegral #-}
fromIntegral :: (Integral a, Num b) => a -> b
fromIntegral = fromInteger . toInteger
{-# RULES
"fromIntegral/Int->Int" fromIntegral = id :: Int -> Int
#-}
{-# RULES
"fromIntegral/Int->Word" fromIntegral = \(I# x#) -> W# (int2Word# x#)
"fromIntegral/Word->Int" fromIntegral = \(W# x#) -> I# (word2Int# x#)
"fromIntegral/Word->Word" fromIntegral = id :: Word -> Word
#-}
realToFrac :: (Real a, Fractional b) => a -> b
{-# NOINLINE [1] realToFrac #-}
realToFrac = fromRational . toRational
showSigned :: (Real a)
=> (a -> ShowS)
-> Int
-> a
-> ShowS
showSigned showPos p x
| x < 0 = showParen (p > 6) (showChar '-' . showPos (-x))
| otherwise = showPos x
even, odd :: (Integral a) => a -> Bool
even n = n `rem` 2 == 0
odd = not . even
{-# INLINABLE even #-}
{-# INLINABLE odd #-}
{-# SPECIALISE [1] (^) ::
Integer -> Integer -> Integer,
Integer -> Int -> Integer,
Int -> Int -> Int #-}
{-# INLINABLE [1] (^) #-}
(^) :: (Num a, Integral b) => a -> b -> a
x0 ^ y0 | y0 < 0 = errorWithoutStackTrace "Negative exponent"
| y0 == 0 = 1
| otherwise = f x0 y0
where
f x y | even y = f (x * x) (y `quot` 2)
| y == 1 = x
| otherwise = g (x * x) (y `quot` 2) x
g x y z | even y = g (x * x) (y `quot` 2) z
| y == 1 = x * z
| otherwise = g (x * x) (y `quot` 2) (x * z)
(^^) :: (Fractional a, Integral b) => a -> b -> a
{-# INLINABLE [1] (^^) #-}
x ^^ n = if n >= 0 then x^n else recip (x^(negate n))
{-# RULES
"^2/Int" forall x. x ^ (2 :: Int) = let u = x in u*u
"^3/Int" forall x. x ^ (3 :: Int) = let u = x in u*u*u
"^4/Int" forall x. x ^ (4 :: Int) = let u = x in u*u*u*u
"^5/Int" forall x. x ^ (5 :: Int) = let u = x in u*u*u*u*u
"^2/Integer" forall x. x ^ (2 :: Integer) = let u = x in u*u
"^3/Integer" forall x. x ^ (3 :: Integer) = let u = x in u*u*u
"^4/Integer" forall x. x ^ (4 :: Integer) = let u = x in u*u*u*u
"^5/Integer" forall x. x ^ (5 :: Integer) = let u = x in u*u*u*u*u
#-}
{-# RULES "(^)/Rational" (^) = (^%^) #-}
(^%^) :: Integral a => Rational -> a -> Rational
(n :% d) ^%^ e
| e < 0 = errorWithoutStackTrace "Negative exponent"
| e == 0 = 1 :% 1
| otherwise = (n ^ e) :% (d ^ e)
{-# RULES "(^^)/Rational" (^^) = (^^%^^) #-}
(^^%^^) :: Integral a => Rational -> a -> Rational
(n :% d) ^^%^^ e
| e > 0 = (n ^ e) :% (d ^ e)
| e == 0 = 1 :% 1
| n > 0 = (d ^ (negate e)) :% (n ^ (negate e))
| n == 0 = ratioZeroDenominatorError
| otherwise = let nn = d ^ (negate e)
dd = (negate n) ^ (negate e)
in if even e then (nn :% dd) else (negate nn :% dd)
gcd :: (Integral a) => a -> a -> a
{-# NOINLINE [1] gcd #-}
gcd x y = gcd' (abs x) (abs y)
where gcd' a 0 = a
gcd' a b = gcd' b (a `rem` b)
lcm :: (Integral a) => a -> a -> a
{-# SPECIALISE lcm :: Int -> Int -> Int #-}
{-# SPECIALISE lcm :: Word -> Word -> Word #-}
{-# NOINLINE [1] lcm #-}
lcm _ 0 = 0
lcm 0 _ = 0
lcm x y = abs ((x `quot` (gcd x y)) * y)
#if defined(OPTIMISE_INTEGER_GCD_LCM)
{-# RULES
"gcd/Int->Int->Int" gcd = gcdInt'
"gcd/Integer->Integer->Integer" gcd = gcdInteger
"lcm/Integer->Integer->Integer" lcm = lcmInteger
#-}
gcdInt' :: Int -> Int -> Int
gcdInt' (I# x) (I# y) = I# (gcdInt x y)
{-# RULES
"gcd/Word->Word->Word" gcd = gcdWord'
#-}
gcdWord' :: Word -> Word -> Word
gcdWord' (W# x) (W# y) = W# (gcdWord x y)
#endif
integralEnumFrom :: (Integral a, Bounded a) => a -> [a]
integralEnumFrom n = map fromInteger [toInteger n .. toInteger (maxBound `asTypeOf` n)]
integralEnumFromThen :: (Integral a, Bounded a) => a -> a -> [a]
integralEnumFromThen n1 n2
| i_n2 >= i_n1 = map fromInteger [i_n1, i_n2 .. toInteger (maxBound `asTypeOf` n1)]
| otherwise = map fromInteger [i_n1, i_n2 .. toInteger (minBound `asTypeOf` n1)]
where
i_n1 = toInteger n1
i_n2 = toInteger n2
integralEnumFromTo :: Integral a => a -> a -> [a]
integralEnumFromTo n m = map fromInteger [toInteger n .. toInteger m]
integralEnumFromThenTo :: Integral a => a -> a -> a -> [a]
integralEnumFromThenTo n1 n2 m
= map fromInteger [toInteger n1, toInteger n2 .. toInteger m]