Movatterモバイル変換
[0]ホーム
{-# LANGUAGE Trustworthy #-}{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples, BangPatterns #-}{-# OPTIONS_GHC -Wno-orphans #-}{-# OPTIONS_HADDOCK not-home #-}------------------------------------------------------------------------------- |-- Module : GHC.Real-- 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)---- The types 'Ratio' and 'Rational', and the classes 'Real', 'Fractional',-- 'Integral', and 'RealFrac'.-------------------------------------------------------------------------------moduleGHC.Realwhere#include "MachDeps.h"importGHC.BaseimportGHC.NumimportGHC.ListimportGHC.EnumimportGHC.Showimport{-# SOURCE#-}GHC.Exception(divZeroException,overflowException,underflowException,ratioZeroDenomException)importGHC.Num.BigNat(gcdInt,gcdWord)infixr8^,^^infixl7/,`quot`,`rem`,`div`,`mod`infixl7%default()-- Double isn't available yet,-- and we shouldn't be using defaults anyway{- Note [Allow time for type-specialisation rules to fire]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~Consider lcm = ... {-# RULES "lcm/Integer->Integer->Integer" lcm = integerLcm #-}We want to delay inlining `lcm` until the rule (which is a form of manualtype specialisation) has had a chance to fire. It can fire in InitialPhase,so INLINE[2] seems sufficient. c.f. #20709-}-------------------------------------------------------------------------- Divide by zero and arithmetic overflow-------------------------------------------------------------------------- We put them here because they are needed relatively early-- in the libraries before the Exception type has been defined yet.{-# NOINLINEdivZeroError#-}divZeroError::adivZeroError :: forall a. adivZeroError=SomeException -> aforall a b. a -> braise#SomeExceptiondivZeroException{-# NOINLINEratioZeroDenominatorError#-}ratioZeroDenominatorError::aratioZeroDenominatorError :: forall a. aratioZeroDenominatorError=SomeException -> aforall a b. a -> braise#SomeExceptionratioZeroDenomException{-# NOINLINEoverflowError#-}overflowError::aoverflowError :: forall a. aoverflowError=SomeException -> aforall a b. a -> braise#SomeExceptionoverflowException{-# NOINLINEunderflowError#-}underflowError::aunderflowError :: forall a. aunderflowError=SomeException -> aforall a b. a -> braise#SomeExceptionunderflowException---------------------------------------------------------------- The Ratio and Rational types---------------------------------------------------------------- | Rational numbers, with numerator and denominator of some 'Integral' type.---- Note that `Ratio`'s instances inherit the deficiencies from the type-- parameter's. For example, @Ratio Natural@'s 'Num' instance has similar-- problems to `Numeric.Natural.Natural`'s.dataRatioa=!a:%!aderivingRatio 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 -> Boolforall 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 -> BoolEq-- ^ @since 2.01-- | Arbitrary-precision rational numbers, represented as a ratio of-- two 'Integer' values. A rational number may be constructed using-- the '%' operator.typeRational=RatioIntegerratioPrec,ratioPrec1::IntratioPrec :: IntratioPrec=Int7-- Precedence of ':%' constructorratioPrec1 :: IntratioPrec1=IntratioPrecInt -> Int -> Intforall a. Num a => a -> a -> a+Int1infinity,notANumber::Rationalinfinity :: Rationalinfinity=Integer1Integer -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integer0notANumber :: RationalnotANumber=Integer0Integer -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integer0-- Use :%, not % for Inf/NaN; the latter would-- immediately lead to a runtime error, because it normalises.-- | Forms the ratio of two integral numbers.{-# SPECIALISE(%)::Integer->Integer->Rational#-}(%)::(Integrala)=>a->a->Ratioa-- | Extract the numerator of the ratio in reduced form:-- the numerator and denominator have no common factor and the denominator-- is positive.numerator::Ratioa->a-- | Extract the denominator of the ratio in reduced form:-- the numerator and denominator have no common factor and the denominator-- is positive.denominator::Ratioa->a-- | 'reduce' is a subsidiary function used only in this module.-- It normalises a ratio by dividing both numerator and denominator by-- their greatest common divisor.reduce::(Integrala)=>a->a->Ratioa{-# SPECIALISEreduce::Integer->Integer->Rational#-}reduce :: forall a. Integral a => a -> a -> Ratio areducea_a0=Ratio aforall a. aratioZeroDenominatorErrorreduceaxay=(axa -> a -> aforall a. Integral a => a -> a -> a`quot`ad)a -> a -> Ratio aforall a. a -> a -> Ratio a:%(aya -> a -> aforall a. Integral a => a -> a -> a`quot`ad)whered :: ad=a -> a -> aforall a. Integral a => a -> a -> agcdaxayax% :: forall a. Integral a => a -> a -> Ratio a%ay=a -> a -> Ratio aforall a. Integral a => a -> a -> Ratio areduce(axa -> a -> aforall a. Num a => a -> a -> a*a -> aforall a. Num a => a -> asignumay)(a -> aforall a. Num a => a -> aabsay)numerator :: forall a. Ratio a -> anumerator(ax:%a_)=axdenominator :: forall a. Ratio a -> adenominator(a_:%ay)=ay---------------------------------------------------------------- Standard numeric classes---------------------------------------------------------------- | Real numbers.---- The Haskell report defines no laws for 'Real', however 'Real' instances-- are customarily expected to adhere to the following law:---- [__Coherence with 'fromRational'__]: if the type also implements 'Fractional',-- then 'fromRational' is a left inverse for 'toRational', i.e. @fromRational (toRational i) = i@---- The law does not hold for 'Float', 'Double', 'Foreign.C.Types.CFloat',-- 'Foreign.C.Types.CDouble', etc., because these types contain non-finite values,-- which cannot be roundtripped through 'Rational'.class(Numa,Orda)=>Realawhere-- | the rational equivalent of its real argument with full precisiontoRational::a->Rational-- | Integral numbers, supporting integer division.---- The Haskell Report defines no laws for 'Integral'. However, 'Integral'-- instances are customarily expected to define a Euclidean domain and have the-- following properties for the 'div'\/'mod' and 'quot'\/'rem' pairs, given-- suitable Euclidean functions @f@ and @g@:---- * @x@ = @y * quot x y + rem x y@ with @rem x y@ = @fromInteger 0@ or-- @g (rem x y)@ < @g y@-- * @x@ = @y * div x y + mod x y@ with @mod x y@ = @fromInteger 0@ or-- @f (mod x y)@ < @f y@---- An example of a suitable Euclidean function, for 'Integer'\'s instance, is-- 'abs'.---- In addition, 'toInteger` should be total, and 'fromInteger' should be a left-- inverse for it, i.e. @fromInteger (toInteger i) = i@.class(Reala,Enuma)=>Integralawhere-- | integer division truncated toward zero---- WARNING: This function is partial (because it throws when 0 is passed as-- the divisor) for all the integer types in @base@.quot::a->a->a-- | integer remainder, satisfying---- > (x `quot` y)*y + (x `rem` y) == x---- WARNING: This function is partial (because it throws when 0 is passed as-- the divisor) for all the integer types in @base@.rem::a->a->a-- | integer division truncated toward negative infinity---- WARNING: This function is partial (because it throws when 0 is passed as-- the divisor) for all the integer types in @base@.div::a->a->a-- | integer modulus, satisfying---- > (x `div` y)*y + (x `mod` y) == x---- WARNING: This function is partial (because it throws when 0 is passed as-- the divisor) for all the integer types in @base@.mod::a->a->a-- | simultaneous 'quot' and 'rem'---- WARNING: This function is partial (because it throws when 0 is passed as-- the divisor) for all the integer types in @base@.quotRem::a->a->(a,a)-- | simultaneous 'div' and 'mod'---- WARNING: This function is partial (because it throws when 0 is passed as-- the divisor) for all the integer types in @base@.divMod::a->a->(a,a)-- | conversion to 'Integer'toInteger::a->Integer{-# INLINEquot#-}{-# INLINErem#-}{-# INLINEdiv#-}{-# INLINEmod#-}an`quot`ad=aqwhere(aq,a_)=a -> a -> (a, a)forall a. Integral a => a -> a -> (a, a)quotRemanadan`rem`ad=arwhere(a_,ar)=a -> a -> (a, a)forall a. Integral a => a -> a -> (a, a)quotRemanadan`div`ad=aqwhere(aq,a_)=a -> a -> (a, a)forall a. Integral a => a -> a -> (a, a)divModanadan`mod`ad=arwhere(a_,ar)=a -> a -> (a, a)forall a. Integral a => a -> a -> (a, a)divModanaddivModanad=ifa -> aforall a. Num a => a -> asignumara -> a -> Boolforall a. Eq a => a -> a -> Bool==a -> aforall a. Num a => a -> anegate(a -> aforall a. Num a => a -> asignumad)then(aqa -> a -> aforall a. Num a => a -> a -> a-a1,ara -> a -> aforall a. Num a => a -> a -> a+ad)else(a, a)qrwhereqr :: (a, a)qr@(aq,ar)=a -> a -> (a, a)forall a. Integral a => a -> a -> (a, a)quotRemanad-- | Fractional numbers, supporting real division.---- The Haskell Report defines no laws for 'Fractional'. However, @('+')@ and-- @('*')@ are customarily expected to define a division ring and have the-- following properties:---- [__'recip' gives the multiplicative inverse__]:-- @x * recip x@ = @recip x * x@ = @fromInteger 1@-- [__Totality of 'toRational'__]: 'toRational' is total-- [__Coherence with 'toRational'__]: if the type also implements 'Real',-- then 'fromRational' is a left inverse for 'toRational', i.e. @fromRational (toRational i) = i@---- Note that it /isn't/ customarily expected that a type instance of-- 'Fractional' implement a field. However, all instances in @base@ do.class(Numa)=>Fractionalawhere{-# MINIMALfromRational,(recip|(/))#-}-- | 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{-# INLINErecip#-}{-# INLINE(/)#-}recipax=a1a -> a -> aforall a. Fractional a => a -> a -> a/axax/ay=axa -> a -> aforall a. Num a => a -> a -> a*a -> aforall a. Fractional a => a -> arecipay-- | Extracting components of fractions.class(Reala,Fractionala)=>RealFracawhere-- | 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::(Integralb)=>a->(b,a)-- | @'truncate' x@ returns the integer nearest @x@ between zero and @x@truncate::(Integralb)=>a->b-- | @'round' x@ returns the nearest integer to @x@;-- the even integer if @x@ is equidistant between two integersround::(Integralb)=>a->b-- | @'ceiling' x@ returns the least integer not less than @x@ceiling::(Integralb)=>a->b-- | @'floor' x@ returns the greatest integer not greater than @x@floor::(Integralb)=>a->b{-# INLINEtruncate#-}truncateax=bmwhere(bm,a_)=a -> (b, a)forall b. Integral b => a -> (b, a)forall a b. (RealFrac a, Integral b) => a -> (b, a)properFractionaxroundax=let(bn,ar)=a -> (b, a)forall b. Integral b => a -> (b, a)forall a b. (RealFrac a, Integral b) => a -> (b, a)properFractionaxm :: bm=ifara -> a -> Boolforall a. Ord a => a -> a -> Bool<a0thenbnb -> b -> bforall a. Num a => a -> a -> a-b1elsebnb -> b -> bforall a. Num a => a -> a -> a+b1incasea -> aforall a. Num a => a -> asignum(a -> aforall a. Num a => a -> aabsara -> a -> aforall a. Num a => a -> a -> a-a0.5)of-1->bna0->ifb -> Boolforall a. Integral a => a -> Boolevenbnthenbnelsebma1->bma_->[Char] -> bforall a. [Char] -> aerrorWithoutStackTrace[Char]"round default defn: Bad value"ceilingax=ifara -> a -> Boolforall a. Ord a => a -> a -> Bool>a0thenbnb -> b -> bforall a. Num a => a -> a -> a+b1elsebnwhere(bn,ar)=a -> (b, a)forall b. Integral b => a -> (b, a)forall a b. (RealFrac a, Integral b) => a -> (b, a)properFractionaxfloorax=ifara -> a -> Boolforall a. Ord a => a -> a -> Bool<a0thenbnb -> b -> bforall a. Num a => a -> a -> a-b1elsebnwhere(bn,ar)=a -> (b, a)forall b. Integral b => a -> (b, a)forall a b. (RealFrac a, Integral b) => a -> (b, a)properFractionax-- These 'numeric' enumerations come straight from the ReportnumericEnumFrom::(Fractionala)=>a->[a]{-# INLINEnumericEnumFrom#-}-- See Note [Inline Enum method helpers] in GHC.EnumnumericEnumFrom :: forall a. Fractional a => a -> [a]numericEnumFroman=a -> [a]goa0where-- See Note [Numeric Stability of Enumerating Floating Numbers]go :: a -> [a]go!ak=let!n' :: an'=ana -> a -> aforall a. Num a => a -> a -> a+akinan'a -> [a] -> [a]forall a. a -> [a] -> [a]:a -> [a]go(aka -> a -> aforall a. Num a => a -> a -> a+a1)numericEnumFromThen::(Fractionala)=>a->a->[a]{-# INLINEnumericEnumFromThen#-}-- See Note [Inline Enum method helpers] in GHC.EnumnumericEnumFromThen :: forall a. Fractional a => a -> a -> [a]numericEnumFromThenanam=a -> [a]goa0wherestep :: astep=ama -> a -> aforall a. Num a => a -> a -> a-an-- See Note [Numeric Stability of Enumerating Floating Numbers]go :: a -> [a]go!ak=let!n' :: an'=ana -> a -> aforall a. Num a => a -> a -> a+aka -> a -> aforall a. Num a => a -> a -> a*astepinan'a -> [a] -> [a]forall a. a -> [a] -> [a]:a -> [a]go(aka -> a -> aforall a. Num a => a -> a -> a+a1)numericEnumFromTo::(Orda,Fractionala)=>a->a->[a]{-# INLINEnumericEnumFromTo#-}-- See Note [Inline Enum method helpers] in GHC.EnumnumericEnumFromTo :: forall a. (Ord a, Fractional a) => a -> a -> [a]numericEnumFromToanam=(a -> Bool) -> [a] -> [a]forall a. (a -> Bool) -> [a] -> [a]takeWhile(a -> a -> Boolforall a. Ord a => a -> a -> Bool<=ama -> a -> aforall a. Num a => a -> a -> a+a1a -> a -> aforall a. Fractional a => a -> a -> a/a2)(a -> [a]forall a. Fractional a => a -> [a]numericEnumFroman)numericEnumFromThenTo::(Orda,Fractionala)=>a->a->a->[a]{-# INLINEnumericEnumFromThenTo#-}-- See Note [Inline Enum method helpers] in GHC.EnumnumericEnumFromThenTo :: forall a. (Ord a, Fractional a) => a -> a -> a -> [a]numericEnumFromThenToae1ae2ae3=(a -> Bool) -> [a] -> [a]forall a. (a -> Bool) -> [a] -> [a]takeWhilea -> Boolpredicate(a -> a -> [a]forall a. Fractional a => a -> a -> [a]numericEnumFromThenae1ae2)wheremid :: amid=(ae2a -> a -> aforall a. Num a => a -> a -> a-ae1)a -> a -> aforall a. Fractional a => a -> a -> a/a2predicate :: a -> Boolpredicate|ae2a -> a -> Boolforall a. Ord a => a -> a -> Bool>=ae1=(a -> a -> Boolforall a. Ord a => a -> a -> Bool<=ae3a -> a -> aforall a. Num a => a -> a -> a+amid)|Boolotherwise=(a -> a -> Boolforall a. Ord a => a -> a -> Bool>=ae3a -> a -> aforall a. Num a => a -> a -> a+amid){- Note [Numeric Stability of Enumerating Floating Numbers]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~When enumerate floating numbers, we could add the increment to the last numberat every run (as what we did previously): numericEnumFrom n = n `seq` (n : numericEnumFrom (n + 1))This approach is concise and really fast, only needs an addition operation.However when a floating number is large enough, for `n`, `n` and `n+1` willhave the same binary representation. For example (all number has type`Double`): 9007199254740990 is: 0x433ffffffffffffe 9007199254740990 + 1 is: 0x433fffffffffffff (9007199254740990 + 1) + 1 is: 0x4340000000000000 ((9007199254740990 + 1) + 1) + 1 is: 0x4340000000000000When we evaluate ([9007199254740990..9007199254740991] :: Double), we wouldnever reach the condition in `numericEnumFromTo` 9007199254740990 + 1 + 1 + ... > 9007199254740991 + 1/2We would fall into infinite loop (as reported in #15081).To remedy the situation, we record the number of `1` that needed to be addedto the start number, rather than increasing `1` at every time. This approachcan improvement the numeric stability greatly at the cost of a multiplication.Furthermore, we use the type of the enumerated number, `Fractional a => a`,as the type of multiplier. In rare situations, the multiplier could be verylarge and will lead to the enumeration to infinite loop, too, which shouldbe very rare. Consider the following example: [1..9007199254740994]We could fix that by using an Integer as multiplier but we don't do that.The benchmark on T7954.hs shows that this approach leads to significantdegeneration on performance (33% increase allocation and 300% increase onelapsed time).See #15081 and Phab:D4650 for the related discussion about this problem.-}---------------------------------------------------------------- Instances for Int---------------------------------------------------------------- | @since 2.0.1instanceRealIntwheretoRational :: Int -> RationaltoRationalIntx=Int -> Integerforall a. Integral a => a -> IntegertoIntegerIntxInteger -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integer1-- | @since 2.0.1instanceIntegralIntwheretoInteger :: Int -> IntegertoInteger(I#Int#i)=Int# -> IntegerISInt#i{-# INLINEquot#-}-- see Note [INLINE division wrappers] in GHC.BaseIntaquot :: Int -> Int -> Int`quot`Intb|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=Intforall a. adivZeroError|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==(-Int1)Bool -> Bool -> Bool&&IntaInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Intforall a. Bounded a => aminBound=Intforall a. aoverflowError-- Note [Order of tests]-- in GHC.Int|Boolotherwise=IntaInt -> Int -> Int`quotInt`Intb{-# INLINErem#-}-- see Note [INLINE division wrappers] in GHC.Base!Intarem :: Int -> Int -> Int`rem`Intb-- See Note [Special case of mod and rem is lazy]|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=Intforall a. adivZeroError|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==(-Int1)=Int0|Boolotherwise=IntaInt -> Int -> Int`remInt`Intb{-# INLINEdiv#-}-- see Note [INLINE division wrappers] in GHC.BaseIntadiv :: Int -> Int -> Int`div`Intb|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=Intforall a. adivZeroError|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==(-Int1)Bool -> Bool -> Bool&&IntaInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Intforall a. Bounded a => aminBound=Intforall a. aoverflowError-- Note [Order of tests]-- in GHC.Int|Boolotherwise=IntaInt -> Int -> Int`divInt`Intb{-# INLINEmod#-}-- see Note [INLINE division wrappers] in GHC.Base!Intamod :: Int -> Int -> Int`mod`Intb-- See Note [Special case of mod and rem is lazy]|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=Intforall a. adivZeroError|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==(-Int1)=Int0|Boolotherwise=IntaInt -> Int -> Int`modInt`Intb{-# INLINEquotRem#-}-- see Note [INLINE division wrappers] in GHC.BaseIntaquotRem :: Int -> Int -> (Int, Int)`quotRem`Intb|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=(Int, Int)forall a. adivZeroError-- Note [Order of tests] in GHC.Int|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==(-Int1)Bool -> Bool -> Bool&&IntaInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Intforall a. Bounded a => aminBound=(Intforall a. aoverflowError,Int0)|Boolotherwise=IntaInt -> Int -> (Int, Int)`quotRemInt`Intb{-# INLINEdivMod#-}-- see Note [INLINE division wrappers] in GHC.BaseIntadivMod :: Int -> Int -> (Int, Int)`divMod`Intb|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Int0=(Int, Int)forall a. adivZeroError-- Note [Order of tests] in GHC.Int|IntbInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==(-Int1)Bool -> Bool -> Bool&&IntaInt -> Int -> Boolforall a. Eq a => a -> a -> Bool==Intforall a. Bounded a => aminBound=(Intforall a. aoverflowError,Int0)|Boolotherwise=IntaInt -> Int -> (Int, Int)`divModInt`Intb{- Note [Special case of mod and rem is lazy]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~The `quotRem`/`divMod` CPU instruction fails for minBound `quotRem` -1, butminBound `rem` -1 is well-defined (0). We therefore special-case for `b == -1`,but not for `a == minBound` because of Note [Order of tests] in GHC.Int. Butnow we have to make sure the function stays strict in a, to guarantee unboxing.Hence the bang on a, see #18187.-}---------------------------------------------------------------- Instances for @Word@---------------------------------------------------------------- | @since 2.01instanceRealWordwheretoRational :: Word -> RationaltoRationalWordx=Word -> Integerforall a. Integral a => a -> IntegertoIntegerWordxInteger -> Integer -> Rationalforall a. Integral a => a -> a -> Ratio a%Integer1-- | @since 2.01instanceIntegralWordwhere-- see Note [INLINE division wrappers] in GHC.Base{-# INLINEquot#-}{-# INLINErem#-}{-# INLINEquotRem#-}{-# INLINEdiv#-}{-# INLINEmod#-}{-# INLINEdivMod#-}quot :: Word -> Word -> Wordquot(W#Word#x#)y :: Wordy@(W#Word#y#)|WordyWord -> Word -> Boolforall a. Eq a => a -> a -> Bool/=Word0=Word# -> WordW#(Word#x#Word# -> Word# -> Word#`quotWord#`Word#y#)|Boolotherwise=Wordforall a. adivZeroErrorrem :: Word -> Word -> Wordrem(W#Word#x#)y :: Wordy@(W#Word#y#)|WordyWord -> Word -> Boolforall a. Eq a => a -> a -> Bool/=Word0=Word# -> WordW#(Word#x#Word# -> Word# -> Word#`remWord#`Word#y#)|Boolotherwise=Wordforall a. adivZeroErrorquotRem :: Word -> Word -> (Word, Word)quotRem(W#Word#x#)y :: Wordy@(W#Word#y#)|WordyWord -> Word -> Boolforall a. Eq a => a -> a -> Bool/=Word0=caseWord#x#Word# -> Word# -> (# Word#, Word# #)`quotRemWord#`Word#y#of(#Word#q,Word#r#)->(Word# -> WordW#Word#q,Word# -> WordW#Word#r)|Boolotherwise=(Word, Word)forall a. adivZeroErrordiv :: Word -> Word -> WorddivWordxWordy=Word -> Word -> Wordforall a. Integral a => a -> a -> aquotWordxWordymod :: Word -> Word -> WordmodWordxWordy=Word -> Word -> Wordforall a. Integral a => a -> a -> aremWordxWordydivMod :: Word -> Word -> (Word, Word)divModWordxWordy=Word -> Word -> (Word, Word)forall a. Integral a => a -> a -> (a, a)quotRemWordxWordytoInteger :: Word -> IntegertoInteger(W#Word#x#)=Word# -> IntegerintegerFromWord#Word#x#---------------------------------------------------------------- Instances for Integer---------------------------------------------------------------- | @since 2.0.1instanceRealIntegerwheretoRational :: Integer -> RationaltoRationalIntegerx=IntegerxInteger -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integer1-- | @since 4.8.0.0instanceRealNaturalwheretoRational :: Natural -> RationaltoRationalNaturaln=Natural -> IntegerintegerFromNaturalNaturalnInteger -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integer1-- Note [Integer division constant folding]-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~---- Constant folding of quot, rem, div, mod, divMod and quotRem for Integer-- arguments depends crucially on inlining. Constant folding rules defined in-- GHC.Core.Opt.ConstantFold trigger for integerQuot, integerRem and so on.-- So if calls to quot, rem and so on were not inlined the rules would not fire.---- The rules would also not fire if calls to integerQuot and so on were inlined,-- but this does not happen because they are all marked with NOINLINE pragma.-- | @since 2.0.1instanceIntegralIntegerwhere-- see Note [INLINE division wrappers] in GHC.Base{-# INLINEquot#-}{-# INLINErem#-}{-# INLINEquotRem#-}{-# INLINEdiv#-}{-# INLINEmod#-}{-# INLINEdivMod#-}toInteger :: Integer -> IntegertoIntegerIntegern=Integern!Integer_quot :: Integer -> Integer -> Integer`quot`Integer0=Integerforall a. adivZeroErrorIntegern`quot`Integerd=IntegernInteger -> Integer -> Integer`integerQuot`Integerd!Integer_rem :: Integer -> Integer -> Integer`rem`Integer0=Integerforall a. adivZeroErrorIntegern`rem`Integerd=IntegernInteger -> Integer -> Integer`integerRem`Integerd!Integer_div :: Integer -> Integer -> Integer`div`Integer0=Integerforall a. adivZeroErrorIntegern`div`Integerd=IntegernInteger -> Integer -> Integer`integerDiv`Integerd!Integer_mod :: Integer -> Integer -> Integer`mod`Integer0=Integerforall a. adivZeroErrorIntegern`mod`Integerd=IntegernInteger -> Integer -> Integer`integerMod`Integerd!Integer_divMod :: Integer -> Integer -> (Integer, Integer)`divMod`Integer0=(Integer, Integer)forall a. adivZeroErrorIntegern`divMod`Integerd=IntegernInteger -> Integer -> (Integer, Integer)`integerDivMod`Integerd!Integer_quotRem :: Integer -> Integer -> (Integer, Integer)`quotRem`Integer0=(Integer, Integer)forall a. adivZeroErrorIntegern`quotRem`Integerd=IntegernInteger -> Integer -> (Integer, Integer)`integerQuotRem`Integerd-- | @since 4.8.0.0instanceIntegralNaturalwhere-- see Note [INLINE division wrappers] in GHC.Base{-# INLINEquot#-}{-# INLINErem#-}{-# INLINEquotRem#-}{-# INLINEdiv#-}{-# INLINEmod#-}{-# INLINEdivMod#-}toInteger :: Natural -> IntegertoIntegerNaturalx=Natural -> IntegerintegerFromNaturalNaturalx!Natural_quot :: Natural -> Natural -> Natural`quot`Natural0=Naturalforall a. adivZeroErrorNaturaln`quot`Naturald=NaturalnNatural -> Natural -> Natural`naturalQuot`Naturald!Natural_rem :: Natural -> Natural -> Natural`rem`Natural0=Naturalforall a. adivZeroErrorNaturaln`rem`Naturald=NaturalnNatural -> Natural -> Natural`naturalRem`Naturald!Natural_quotRem :: Natural -> Natural -> (Natural, Natural)`quotRem`Natural0=(Natural, Natural)forall a. adivZeroErrorNaturaln`quotRem`Naturald=NaturalnNatural -> Natural -> (Natural, Natural)`naturalQuotRem`Naturalddiv :: Natural -> Natural -> NaturaldivNaturalxNaturaly=Natural -> Natural -> Naturalforall a. Integral a => a -> a -> aquotNaturalxNaturalymod :: Natural -> Natural -> NaturalmodNaturalxNaturaly=Natural -> Natural -> Naturalforall a. Integral a => a -> a -> aremNaturalxNaturalydivMod :: Natural -> Natural -> (Natural, Natural)divModNaturalxNaturaly=Natural -> Natural -> (Natural, Natural)forall a. Integral a => a -> a -> (a, a)quotRemNaturalxNaturaly---------------------------------------------------------------- Instances for @Ratio@---------------------------------------------------------------- | @since 2.0.1instance(Integrala)=>Ord(Ratioa)where{-# SPECIALIZEinstanceOrdRational#-}(ax:%ay)<= :: Ratio a -> Ratio a -> Bool<=(ax':%ay')=axa -> a -> aforall a. Num a => a -> a -> a*ay'a -> a -> Boolforall a. Ord a => a -> a -> Bool<=ax'a -> a -> aforall a. Num a => a -> a -> a*ay(ax:%ay)< :: Ratio a -> Ratio a -> Bool<(ax':%ay')=axa -> a -> aforall a. Num a => a -> a -> a*ay'a -> a -> Boolforall a. Ord a => a -> a -> Bool<ax'a -> a -> aforall a. Num a => a -> a -> a*ay-- | @since 2.0.1instance(Integrala)=>Num(Ratioa)where{-# SPECIALIZEinstanceNumRational#-}(ax:%ay)+ :: Ratio a -> Ratio a -> Ratio a+(ax':%ay')=a -> a -> Ratio aforall a. Integral a => a -> a -> Ratio areduce(axa -> a -> aforall a. Num a => a -> a -> a*ay'a -> a -> aforall a. Num a => a -> a -> a+ax'a -> a -> aforall a. Num a => a -> a -> a*ay)(aya -> a -> aforall a. Num a => a -> a -> a*ay')(ax:%ay)- :: Ratio a -> Ratio a -> Ratio a-(ax':%ay')=a -> a -> Ratio aforall a. Integral a => a -> a -> Ratio areduce(axa -> a -> aforall a. Num a => a -> a -> a*ay'a -> a -> aforall a. Num a => a -> a -> a-ax'a -> a -> aforall a. Num a => a -> a -> a*ay)(aya -> a -> aforall a. Num a => a -> a -> a*ay')(ax:%ay)* :: Ratio a -> Ratio a -> Ratio a*(ax':%ay')=a -> a -> Ratio aforall a. Integral a => a -> a -> Ratio areduce(axa -> a -> aforall a. Num a => a -> a -> a*ax')(aya -> a -> aforall a. Num a => a -> a -> a*ay')negate :: Ratio a -> Ratio anegate(ax:%ay)=(-ax)a -> a -> Ratio aforall a. a -> a -> Ratio a:%ayabs :: Ratio a -> Ratio aabs(ax:%ay)=a -> aforall a. Num a => a -> aabsaxa -> a -> Ratio aforall a. a -> a -> Ratio a:%aysignum :: Ratio a -> Ratio asignum(ax:%a_)=a -> aforall a. Num a => a -> asignumaxa -> a -> Ratio aforall a. a -> a -> Ratio a:%a1fromInteger :: Integer -> Ratio afromIntegerIntegerx=Integer -> aforall a. Num a => Integer -> afromIntegerIntegerxa -> a -> Ratio aforall a. a -> a -> Ratio a:%a1-- | @since 2.0.1{-# RULES"fromRational/id"fromRational=id::Rational->Rational#-}instance(Integrala)=>Fractional(Ratioa)where{-# SPECIALIZEinstanceFractionalRational#-}(ax:%ay)/ :: Ratio a -> Ratio a -> Ratio a/(ax':%ay')=(axa -> a -> aforall a. Num a => a -> a -> a*ay')a -> a -> Ratio aforall a. Integral a => a -> a -> Ratio a%(aya -> a -> aforall a. Num a => a -> a -> a*ax')recip :: Ratio a -> Ratio arecip(a0:%a_)=Ratio aforall a. aratioZeroDenominatorErrorrecip(ax:%ay)|axa -> a -> Boolforall a. Ord a => a -> a -> Bool<a0=a -> aforall a. Num a => a -> anegateaya -> a -> Ratio aforall a. a -> a -> Ratio a:%a -> aforall a. Num a => a -> anegateax|Boolotherwise=aya -> a -> Ratio aforall a. a -> a -> Ratio a:%axfromRational :: Rational -> Ratio afromRational(Integerx:%Integery)=Integer -> aforall a. Num a => Integer -> afromIntegerIntegerxa -> a -> Ratio aforall a. Integral a => a -> a -> Ratio a%Integer -> aforall a. Num a => Integer -> afromIntegerIntegery-- | @since 2.0.1instance(Integrala)=>Real(Ratioa)where{-# SPECIALIZEinstanceRealRational#-}toRational :: Ratio a -> RationaltoRational(ax:%ay)=a -> Integerforall a. Integral a => a -> IntegertoIntegeraxInteger -> Integer -> Rationalforall a. a -> a -> Ratio a:%a -> Integerforall a. Integral a => a -> IntegertoIntegeray-- | @since 2.0.1instance(Integrala)=>RealFrac(Ratioa)where{-# SPECIALIZEinstanceRealFracRational#-}properFraction :: forall b. Integral b => Ratio a -> (b, Ratio a)properFraction(ax:%ay)=(Integer -> bforall a. Num a => Integer -> afromInteger(a -> Integerforall a. Integral a => a -> IntegertoIntegeraq),ara -> a -> Ratio aforall a. a -> a -> Ratio a:%ay)where(aq,ar)=a -> a -> (a, a)forall a. Integral a => a -> a -> (a, a)quotRemaxayround :: forall b. Integral b => Ratio a -> broundRatio ar=let(bn,Ratio af)=Ratio a -> (b, Ratio a)forall b. Integral b => Ratio a -> (b, Ratio a)forall a b. (RealFrac a, Integral b) => a -> (b, a)properFractionRatio arx :: bx=ifRatio arRatio a -> Ratio a -> Boolforall a. Ord a => a -> a -> Bool<Ratio a0then-b1elseb1incase(Ratio a -> Ratio a -> Orderingforall a. Ord a => a -> a -> Orderingcompare(Ratio a -> Ratio aforall a. Num a => a -> aabsRatio af)Ratio a0.5,b -> Boolforall a. Integral a => a -> Booloddbn)of(OrderingLT,Bool_)->bn(OrderingEQ,BoolFalse)->bn(OrderingEQ,BoolTrue)->bnb -> b -> bforall a. Num a => a -> a -> a+bx(OrderingGT,Bool_)->bnb -> b -> bforall a. Num a => a -> a -> a+bx-- | @since 2.0.1instance(Showa)=>Show(Ratioa)where{-# SPECIALIZEinstanceShowRational#-}showsPrec :: Int -> Ratio a -> ShowSshowsPrecIntp(ax:%ay)=Bool -> ShowS -> ShowSshowParen(IntpInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>IntratioPrec)(ShowS -> ShowS) -> ShowS -> ShowSforall a b. (a -> b) -> a -> b$Int -> a -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntratioPrec1axShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.[Char] -> ShowSshowString[Char]" % "ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.-- H98 report has spaces round the %-- but we removed them [May 04]-- and added them again for consistency with-- Haskell 98 [Sep 08, #1920]Int -> a -> ShowSforall a. Show a => Int -> a -> ShowSshowsPrecIntratioPrec1ay-- | @since 2.0.1instance(Integrala)=>Enum(Ratioa)where{-# SPECIALIZEinstanceEnumRational#-}succ :: Ratio a -> Ratio asuccRatio ax=Ratio axRatio a -> Ratio a -> Ratio aforall a. Num a => a -> a -> a+Ratio a1pred :: Ratio a -> Ratio apredRatio ax=Ratio axRatio a -> Ratio a -> Ratio aforall a. Num a => a -> a -> a-Ratio a1toEnum :: Int -> Ratio atoEnumIntn=Int -> aforall a b. (Integral a, Num b) => a -> bfromIntegralIntna -> a -> Ratio aforall a. a -> a -> Ratio a:%a1fromEnum :: Ratio a -> IntfromEnum=Integer -> Intforall a. Num a => Integer -> afromInteger(Integer -> Int) -> (Ratio a -> Integer) -> Ratio a -> Intforall b c a. (b -> c) -> (a -> b) -> a -> c.Ratio a -> Integerforall b. Integral b => Ratio a -> bforall a b. (RealFrac a, Integral b) => a -> btruncateenumFrom :: Ratio a -> [Ratio a]enumFrom=Ratio a -> [Ratio a]forall a. Fractional a => a -> [a]numericEnumFromenumFromThen :: Ratio a -> Ratio a -> [Ratio a]enumFromThen=Ratio a -> Ratio a -> [Ratio a]forall a. Fractional a => a -> a -> [a]numericEnumFromThenenumFromTo :: Ratio a -> Ratio a -> [Ratio a]enumFromTo=Ratio a -> Ratio a -> [Ratio a]forall a. (Ord a, Fractional a) => a -> a -> [a]numericEnumFromToenumFromThenTo :: 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---------------------------------------------------------------- Coercions---------------------------------------------------------------- | General coercion from 'Integral' types.---- WARNING: This function performs silent truncation if the result type is not-- at least as big as the argument's type.{-# INLINEfromIntegral#-}-- Inlined to allow built-in rules to match.-- See Note [Optimising conversions between numeric types]-- in GHC.Core.Opt.ConstantFoldfromIntegral::(Integrala,Numb)=>a->bfromIntegral :: forall a b. (Integral a, Num b) => a -> bfromIntegral=Integer -> bforall a. Num a => Integer -> afromInteger(Integer -> b) -> (a -> Integer) -> a -> bforall b c a. (b -> c) -> (a -> b) -> a -> c.a -> Integerforall a. Integral a => a -> IntegertoInteger-- | General coercion to 'Fractional' types.---- WARNING: This function goes through the 'Rational' type, which does not have values for 'NaN' for example.-- This means it does not round-trip.---- For 'Double' it also behaves differently with or without -O0:---- > Prelude> realToFrac nan -- With -O0-- > -Infinity-- > Prelude> realToFrac nan-- > NaNrealToFrac::(Reala,Fractionalb)=>a->b{-# NOINLINE[1]realToFrac#-}-- See Note [Allow time for type-specialisation rules to fire]-- These rule actually appear in other modules, e.g. GHC.FloatrealToFrac :: forall a b. (Real a, Fractional b) => a -> brealToFrac=Rational -> bforall a. Fractional a => Rational -> afromRational(Rational -> b) -> (a -> Rational) -> a -> bforall b c a. (b -> c) -> (a -> b) -> a -> c.a -> Rationalforall a. Real a => a -> RationaltoRational---------------------------------------------------------------- Overloaded numeric functions---------------------------------------------------------------- | Converts a possibly-negative 'Real' value to a string.showSigned::(Reala)=>(a->ShowS)-- ^ a function that can show unsigned values->Int-- ^ the precedence of the enclosing context->a-- ^ the value to show->ShowSshowSigned :: forall a. Real a => (a -> ShowS) -> Int -> a -> ShowSshowSigneda -> ShowSshowPosIntpax|axa -> a -> Boolforall a. Ord a => a -> a -> Bool<a0=Bool -> ShowS -> ShowSshowParen(IntpInt -> Int -> Boolforall a. Ord a => a -> a -> Bool>Int6)(Char -> ShowSshowCharChar'-'ShowS -> ShowS -> ShowSforall b c a. (b -> c) -> (a -> b) -> a -> c.a -> ShowSshowPos(-ax))|Boolotherwise=a -> ShowSshowPosaxeven,odd::(Integrala)=>a->Booleven :: forall a. Integral a => a -> Boolevenan=ana -> a -> aforall a. Integral a => a -> a -> a`rem`a2a -> a -> Boolforall a. Eq a => a -> a -> Bool==a0odd :: forall a. Integral a => a -> Boolodd=Bool -> Boolnot(Bool -> Bool) -> (a -> Bool) -> a -> Boolforall b c a. (b -> c) -> (a -> b) -> a -> c.a -> Boolforall a. Integral a => a -> Booleven{-# INLINABLEeven#-}{-# INLINABLEodd#-}--------------------------------------------------------- | raise a number to a non-negative integral power{-# INLINE[1](^)#-}-- See Note [Inlining (^)](^)::(Numa,Integralb)=>a->b->aax0^ :: forall a b. (Num a, Integral b) => a -> b -> a^by0|by0b -> b -> Boolforall a. Ord a => a -> a -> Bool<b0=[Char] -> aforall a. [Char] -> aerrorWithoutStackTrace[Char]"Negative exponent"|by0b -> b -> Boolforall a. Eq a => a -> a -> Bool==b0=a1|Boolotherwise=a -> b -> aforall a b. (Num a, Integral b) => a -> b -> apowImplax0by0{-# SPECIALISEpowImpl::Integer->Integer->Integer,Integer->Int->Integer,Int->Int->Int#-}{-# INLINABLEpowImpl#-}-- See Note [Inlining (^)]powImpl::(Numa,Integralb)=>a->b->a-- powImpl : x0 ^ y0 = (x ^ y)powImpl :: forall a b. (Num a, Integral b) => a -> b -> apowImplaxby|b -> Boolforall a. Integral a => a -> Boolevenby=a -> b -> aforall a b. (Num a, Integral b) => a -> b -> apowImpl(axa -> a -> aforall a. Num a => a -> a -> a*ax)(byb -> b -> bforall a. Integral a => a -> a -> a`quot`b2)|byb -> b -> Boolforall a. Eq a => a -> a -> Bool==b1=ax|Boolotherwise=a -> b -> a -> aforall a b. (Num a, Integral b) => a -> b -> a -> apowImplAcc(axa -> a -> aforall a. Num a => a -> a -> a*ax)(byb -> b -> bforall a. Integral a => a -> a -> a`quot`b2)ax-- See Note [Half of y - 1]{-# SPECIALISEpowImplAcc::Integer->Integer->Integer->Integer,Integer->Int->Integer->Integer,Int->Int->Int->Int#-}{-# INLINABLEpowImplAcc#-}-- See Note [Inlining (^)]powImplAcc::(Numa,Integralb)=>a->b->a->a-- powImplAcc : x0 ^ y0 = (x ^ y) * zpowImplAcc :: forall a b. (Num a, Integral b) => a -> b -> a -> apowImplAccaxbyaz|b -> Boolforall a. Integral a => a -> Boolevenby=a -> b -> a -> aforall a b. (Num a, Integral b) => a -> b -> a -> apowImplAcc(axa -> a -> aforall a. Num a => a -> a -> a*ax)(byb -> b -> bforall a. Integral a => a -> a -> a`quot`b2)az|byb -> b -> Boolforall a. Eq a => a -> a -> Bool==b1=axa -> a -> aforall a. Num a => a -> a -> a*az|Boolotherwise=a -> b -> a -> aforall a b. (Num a, Integral b) => a -> b -> a -> apowImplAcc(axa -> a -> aforall a. Num a => a -> a -> a*ax)(byb -> b -> bforall a. Integral a => a -> a -> a`quot`b2)(axa -> a -> aforall a. Num a => a -> a -> a*az)-- See Note [Half of y - 1]-- | raise a number to an integral power(^^)::(Fractionala,Integralb)=>a->b->a{-# INLINE[1](^^)#-}-- See Note [Inlining (^)ax^^ :: forall a b. (Fractional a, Integral b) => a -> b -> a^^bn=ifbnb -> b -> Boolforall a. Ord a => a -> a -> Bool>=b0thenaxa -> b -> aforall a b. (Num a, Integral b) => a -> b -> a^bnelsea -> aforall a. Fractional a => a -> arecip(axa -> b -> aforall a b. (Num a, Integral b) => a -> b -> a^(b -> bforall a. Num a => a -> anegatebn)){- Note [Half of y - 1]~~~~~~~~~~~~~~~~~~~~~~~~Since y is guaranteed to be odd and positive here,half of y - 1 can be computed as y `quot` 2, optimising subtraction away.Note [Inlining (^)]~~~~~~~~~~~~~~~~~~~We want to achieve the following:* Noting that (^) is lazy in its first argument, we'd still like to avoid allocating a box for the first argument. Example: nofib/imaginary/x2n1, which makes many calls to (^) with different first arguments each time. Solution: split (^) into a small INLINE wrapper that tests the second arg, which then calls the strict (and recursive) auxiliary function `powImpl`.* Don't inline (^) too early because we want rewrite rules to optimise calls to (^) with small exponents. See Note [Powers with small exponent]. Solution: use INLINE[1] to delay inlining to phase 1, giving the rewrite rules time to fire.* (^) is overloaded on two different type parameters. We want to specialise. Solution: make `powImpl` (and its friend `powImplAcc`) INLINEABLE, so they can be specialised at call sites. Also give them some common specialisations right here, to avoid duplicating that specialisation in clients.Specialisation can make a huge difference for repeated calls, because ofconstants which would otherwise be calculated repeatedly and unboxing ofarguments.Why not make (^) strict in `x0` with a bang and make it INLINABLE? Well, becauseit is futile: Being strict in the `Complex Double` pair won't be enough to unboxthe `Double`s anyway. Even after deep specisalisation, we will only unbox the`Double`s when we inline (^), because (^) remains lazy in the `Double` fields.Given that (^) must always inline to yield good code, we can just as well markit as such.A small note on perf: Currently the fromInteger calls from the desugaring ofliterals are not floated because we get \d1 d2 x y -> blahafter the gentle round of simplification.Note [Powers with small exponent]~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~For small exponents, (^) is inefficient compared to manuallyexpanding the multiplication tree (see #5237).Here, rules for the most common exponent types are given.The range of exponents for which rules are given is quitearbitrary and kept small to not unduly increase the number of rules.0 and 1 are excluded based on the assumption that nobody wouldwrite x^0 or x^1 in code and the cases where an exponent couldbe statically resolved to 0 or 1 are rare.It might be desirable to have corresponding rules also forexponents of other types (e. g., Word), but it's doubtful theywould fire, since the exponents of other types tend to getfloated out before the rule has a chance to fire.Also desirable would be rules for (^^), but I haven't managedto get those to fire.Note: Since (*) is not associative for some types (e.g. Double), it isimportant that the RHS of these rules produce the same bracketing aswould the actual implementation of (^). A mismatch here led to #19569.-}-- See Note [Powers with small exponent]{-# RULES"^2/Int"forallx.x^(2::Int)=x*x"^3/Int"forallx.x^(3::Int)=x*x*x"^4/Int"forallx.x^(4::Int)=letu=x*xinu*u"^5/Int"forallx.x^(5::Int)=letu=x*xinu*u*x"^2/Integer"forallx.x^(2::Integer)=x*x"^3/Integer"forallx.x^(3::Integer)=x*x*x"^4/Integer"forallx.x^(4::Integer)=letu=x*xinu*u"^5/Integer"forallx.x^(5::Integer)=letu=x*xinu*u*x#-}--------------------------------------------------------- Special power functions for Rational---- see #4337---- Rationale:-- For a legitimate Rational (n :% d), the numerator and denominator are-- coprime, i.e. they have no common prime factor.-- Therefore all powers (n ^ a) and (d ^ b) are also coprime, so it is-- not necessary to compute the greatest common divisor, which would be-- done in the default implementation at each multiplication step.-- Since exponentiation quickly leads to very large numbers and-- calculation of gcds is generally very slow for large numbers,-- avoiding the gcd leads to an order of magnitude speedup relatively-- soon (and an asymptotic improvement overall).---- Note:-- We cannot use these functions for general Ratio a because that would-- change results in a multitude of cases.-- The cause is that if a and b are coprime, their remainders by any-- positive modulus generally aren't, so in the default implementation-- reduction occurs.---- Example:-- (17 % 3) ^ 3 :: Ratio Word8-- Default:-- (17 % 3) ^ 3 = ((17 % 3) ^ 2) * (17 % 3)-- = ((289 `mod` 256) % 9) * (17 % 3)-- = (33 % 9) * (17 % 3)-- = (11 % 3) * (17 % 3)-- = (187 % 9)-- But:-- ((17^3) `mod` 256) % (3^3) = (4913 `mod` 256) % 27-- = 49 % 27---- TODO:-- Find out whether special-casing for numerator, denominator or-- exponent = 1 (or -1, where that may apply) gains something.-- Special version of (^) for Rational base{-# RULES"(^)/Rational"(^)=(^%^)#-}(^%^)::Integrala=>Rational->a->Rational(Integern:%Integerd)^%^ :: forall a. Integral a => Rational -> a -> Rational^%^ae|aea -> a -> Boolforall a. Ord a => a -> a -> Bool<a0=[Char] -> Rationalforall a. [Char] -> aerrorWithoutStackTrace[Char]"Negative exponent"|aea -> a -> Boolforall a. Eq a => a -> a -> Bool==a0=Integer1Integer -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integer1|Boolotherwise=(IntegernInteger -> a -> Integerforall a b. (Num a, Integral b) => a -> b -> a^ae)Integer -> Integer -> Rationalforall a. a -> a -> Ratio a:%(IntegerdInteger -> a -> Integerforall a b. (Num a, Integral b) => a -> b -> a^ae)-- Special version of (^^) for Rational base{-# RULES"(^^)/Rational"(^^)=(^^%^^)#-}(^^%^^)::Integrala=>Rational->a->Rational(Integern:%Integerd)^^%^^ :: forall a. Integral a => Rational -> a -> Rational^^%^^ae|aea -> a -> Boolforall a. Ord a => a -> a -> Bool>a0=(IntegernInteger -> a -> Integerforall a b. (Num a, Integral b) => a -> b -> a^ae)Integer -> Integer -> Rationalforall a. a -> a -> Ratio a:%(IntegerdInteger -> a -> Integerforall a b. (Num a, Integral b) => a -> b -> a^ae)|aea -> a -> Boolforall a. Eq a => a -> a -> Bool==a0=Integer1Integer -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integer1|IntegernInteger -> Integer -> Boolforall a. Ord a => a -> a -> Bool>Integer0=(IntegerdInteger -> a -> Integerforall a b. (Num a, Integral b) => a -> b -> a^(a -> aforall a. Num a => a -> anegateae))Integer -> Integer -> Rationalforall a. a -> a -> Ratio a:%(IntegernInteger -> a -> Integerforall a b. (Num a, Integral b) => a -> b -> a^(a -> aforall a. Num a => a -> anegateae))|IntegernInteger -> Integer -> Boolforall a. Eq a => a -> a -> Bool==Integer0=Rationalforall a. aratioZeroDenominatorError|Boolotherwise=letnn :: Integernn=IntegerdInteger -> a -> Integerforall a b. (Num a, Integral b) => a -> b -> a^(a -> aforall a. Num a => a -> anegateae)dd :: Integerdd=(Integer -> Integerforall a. Num a => a -> anegateIntegern)Integer -> a -> Integerforall a b. (Num a, Integral b) => a -> b -> a^(a -> aforall a. Num a => a -> anegateae)inifa -> Boolforall a. Integral a => a -> Boolevenaethen(IntegernnInteger -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integerdd)else(Integer -> Integerforall a. Num a => a -> anegateIntegernnInteger -> Integer -> Rationalforall a. a -> a -> Ratio a:%Integerdd)--------------------------------------------------------- | @'gcd' x y@ is the non-negative factor of both @x@ and @y@ of which-- every common factor of @x@ and @y@ is also a factor; for example-- @'gcd' 4 2 = 2@, @'gcd' (-4) 6 = 2@, @'gcd' 0 4@ = @4@. @'gcd' 0 0@ = @0@.-- (That is, the common divisor that is \"greatest\" in the divisibility-- preordering.)---- Note: Since for signed fixed-width integer types, @'abs' 'minBound' < 0@,-- the result may be negative if one of the arguments is @'minBound'@ (and-- necessarily is if the other is @0@ or @'minBound'@) for such types.gcd::(Integrala)=>a->a->a{-# SPECIALISEgcd::Int->Int->Int#-}{-# SPECIALISEgcd::Word->Word->Word#-}{-# NOINLINE[2]gcd#-}-- See Note [Allow time for type-specialisation rules to fire]gcd :: forall a. Integral a => a -> a -> agcdaxay=a -> a -> aforall a. Integral a => a -> a -> agcd'(a -> aforall a. Num a => a -> aabsax)(a -> aforall a. Num a => a -> aabsay)wheregcd' :: t -> t -> tgcd'tat0=tagcd'tatb=t -> t -> tgcd'tb(tat -> t -> tforall a. Integral a => a -> a -> a`rem`tb)-- | @'lcm' x y@ is the smallest positive integer that both @x@ and @y@ divide.lcm::(Integrala)=>a->a->a{-# SPECIALISElcm::Int->Int->Int#-}{-# SPECIALISElcm::Word->Word->Word#-}{-# NOINLINE[2]lcm#-}-- See Note [Allow time for type-specialisation rules to fire]lcm :: forall a. Integral a => a -> a -> alcma_a0=a0lcma0a_=a0lcmaxay=a -> aforall a. Num a => a -> aabs((axa -> a -> aforall a. Integral a => a -> a -> a`quot`(a -> a -> aforall a. Integral a => a -> a -> agcdaxay))a -> a -> aforall a. Num a => a -> a -> a*ay){-# 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 pragma: see Note [Inline Enum method helpers] in GHC.Enum{-# INLINEintegralEnumFrom#-}integralEnumFrom::(Integrala,Boundeda)=>a->[a]integralEnumFrom :: forall a. (Integral a, Bounded a) => a -> [a]integralEnumFroman=(Integer -> a) -> [Integer] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInteger -> aforall a. Num a => Integer -> afromInteger[a -> Integerforall a. Integral a => a -> IntegertoIntegeran..a -> Integerforall a. Integral a => a -> IntegertoInteger(aforall a. Bounded a => amaxBounda -> a -> aforall a. a -> a -> a`asTypeOf`an)]-- INLINE pragma: see Note [Inline Enum method helpers] in GHC.Enum{-# INLINEintegralEnumFromThen#-}integralEnumFromThen::(Integrala,Boundeda)=>a->a->[a]integralEnumFromThen :: forall a. (Integral a, Bounded a) => a -> a -> [a]integralEnumFromThenan1an2|Integeri_n2Integer -> Integer -> Boolforall a. Ord a => a -> a -> Bool>=Integeri_n1=(Integer -> a) -> [Integer] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInteger -> aforall a. Num a => Integer -> afromInteger[Integeri_n1,Integeri_n2..a -> Integerforall a. Integral a => a -> IntegertoInteger(aforall a. Bounded a => amaxBounda -> a -> aforall a. a -> a -> a`asTypeOf`an1)]|Boolotherwise=(Integer -> a) -> [Integer] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInteger -> aforall a. Num a => Integer -> afromInteger[Integeri_n1,Integeri_n2..a -> Integerforall a. Integral a => a -> IntegertoInteger(aforall a. Bounded a => aminBounda -> a -> aforall a. a -> a -> a`asTypeOf`an1)]wherei_n1 :: Integeri_n1=a -> Integerforall a. Integral a => a -> IntegertoIntegeran1i_n2 :: Integeri_n2=a -> Integerforall a. Integral a => a -> IntegertoIntegeran2-- INLINE pragma: see Note [Inline Enum method helpers] in GHC.Enum{-# INLINEintegralEnumFromTo#-}integralEnumFromTo::Integrala=>a->a->[a]integralEnumFromTo :: forall a. Integral a => a -> a -> [a]integralEnumFromToanam=(Integer -> a) -> [Integer] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInteger -> aforall a. Num a => Integer -> afromInteger[a -> Integerforall a. Integral a => a -> IntegertoIntegeran..a -> Integerforall a. Integral a => a -> IntegertoIntegeram]-- INLINE pragma: see Note [Inline Enum method helpers] in GHC.Enum{-# INLINEintegralEnumFromThenTo#-}integralEnumFromThenTo::Integrala=>a->a->a->[a]integralEnumFromThenTo :: forall a. Integral a => a -> a -> a -> [a]integralEnumFromThenToan1an2am=(Integer -> a) -> [Integer] -> [a]forall a b. (a -> b) -> [a] -> [b]mapInteger -> aforall a. Num a => Integer -> afromInteger[a -> Integerforall a. Integral a => a -> IntegertoIntegeran1,a -> Integerforall a. Integral a => a -> IntegertoIntegeran2..a -> Integerforall a. Integral a => a -> IntegertoIntegeram]-- mkRational related codedataFractionalExponentBase=Base2|Base10deriving(Int -> FractionalExponentBase -> ShowS[FractionalExponentBase] -> ShowSFractionalExponentBase -> [Char](Int -> FractionalExponentBase -> ShowS)-> (FractionalExponentBase -> [Char])-> ([FractionalExponentBase] -> ShowS)-> Show FractionalExponentBaseforall a.(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a$cshowsPrec :: Int -> FractionalExponentBase -> ShowSshowsPrec :: Int -> FractionalExponentBase -> ShowS$cshow :: FractionalExponentBase -> [Char]show :: FractionalExponentBase -> [Char]$cshowList :: [FractionalExponentBase] -> ShowSshowList :: [FractionalExponentBase] -> ShowSShow)mkRationalBase2::Rational->Integer->RationalmkRationalBase2 :: Rational -> Integer -> RationalmkRationalBase2RationalrIntegere=Rational -> Integer -> FractionalExponentBase -> RationalmkRationalWithExponentBaseRationalrIntegereFractionalExponentBaseBase2mkRationalBase10::Rational->Integer->RationalmkRationalBase10 :: Rational -> Integer -> RationalmkRationalBase10RationalrIntegere=Rational -> Integer -> FractionalExponentBase -> RationalmkRationalWithExponentBaseRationalrIntegereFractionalExponentBaseBase10mkRationalWithExponentBase::Rational->Integer->FractionalExponentBase->RationalmkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> RationalmkRationalWithExponentBaseRationalrIntegereFractionalExponentBasefeb=RationalrRational -> Rational -> Rationalforall a. Num a => a -> a -> a*(RationalebRational -> Integer -> Rationalforall a b. (Fractional a, Integral b) => a -> b -> a^^Integere)-- See Note [fractional exponent bases] for why only these bases.whereeb :: Rationaleb=caseFractionalExponentBasefebofFractionalExponentBaseBase2->Rational2;FractionalExponentBaseBase10->Rational10
[8]ページ先頭