{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples, BangPatterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.Real where
#include "MachDeps.h"
import GHC.Base
import GHC.Num
import GHC.List
import GHC.Enum
import GHC.Show
import {-# SOURCE #-} GHC.Exception( divZeroException, overflowException
                                   , underflowException
                                   , ratioZeroDenomException )
import GHC.Num.BigNat (gcdInt,gcdWord)
infixr 8  ^, ^^
infixl 7  /, `quot`, `rem`, `div`, `mod`
infixl 7  %
default ()              
                        
{-# NOINLINE divZeroError #-}
divZeroError :: a
divZeroError :: forall a. a
divZeroError = SomeException -> a
forall a b. a -> b
raise# SomeException
divZeroException
{-# NOINLINE ratioZeroDenominatorError #-}
ratioZeroDenominatorError :: a
ratioZeroDenominatorError :: forall a. a
ratioZeroDenominatorError = SomeException -> a
forall a b. a -> b
raise# SomeException
ratioZeroDenomException
{-# NOINLINE overflowError #-}
overflowError :: a
overflowError :: forall a. a
overflowError = SomeException -> a
forall a b. a -> b
raise# SomeException
overflowException
{-# NOINLINE underflowError #-}
underflowError :: a
underflowError :: forall a. a
underflowError = SomeException -> a
forall a b. a -> b
raise# SomeException
underflowException
data  Ratio a = !a :% !a  deriving Ratio a -> Ratio a -> Bool
(Ratio a -> Ratio a -> Bool)
-> (Ratio a -> Ratio a -> Bool) -> Eq (Ratio a)
forall a. Eq a => Ratio a -> Ratio a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Ratio a -> Ratio a -> Bool
== :: Ratio a -> Ratio a -> Bool
$c/= :: forall a. Eq a => Ratio a -> Ratio a -> Bool
/= :: Ratio a -> Ratio a -> Bool
Eq 
type  Rational          =  Ratio Integer
ratioPrec, ratioPrec1 :: Int
ratioPrec :: Int
ratioPrec  = Int
7  
ratioPrec1 :: Int
ratioPrec1 = Int
ratioPrec Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
infinity, notANumber :: Rational
infinity :: Rational
infinity   = Integer
1 Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
0
notANumber :: Rational
notANumber = Integer
0 Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
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 :: forall a. Integral a => a -> a -> Ratio a
reduce a
_ a
0              =  Ratio a
forall a. a
ratioZeroDenominatorError
reduce a
x a
y              =  (a
x a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
d) a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% (a
y a -> a -> a
forall a. Integral a => a -> a -> a
`quot` a
d)
                           where d :: a
d = a -> a -> a
forall a. Integral a => a -> a -> a
gcd a
x a
y
a
x % :: forall a. Integral a => a -> a -> Ratio a
% a
y                   =  a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
reduce (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a. Num a => a -> a
signum a
y) (a -> a
forall a. Num a => a -> a
abs a
y)
numerator :: forall a. Ratio a -> a
numerator   (a
x :% a
_)    =  a
x
denominator :: forall a. Ratio a -> a
denominator (a
_ :% a
y)    =  a
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 #-}
    a
n `quot` a
d          =  a
q  where (a
q,a
_) = a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
quotRem a
n a
d
    a
n `rem` a
d           =  a
r  where (a
_,a
r) = a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
quotRem a
n a
d
    a
n `div` a
d           =  a
q  where (a
q,a
_) = a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
divMod a
n a
d
    a
n `mod` a
d           =  a
r  where (a
_,a
r) = a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
divMod a
n a
d
    divMod a
n a
d          =  if a -> a
forall a. Num a => a -> a
signum a
r a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a -> a
forall a. Num a => a -> a
negate (a -> a
forall a. Num a => a -> a
signum a
d) then (a
qa -> a -> a
forall a. Num a => a -> a -> a
-a
1, a
ra -> a -> a
forall a. Num a => a -> a -> a
+a
d) else (a, a)
qr
                           where qr :: (a, a)
qr@(a
q,a
r) = a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
quotRem a
n a
d
class  (Num a) => Fractional a  where
    {-# MINIMAL fromRational, (recip | (/)) #-}
    
    (/)                 :: a -> a -> a
    
    recip               :: a -> a
    
    
    
    
    fromRational        :: Rational -> a
    {-# INLINE recip #-}
    {-# INLINE (/) #-}
    recip a
x             =  a
1 a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
x
    a
x / a
y               = a
x a -> a -> a
forall a. Num a => a -> a -> a
* a -> a
forall a. Fractional a => a -> a
recip a
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 a
x          =  b
m  where (b
m,a
_) = a -> (b, a)
forall b. Integral b => a -> (b, a)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction a
x
    round a
x             =  let (b
n,a
r) = a -> (b, a)
forall b. Integral b => a -> (b, a)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction a
x
                               m :: b
m     = if a
r a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 then b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1 else b
n b -> b -> b
forall a. Num a => a -> a -> a
+ b
1
                           in case a -> a
forall a. Num a => a -> a
signum (a -> a
forall a. Num a => a -> a
abs a
r a -> a -> a
forall a. Num a => a -> a -> a
- a
0.5) of
                                -1 -> b
n
                                a
0  -> if b -> Bool
forall a. Integral a => a -> Bool
even b
n then b
n else b
m
                                a
1  -> b
m
                                a
_  -> [Char] -> b
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"round default defn: Bad value"
    ceiling a
x           =  if a
r a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0 then b
n b -> b -> b
forall a. Num a => a -> a -> a
+ b
1 else b
n
                           where (b
n,a
r) = a -> (b, a)
forall b. Integral b => a -> (b, a)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction a
x
    floor a
x             =  if a
r a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 then b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1 else b
n
                           where (b
n,a
r) = a -> (b, a)
forall b. Integral b => a -> (b, a)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction a
x
numericEnumFrom         :: (Fractional a) => a -> [a]
{-# INLINE numericEnumFrom #-}  
numericEnumFrom :: forall a. Fractional a => a -> [a]
numericEnumFrom a
n       = a -> [a]
go a
0
  where
    
    go :: a -> [a]
go !a
k = let !n' :: a
n' = a
n a -> a -> a
forall a. Num a => a -> a -> a
+ a
k
             in a
n' a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a -> [a]
go (a
k a -> a -> a
forall a. Num a => a -> a -> a
+ a
1)
numericEnumFromThen     :: (Fractional a) => a -> a -> [a]
{-# INLINE numericEnumFromThen #-}  
numericEnumFromThen :: forall a. Fractional a => a -> a -> [a]
numericEnumFromThen a
n a
m = a -> [a]
go a
0
  where
    step :: a
step = a
m a -> a -> a
forall a. Num a => a -> a -> a
- a
n
    
    go :: a -> [a]
go !a
k = let !n' :: a
n' = a
n a -> a -> a
forall a. Num a => a -> a -> a
+ a
k a -> a -> a
forall a. Num a => a -> a -> a
* a
step
             in a
n' a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a -> [a]
go (a
k a -> a -> a
forall a. Num a => a -> a -> a
+ a
1)
numericEnumFromTo       :: (Ord a, Fractional a) => a -> a -> [a]
{-# INLINE numericEnumFromTo #-}  
numericEnumFromTo :: forall a. (Ord a, Fractional a) => a -> a -> [a]
numericEnumFromTo a
n a
m   = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
m a -> a -> a
forall a. Num a => a -> a -> a
+ a
1a -> a -> a
forall a. Fractional a => a -> a -> a
/a
2) (a -> [a]
forall a. Fractional a => a -> [a]
numericEnumFrom a
n)
numericEnumFromThenTo   :: (Ord a, Fractional a) => a -> a -> a -> [a]
{-# INLINE numericEnumFromThenTo #-}  
numericEnumFromThenTo :: forall a. (Ord a, Fractional a) => a -> a -> a -> [a]
numericEnumFromThenTo a
e1 a
e2 a
e3
    = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile a -> Bool
predicate (a -> a -> [a]
forall a. Fractional a => a -> a -> [a]
numericEnumFromThen a
e1 a
e2)
                                where
                                 mid :: a
mid = (a
e2 a -> a -> a
forall a. Num a => a -> a -> a
- a
e1) a -> a -> a
forall a. Fractional a => a -> a -> a
/ a
2
                                 predicate :: a -> Bool
predicate | a
e2 a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
e1  = (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
e3 a -> a -> a
forall a. Num a => a -> a -> a
+ a
mid)
                                           | Bool
otherwise = (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= a
e3 a -> a -> a
forall a. Num a => a -> a -> a
+ a
mid)
instance  Real Int  where
    toRational :: Int -> Rational
toRational Int
x        =  Int -> Integer
forall a. Integral a => a -> Integer
toInteger Int
x Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1
instance Integral Int where
    toInteger :: Int -> Integer
toInteger (I# Int#
i) = Int# -> Integer
IS Int#
i
    {-# INLINE quot #-} 
    Int
a quot :: Int -> Int -> Int
`quot` Int
b
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0                     = Int
forall a. a
divZeroError
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (-Int
1) Bool -> Bool -> Bool
&& Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
forall a. Bounded a => a
minBound = Int
forall a. a
overflowError 
                                                  
     | Bool
otherwise                  =  Int
a Int -> Int -> Int
`quotInt` Int
b
    {-# INLINE rem #-} 
    !Int
a rem :: Int -> Int -> Int
`rem` Int
b 
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0                     = Int
forall a. a
divZeroError
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (-Int
1)                  = Int
0
     | Bool
otherwise                  =  Int
a Int -> Int -> Int
`remInt` Int
b
    {-# INLINE div #-} 
    Int
a div :: Int -> Int -> Int
`div` Int
b
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0                     = Int
forall a. a
divZeroError
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (-Int
1) Bool -> Bool -> Bool
&& Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
forall a. Bounded a => a
minBound = Int
forall a. a
overflowError 
                                                  
     | Bool
otherwise                  =  Int
a Int -> Int -> Int
`divInt` Int
b
    {-# INLINE mod #-} 
    !Int
a mod :: Int -> Int -> Int
`mod` Int
b 
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0                     = Int
forall a. a
divZeroError
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (-Int
1)                  = Int
0
     | Bool
otherwise                  =  Int
a Int -> Int -> Int
`modInt` Int
b
    {-# INLINE quotRem #-} 
    Int
a quotRem :: Int -> Int -> (Int, Int)
`quotRem` Int
b
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0                     = (Int, Int)
forall a. a
divZeroError
       
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (-Int
1) Bool -> Bool -> Bool
&& Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
forall a. Bounded a => a
minBound = (Int
forall a. a
overflowError, Int
0)
     | Bool
otherwise                  =  Int
a Int -> Int -> (Int, Int)
`quotRemInt` Int
b
    {-# INLINE divMod #-} 
    Int
a divMod :: Int -> Int -> (Int, Int)
`divMod` Int
b
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0                     = (Int, Int)
forall a. a
divZeroError
       
     | Int
b Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== (-Int
1) Bool -> Bool -> Bool
&& Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
forall a. Bounded a => a
minBound = (Int
forall a. a
overflowError, Int
0)
     | Bool
otherwise                  =  Int
a Int -> Int -> (Int, Int)
`divModInt` Int
b
instance Real Word where
    toRational :: Word -> Rational
toRational Word
x = Word -> Integer
forall a. Integral a => a -> Integer
toInteger Word
x Integer -> Integer -> Rational
forall a. Integral a => a -> a -> Ratio a
% Integer
1
instance Integral Word where
    
    {-# INLINE quot    #-}
    {-# INLINE rem     #-}
    {-# INLINE quotRem #-}
    {-# INLINE div     #-}
    {-# INLINE mod     #-}
    {-# INLINE divMod  #-}
    quot :: Word -> Word -> Word
quot    (W# Word#
x#) y :: Word
y@(W# Word#
y#)
        | Word
y Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
0                = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`quotWord#` Word#
y#)
        | Bool
otherwise             = Word
forall a. a
divZeroError
    rem :: Word -> Word -> Word
rem     (W# Word#
x#) y :: Word
y@(W# Word#
y#)
        | Word
y Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
0                = Word# -> Word
W# (Word#
x# Word# -> Word# -> Word#
`remWord#` Word#
y#)
        | Bool
otherwise             = Word
forall a. a
divZeroError
    quotRem :: Word -> Word -> (Word, Word)
quotRem (W# Word#
x#) y :: Word
y@(W# Word#
y#)
        | Word
y Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
0                = case Word#
x# Word# -> Word# -> (# Word#, Word# #)
`quotRemWord#` Word#
y# of
                                  (# Word#
q, Word#
r #) ->
                                      (Word# -> Word
W# Word#
q, Word# -> Word
W# Word#
r)
        | Bool
otherwise             = (Word, Word)
forall a. a
divZeroError
    div :: Word -> Word -> Word
div    Word
x Word
y = Word -> Word -> Word
forall a. Integral a => a -> a -> a
quot Word
x Word
y
    mod :: Word -> Word -> Word
mod    Word
x Word
y = Word -> Word -> Word
forall a. Integral a => a -> a -> a
rem Word
x Word
y
    divMod :: Word -> Word -> (Word, Word)
divMod Word
x Word
y = Word -> Word -> (Word, Word)
forall a. Integral a => a -> a -> (a, a)
quotRem Word
x Word
y
    toInteger :: Word -> Integer
toInteger (W# Word#
x#)           = Word# -> Integer
integerFromWord# Word#
x#
instance  Real Integer  where
    toRational :: Integer -> Rational
toRational Integer
x        =  Integer
x Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1
instance Real Natural where
    toRational :: Natural -> Rational
toRational Natural
n = Natural -> Integer
integerFromNatural Natural
n Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1
instance Integral Integer where
    
    {-# INLINE quot    #-}
    {-# INLINE rem     #-}
    {-# INLINE quotRem #-}
    {-# INLINE div     #-}
    {-# INLINE mod     #-}
    {-# INLINE divMod  #-}
    toInteger :: Integer -> Integer
toInteger Integer
n      = Integer
n
    !Integer
_ quot :: Integer -> Integer -> Integer
`quot` Integer
0 = Integer
forall a. a
divZeroError
    Integer
n  `quot` Integer
d = Integer
n Integer -> Integer -> Integer
`integerQuot` Integer
d
    !Integer
_ rem :: Integer -> Integer -> Integer
`rem` Integer
0 = Integer
forall a. a
divZeroError
    Integer
n  `rem` Integer
d = Integer
n Integer -> Integer -> Integer
`integerRem` Integer
d
    !Integer
_ div :: Integer -> Integer -> Integer
`div` Integer
0 = Integer
forall a. a
divZeroError
    Integer
n  `div` Integer
d = Integer
n Integer -> Integer -> Integer
`integerDiv` Integer
d
    !Integer
_ mod :: Integer -> Integer -> Integer
`mod` Integer
0 = Integer
forall a. a
divZeroError
    Integer
n  `mod` Integer
d = Integer
n Integer -> Integer -> Integer
`integerMod` Integer
d
    !Integer
_ divMod :: Integer -> Integer -> (Integer, Integer)
`divMod` Integer
0 = (Integer, Integer)
forall a. a
divZeroError
    Integer
n  `divMod` Integer
d = Integer
n Integer -> Integer -> (Integer, Integer)
`integerDivMod` Integer
d
    !Integer
_ quotRem :: Integer -> Integer -> (Integer, Integer)
`quotRem` Integer
0 = (Integer, Integer)
forall a. a
divZeroError
    Integer
n  `quotRem` Integer
d = Integer
n Integer -> Integer -> (Integer, Integer)
`integerQuotRem` Integer
d
instance Integral Natural where
    
    {-# INLINE quot    #-}
    {-# INLINE rem     #-}
    {-# INLINE quotRem #-}
    {-# INLINE div     #-}
    {-# INLINE mod     #-}
    {-# INLINE divMod  #-}
    toInteger :: Natural -> Integer
toInteger Natural
x = Natural -> Integer
integerFromNatural Natural
x
    !Natural
_ quot :: Natural -> Natural -> Natural
`quot` Natural
0 = Natural
forall a. a
divZeroError
    Natural
n  `quot` Natural
d = Natural
n Natural -> Natural -> Natural
`naturalQuot` Natural
d
    !Natural
_ rem :: Natural -> Natural -> Natural
`rem` Natural
0 = Natural
forall a. a
divZeroError
    Natural
n  `rem` Natural
d = Natural
n Natural -> Natural -> Natural
`naturalRem` Natural
d
    !Natural
_ quotRem :: Natural -> Natural -> (Natural, Natural)
`quotRem` Natural
0 = (Natural, Natural)
forall a. a
divZeroError
    Natural
n  `quotRem` Natural
d = Natural
n Natural -> Natural -> (Natural, Natural)
`naturalQuotRem` Natural
d
    div :: Natural -> Natural -> Natural
div    Natural
x Natural
y = Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
quot Natural
x Natural
y
    mod :: Natural -> Natural -> Natural
mod    Natural
x Natural
y = Natural -> Natural -> Natural
forall a. Integral a => a -> a -> a
rem Natural
x Natural
y
    divMod :: Natural -> Natural -> (Natural, Natural)
divMod Natural
x Natural
y = Natural -> Natural -> (Natural, Natural)
forall a. Integral a => a -> a -> (a, a)
quotRem Natural
x Natural
y
instance  (Integral a)  => Ord (Ratio a)  where
    {-# SPECIALIZE instance Ord Rational #-}
    (a
x:%a
y) <= :: Ratio a -> Ratio a -> Bool
<= (a
x':%a
y')  =  a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
y' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
x' a -> a -> a
forall a. Num a => a -> a -> a
* a
y
    (a
x:%a
y) < :: Ratio a -> Ratio a -> Bool
<  (a
x':%a
y')  =  a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
y' a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<  a
x' a -> a -> a
forall a. Num a => a -> a -> a
* a
y
instance  (Integral a)  => Num (Ratio a)  where
    {-# SPECIALIZE instance Num Rational #-}
    (a
x:%a
y) + :: Ratio a -> Ratio a -> Ratio a
+ (a
x':%a
y')   =  a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
reduce (a
xa -> a -> a
forall a. Num a => a -> a -> a
*a
y' a -> a -> a
forall a. Num a => a -> a -> a
+ a
x'a -> a -> a
forall a. Num a => a -> a -> a
*a
y) (a
ya -> a -> a
forall a. Num a => a -> a -> a
*a
y')
    (a
x:%a
y) - :: Ratio a -> Ratio a -> Ratio a
- (a
x':%a
y')   =  a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
reduce (a
xa -> a -> a
forall a. Num a => a -> a -> a
*a
y' a -> a -> a
forall a. Num a => a -> a -> a
- a
x'a -> a -> a
forall a. Num a => a -> a -> a
*a
y) (a
ya -> a -> a
forall a. Num a => a -> a -> a
*a
y')
    (a
x:%a
y) * :: Ratio a -> Ratio a -> Ratio a
* (a
x':%a
y')   =  a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
reduce (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x') (a
y a -> a -> a
forall a. Num a => a -> a -> a
* a
y')
    negate :: Ratio a -> Ratio a
negate (a
x:%a
y)       =  (-a
x) a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% a
y
    abs :: Ratio a -> Ratio a
abs (a
x:%a
y)          =  a -> a
forall a. Num a => a -> a
abs a
x a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% a
y
    signum :: Ratio a -> Ratio a
signum (a
x:%a
_)       =  a -> a
forall a. Num a => a -> a
signum a
x a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% a
1
    fromInteger :: Integer -> Ratio a
fromInteger Integer
x       =  Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% a
1
{-# RULES "fromRational/id" fromRational = id :: Rational -> Rational #-}
instance  (Integral a)  => Fractional (Ratio a)  where
    {-# SPECIALIZE instance Fractional Rational #-}
    (a
x:%a
y) / :: Ratio a -> Ratio a -> Ratio a
/ (a
x':%a
y')   =  (a
xa -> a -> a
forall a. Num a => a -> a -> a
*a
y') a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
% (a
ya -> a -> a
forall a. Num a => a -> a -> a
*a
x')
    recip :: Ratio a -> Ratio a
recip (a
0:%a
_)        = Ratio a
forall a. a
ratioZeroDenominatorError
    recip (a
x:%a
y)
        | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0         = a -> a
forall a. Num a => a -> a
negate a
y a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% a -> a
forall a. Num a => a -> a
negate a
x
        | Bool
otherwise     = a
y a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% a
x
    fromRational :: Rational -> Ratio a
fromRational (Integer
x:%Integer
y) =  Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
% Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
y
instance  (Integral a)  => Real (Ratio a)  where
    {-# SPECIALIZE instance Real Rational #-}
    toRational :: Ratio a -> Rational
toRational (a
x:%a
y)   =  a -> Integer
forall a. Integral a => a -> Integer
toInteger a
x Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% a -> Integer
forall a. Integral a => a -> Integer
toInteger a
y
instance  (Integral a)  => RealFrac (Ratio a)  where
    {-# SPECIALIZE instance RealFrac Rational #-}
    properFraction :: forall b. Integral b => Ratio a -> (b, Ratio a)
properFraction (a
x:%a
y) = (Integer -> b
forall a. Num a => Integer -> a
fromInteger (a -> Integer
forall a. Integral a => a -> Integer
toInteger a
q), a
ra -> a -> Ratio a
forall a. a -> a -> Ratio a
:%a
y)
                          where (a
q,a
r) = a -> a -> (a, a)
forall a. Integral a => a -> a -> (a, a)
quotRem a
x a
y
    round :: forall b. Integral b => Ratio a -> b
round Ratio a
r =
      let
        (b
n, Ratio a
f) = Ratio a -> (b, Ratio a)
forall b. Integral b => Ratio a -> (b, Ratio a)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction Ratio a
r
        x :: b
x = if Ratio a
r Ratio a -> Ratio a -> Bool
forall a. Ord a => a -> a -> Bool
< Ratio a
0 then -b
1 else b
1
      in
        case (Ratio a -> Ratio a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Ratio a -> Ratio a
forall a. Num a => a -> a
abs Ratio a
f) Ratio a
0.5, b -> Bool
forall a. Integral a => a -> Bool
odd b
n) of
          (Ordering
LT, Bool
_) -> b
n
          (Ordering
EQ, Bool
False) -> b
n
          (Ordering
EQ, Bool
True) -> b
n b -> b -> b
forall a. Num a => a -> a -> a
+ b
x
          (Ordering
GT, Bool
_) -> b
n b -> b -> b
forall a. Num a => a -> a -> a
+ b
x
instance  (Show a)  => Show (Ratio a)  where
    {-# SPECIALIZE instance Show Rational #-}
    showsPrec :: Int -> Ratio a -> ShowS
showsPrec Int
p (a
x:%a
y)  =  Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
ratioPrec) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
                           Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
ratioPrec1 a
x ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                           [Char] -> ShowS
showString [Char]
" % " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                           
                           
                           
                           
                           Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
ratioPrec1 a
y
instance  (Integral a)  => Enum (Ratio a)  where
    {-# SPECIALIZE instance Enum Rational #-}
    succ :: Ratio a -> Ratio a
succ Ratio a
x              =  Ratio a
x Ratio a -> Ratio a -> Ratio a
forall a. Num a => a -> a -> a
+ Ratio a
1
    pred :: Ratio a -> Ratio a
pred Ratio a
x              =  Ratio a
x Ratio a -> Ratio a -> Ratio a
forall a. Num a => a -> a -> a
- Ratio a
1
    toEnum :: Int -> Ratio a
toEnum Int
n            =  Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n a -> a -> Ratio a
forall a. a -> a -> Ratio a
:% a
1
    fromEnum :: Ratio a -> Int
fromEnum            =  Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> (Ratio a -> Integer) -> Ratio a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ratio a -> Integer
forall b. Integral b => Ratio a -> b
forall a b. (RealFrac a, Integral b) => a -> b
truncate
    enumFrom :: Ratio a -> [Ratio a]
enumFrom            =  Ratio a -> [Ratio a]
forall a. Fractional a => a -> [a]
numericEnumFrom
    enumFromThen :: Ratio a -> Ratio a -> [Ratio a]
enumFromThen        =  Ratio a -> Ratio a -> [Ratio a]
forall a. Fractional a => a -> a -> [a]
numericEnumFromThen
    enumFromTo :: Ratio a -> Ratio a -> [Ratio a]
enumFromTo          =  Ratio a -> Ratio a -> [Ratio a]
forall a. (Ord a, Fractional a) => a -> a -> [a]
numericEnumFromTo
    enumFromThenTo :: Ratio a -> Ratio a -> Ratio a -> [Ratio a]
enumFromThenTo      =  Ratio a -> Ratio a -> Ratio a -> [Ratio a]
forall a. (Ord a, Fractional a) => a -> a -> a -> [a]
numericEnumFromThenTo
{-# INLINE fromIntegral #-}
  
  
  
fromIntegral :: (Integral a, Num b) => a -> b
fromIntegral :: forall a b. (Integral a, Num b) => a -> b
fromIntegral = Integer -> b
forall a. Num a => Integer -> a
fromInteger (Integer -> b) -> (a -> Integer) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Integer
forall a. Integral a => a -> Integer
toInteger
realToFrac :: (Real a, Fractional b) => a -> b
{-# NOINLINE [1] realToFrac #-}
realToFrac :: forall a b. (Real a, Fractional b) => a -> b
realToFrac = Rational -> b
forall a. Fractional a => Rational -> a
fromRational (Rational -> b) -> (a -> Rational) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rational
forall a. Real a => a -> Rational
toRational
showSigned :: (Real a)
  => (a -> ShowS)       
  -> Int                
  -> a                  
  -> ShowS
showSigned :: forall a. Real a => (a -> ShowS) -> Int -> a -> ShowS
showSigned a -> ShowS
showPos Int
p a
x
   | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0     = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
6) (Char -> ShowS
showChar Char
'-' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ShowS
showPos (-a
x))
   | Bool
otherwise = a -> ShowS
showPos a
x
even, odd       :: (Integral a) => a -> Bool
even :: forall a. Integral a => a -> Bool
even a
n          =  a
n a -> a -> a
forall a. Integral a => a -> a -> a
`rem` a
2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0
odd :: forall a. Integral a => a -> Bool
odd             =  Bool -> Bool
not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Bool
forall a. Integral a => a -> Bool
even
{-# INLINABLE even #-}
{-# INLINABLE odd  #-}
{-# INLINE [1] (^) #-}    
(^) :: (Num a, Integral b) => a -> b -> a
a
x0 ^ :: forall a b. (Num a, Integral b) => a -> b -> a
^ b
y0 | b
y0 b -> b -> Bool
forall a. Ord a => a -> a -> Bool
< b
0    = [Char] -> a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"Negative exponent"
        | b
y0 b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
0   = a
1
        | Bool
otherwise = a -> b -> a
forall a b. (Num a, Integral b) => a -> b -> a
powImpl a
x0 b
y0
{-# SPECIALISE powImpl ::
        Integer -> Integer -> Integer,
        Integer -> Int -> Integer,
        Int -> Int -> Int #-}
{-# INLINABLE powImpl #-}    
powImpl :: (Num a, Integral b) => a -> b -> a
powImpl :: forall a b. (Num a, Integral b) => a -> b -> a
powImpl a
x b
y | b -> Bool
forall a. Integral a => a -> Bool
even b
y    = a -> b -> a
forall a b. (Num a, Integral b) => a -> b -> a
powImpl (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x) (b
y b -> b -> b
forall a. Integral a => a -> a -> a
`quot` b
2)
            | b
y b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
1    = a
x
            | Bool
otherwise = a -> b -> a -> a
forall a b. (Num a, Integral b) => a -> b -> a -> a
powImplAcc (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x) (b
y b -> b -> b
forall a. Integral a => a -> a -> a
`quot` b
2) a
x 
{-# SPECIALISE powImplAcc ::
        Integer -> Integer -> Integer -> Integer,
        Integer -> Int -> Integer -> Integer,
        Int -> Int -> Int -> Int #-}
{-# INLINABLE powImplAcc #-}    
powImplAcc :: (Num a, Integral b) => a -> b -> a -> a
powImplAcc :: forall a b. (Num a, Integral b) => a -> b -> a -> a
powImplAcc a
x b
y a
z | b -> Bool
forall a. Integral a => a -> Bool
even b
y    = a -> b -> a -> a
forall a b. (Num a, Integral b) => a -> b -> a -> a
powImplAcc (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x) (b
y b -> b -> b
forall a. Integral a => a -> a -> a
`quot` b
2) a
z
                 | b
y b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
1    = a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
z
                 | Bool
otherwise = a -> b -> a -> a
forall a b. (Num a, Integral b) => a -> b -> a -> a
powImplAcc (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x) (b
y b -> b -> b
forall a. Integral a => a -> a -> a
`quot` b
2) (a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
z) 
(^^)            :: (Fractional a, Integral b) => a -> b -> a
{-# INLINE [1] (^^) #-}         
a
x ^^ :: forall a b. (Fractional a, Integral b) => a -> b -> a
^^ b
n          =  if b
n b -> b -> Bool
forall a. Ord a => a -> a -> Bool
>= b
0 then a
xa -> b -> a
forall a b. (Num a, Integral b) => a -> b -> a
^b
n else a -> a
forall a. Fractional a => a -> a
recip (a
xa -> b -> a
forall a b. (Num a, Integral b) => a -> b -> a
^(b -> b
forall a. Num a => a -> a
negate b
n))
{-# RULES
"^2/Int"        forall x. x ^ (2 :: Int) = x*x
"^3/Int"        forall x. x ^ (3 :: Int) = x*x*x
"^4/Int"        forall x. x ^ (4 :: Int) = let u = x*x in u*u
"^5/Int"        forall x. x ^ (5 :: Int) = let u = x*x in u*u*x
"^2/Integer"    forall x. x ^ (2 :: Integer) = x*x
"^3/Integer"    forall x. x ^ (3 :: Integer) = x*x*x
"^4/Integer"    forall x. x ^ (4 :: Integer) = let u = x*x in u*u
"^5/Integer"    forall x. x ^ (5 :: Integer) = let u = x*x in u*u*x
  #-}
{-# RULES "(^)/Rational"    (^) = (^%^) #-}
(^%^)           :: Integral a => Rational -> a -> Rational
(Integer
n :% Integer
d) ^%^ :: forall a. Integral a => Rational -> a -> Rational
^%^ a
e
    | a
e a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0     = [Char] -> Rational
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"Negative exponent"
    | a
e a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0    = Integer
1 Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1
    | Bool
otherwise = (Integer
n Integer -> a -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ a
e) Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% (Integer
d Integer -> a -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ a
e)
{-# RULES "(^^)/Rational"   (^^) = (^^%^^) #-}
(^^%^^)         :: Integral a => Rational -> a -> Rational
(Integer
n :% Integer
d) ^^%^^ :: forall a. Integral a => Rational -> a -> Rational
^^%^^ a
e
    | a
e a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0     = (Integer
n Integer -> a -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ a
e) Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% (Integer
d Integer -> a -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ a
e)
    | a
e a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0    = Integer
1 Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1
    | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0     = (Integer
d Integer -> a -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (a -> a
forall a. Num a => a -> a
negate a
e)) Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% (Integer
n Integer -> a -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (a -> a
forall a. Num a => a -> a
negate a
e))
    | Integer
n Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0    = Rational
forall a. a
ratioZeroDenominatorError
    | Bool
otherwise = let nn :: Integer
nn = Integer
d Integer -> a -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (a -> a
forall a. Num a => a -> a
negate a
e)
                      dd :: Integer
dd = (Integer -> Integer
forall a. Num a => a -> a
negate Integer
n) Integer -> a -> Integer
forall a b. (Num a, Integral b) => a -> b -> a
^ (a -> a
forall a. Num a => a -> a
negate a
e)
                  in if a -> Bool
forall a. Integral a => a -> Bool
even a
e then (Integer
nn Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
dd) else (Integer -> Integer
forall a. Num a => a -> a
negate Integer
nn Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
dd)
gcd             :: (Integral a) => a -> a -> a
{-# SPECIALISE gcd :: Int -> Int -> Int #-}
{-# SPECIALISE gcd :: Word -> Word -> Word #-}
{-# NOINLINE [2] gcd #-} 
gcd :: forall a. Integral a => a -> a -> a
gcd a
x a
y         =  a -> a -> a
forall a. Integral a => a -> a -> a
gcd' (a -> a
forall a. Num a => a -> a
abs a
x) (a -> a
forall a. Num a => a -> a
abs a
y)
                   where gcd' :: t -> t -> t
gcd' t
a t
0  =  t
a
                         gcd' t
a t
b  =  t -> t -> t
gcd' t
b (t
a t -> t -> t
forall a. Integral a => a -> a -> a
`rem` t
b)
lcm             :: (Integral a) => a -> a -> a
{-# SPECIALISE lcm :: Int -> Int -> Int #-}
{-# SPECIALISE lcm :: Word -> Word -> Word #-}
{-# NOINLINE [2] lcm #-} 
lcm :: forall a. Integral a => a -> a -> a
lcm a
_ a
0         =  a
0
lcm a
0 a
_         =  a
0
lcm a
x a
y         =  a -> a
forall a. Num a => a -> a
abs ((a
x a -> a -> a
forall a. Integral a => a -> a -> a
`quot` (a -> a -> a
forall a. Integral a => a -> a -> a
gcd a
x a
y)) a -> a -> a
forall a. Num a => a -> a -> a
* a
y)
{-# RULES
"gcd/Integer->Integer->Integer" gcd = integerGcd
"lcm/Integer->Integer->Integer" lcm = integerLcm
"gcd/Natural->Natural->Natural" gcd = naturalGcd
"lcm/Natural->Natural->Natural" lcm = naturalLcm
 #-}
{-# RULES
"gcd/Int->Int->Int"             gcd = gcdInt
"gcd/Word->Word->Word"          gcd = gcdWord
 #-}
{-# INLINE integralEnumFrom #-}
integralEnumFrom :: (Integral a, Bounded a) => a -> [a]
integralEnumFrom :: forall a. (Integral a, Bounded a) => a -> [a]
integralEnumFrom a
n = (Integer -> a) -> [Integer] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> a
forall a. Num a => Integer -> a
fromInteger [a -> Integer
forall a. Integral a => a -> Integer
toInteger a
n .. a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
maxBound a -> a -> a
forall a. a -> a -> a
`asTypeOf` a
n)]
{-# INLINE integralEnumFromThen #-}
integralEnumFromThen :: (Integral a, Bounded a) => a -> a -> [a]
integralEnumFromThen :: forall a. (Integral a, Bounded a) => a -> a -> [a]
integralEnumFromThen a
n1 a
n2
  | Integer
i_n2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
>= Integer
i_n1  = (Integer -> a) -> [Integer] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> a
forall a. Num a => Integer -> a
fromInteger [Integer
i_n1, Integer
i_n2 .. a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
maxBound a -> a -> a
forall a. a -> a -> a
`asTypeOf` a
n1)]
  | Bool
otherwise     = (Integer -> a) -> [Integer] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> a
forall a. Num a => Integer -> a
fromInteger [Integer
i_n1, Integer
i_n2 .. a -> Integer
forall a. Integral a => a -> Integer
toInteger (a
forall a. Bounded a => a
minBound a -> a -> a
forall a. a -> a -> a
`asTypeOf` a
n1)]
  where
    i_n1 :: Integer
i_n1 = a -> Integer
forall a. Integral a => a -> Integer
toInteger a
n1
    i_n2 :: Integer
i_n2 = a -> Integer
forall a. Integral a => a -> Integer
toInteger a
n2
{-# INLINE integralEnumFromTo #-}
integralEnumFromTo :: Integral a => a -> a -> [a]
integralEnumFromTo :: forall a. Integral a => a -> a -> [a]
integralEnumFromTo a
n a
m = (Integer -> a) -> [Integer] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> a
forall a. Num a => Integer -> a
fromInteger [a -> Integer
forall a. Integral a => a -> Integer
toInteger a
n .. a -> Integer
forall a. Integral a => a -> Integer
toInteger a
m]
{-# INLINE integralEnumFromThenTo #-}
integralEnumFromThenTo :: Integral a => a -> a -> a -> [a]
integralEnumFromThenTo :: forall a. Integral a => a -> a -> a -> [a]
integralEnumFromThenTo a
n1 a
n2 a
m
  = (Integer -> a) -> [Integer] -> [a]
forall a b. (a -> b) -> [a] -> [b]
map Integer -> a
forall a. Num a => Integer -> a
fromInteger [a -> Integer
forall a. Integral a => a -> Integer
toInteger a
n1, a -> Integer
forall a. Integral a => a -> Integer
toInteger a
n2 .. a -> Integer
forall a. Integral a => a -> Integer
toInteger a
m]
data FractionalExponentBase
  = Base2
  | Base10
  deriving (Int -> FractionalExponentBase -> ShowS
[FractionalExponentBase] -> ShowS
FractionalExponentBase -> [Char]
(Int -> FractionalExponentBase -> ShowS)
-> (FractionalExponentBase -> [Char])
-> ([FractionalExponentBase] -> ShowS)
-> Show FractionalExponentBase
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FractionalExponentBase -> ShowS
showsPrec :: Int -> FractionalExponentBase -> ShowS
$cshow :: FractionalExponentBase -> [Char]
show :: FractionalExponentBase -> [Char]
$cshowList :: [FractionalExponentBase] -> ShowS
showList :: [FractionalExponentBase] -> ShowS
Show)
mkRationalBase2 :: Rational -> Integer -> Rational
mkRationalBase2 :: Rational -> Integer -> Rational
mkRationalBase2 Rational
r Integer
e = Rational -> Integer -> FractionalExponentBase -> Rational
mkRationalWithExponentBase Rational
r Integer
e FractionalExponentBase
Base2
mkRationalBase10 :: Rational -> Integer -> Rational
mkRationalBase10 :: Rational -> Integer -> Rational
mkRationalBase10 Rational
r Integer
e = Rational -> Integer -> FractionalExponentBase -> Rational
mkRationalWithExponentBase Rational
r Integer
e FractionalExponentBase
Base10
mkRationalWithExponentBase :: Rational -> Integer
                           -> FractionalExponentBase -> Rational
mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational
mkRationalWithExponentBase Rational
r Integer
e FractionalExponentBase
feb = Rational
r Rational -> Rational -> Rational
forall a. Num a => a -> a -> a
* (Rational
eb Rational -> Integer -> Rational
forall a b. (Fractional a, Integral b) => a -> b -> a
^^ Integer
e)
  
  where eb :: Rational
eb = case FractionalExponentBase
feb of FractionalExponentBase
Base2 -> Rational
2 ; FractionalExponentBase
Base10 -> Rational
10