{-# LANGUAGE NoImplicitPrelude #-}{-# LANGUAGE BangPatterns #-}{-# LANGUAGE CPP #-}{-# LANGUAGE MagicHash #-}{-# LANGUAGE UnboxedTuples #-}------------------------------------------------------------------------------- |-- Module : GHC.Natural-- Copyright : (C) 2014 Herbert Valerio Riedel,-- (C) 2011 Edward Kmett-- License : see libraries/base/LICENSE---- Maintainer : libraries@haskell.org-- Stability : internal-- Portability : non-portable (GHC Extensions)---- The arbitrary-precision 'Natural' number type.---- __Note__: This is an internal GHC module with an API subject to-- change. It's recommended use the "Numeric.Natural" module to import-- the 'Natural' type.---- @since 4.8.0.0-----------------------------------------------------------------------------moduleGHC.Natural(-- * The 'Natural' number type---- | __Warning__: The internal implementation of 'Natural'-- (i.e. which constructors are available) depends on the-- 'Integer' backend used!Natural (..),mkNatural ,isValidNatural -- * Arithmetic,plusNatural ,minusNatural ,minusNaturalMaybe ,timesNatural ,negateNatural ,signumNatural ,quotRemNatural ,quotNatural ,remNatural ,gcdNatural ,lcmNatural -- * Bits,andNatural ,orNatural ,xorNatural ,bitNatural ,testBitNatural ,popCountNatural ,shiftLNatural ,shiftRNatural -- * Conversions,naturalToInteger ,naturalToWord ,naturalToInt ,naturalFromInteger ,wordToNatural ,intToNatural ,naturalToWordMaybe ,wordToNatural# ,wordToNaturalBase -- * Modular arithmetic,powModNatural )where #include "MachDeps.h" importGHC.ClassesimportGHC.Maybe importGHC.TypesimportGHC.Primimport{-# SOURCE#-}GHC.Exception.Type (underflowException ,divZeroException ) #if defined(MIN_VERSION_integer_gmp) importGHC.Integer.GMP.Internals #else importGHC.Integer #endif default()-- Most high-level operations need to be marked `NOINLINE` as-- otherwise GHC doesn't recognize them and fails to apply constant-- folding to `Natural`-typed expression.---- To this end, the CPP hack below allows to write the pseudo-pragma---- {-# CONSTANT_FOLDED plusNatural #-}---- which is simply expanded into a---- {-# NOINLINE plusNatural #-}------ TODO: Note that some functions have commented CONSTANT_FOLDED annotations,-- that's because the Integer counter-parts of these functions do actually have-- a builtinRule in PrelRules, where the Natural functions do not. The plan is-- to eventually also add builtin rules for those functions on Natural. #define CONSTANT_FOLDED NOINLINE --------------------------------------------------------------------------------- Arithmetic underflow--------------------------------------------------------------------------------- We put them here because they are needed relatively early-- in the libraries before the Exception type has been defined yet.{-# NOINLINEunderflowError #-}underflowError ::a underflowError :: a underflowError =SomeException -> a forall b a. b -> a raise#SomeException underflowException {-# NOINLINEdivZeroError #-}divZeroError ::a divZeroError :: a divZeroError =SomeException -> a forall b a. b -> a raise#SomeException divZeroException --------------------------------------------------------------------------------- Natural type------------------------------------------------------------------------------- #if defined(MIN_VERSION_integer_gmp) -- TODO: if saturated arithmetic is to used, replace 'underflowError' by '0'-- | Type representing arbitrary-precision non-negative integers.---- >>> 2^100 :: Natural-- 1267650600228229401496703205376---- Operations whose result would be negative @'Control.Exception.throw'-- ('Control.Exception.Underflow' :: 'Control.Exception.ArithException')@,---- >>> -1 :: Natural-- *** Exception: arithmetic underflow---- @since 4.8.0.0dataNatural =NatS# GmpLimb#-- ^ in @[0, maxBound::Word]@|NatJ# {-# UNPACK#-}!BigNat-- ^ in @]maxBound::Word, +inf[@---- __Invariant__: 'NatJ#' is used-- /iff/ value doesn't fit in-- 'NatS#' constructor.-- NB: Order of constructors *must*-- coincide with 'Ord' relationderiving(Eq-- ^ @since 4.8.0.0,Ord-- ^ @since 4.8.0.0)-- | Test whether all internal invariants are satisfied by 'Natural' value---- This operation is mostly useful for test-suites and/or code which-- constructs 'Integer' values directly.---- @since 4.8.0.0isValidNatural ::Natural ->BoolisValidNatural :: Natural -> Bool isValidNatural (NatS# GmpLimb# _)=Bool TrueisValidNatural (NatJ# BigNat bn )=Int# -> Bool isTrue#(BigNat -> Int# isValidBigNat#BigNat bn )-- A 1-limb BigNat could fit into a NatS#, so we-- require at least 2 limbs.Bool -> Bool -> Bool &&Int# -> Bool isTrue#(BigNat -> Int# sizeofBigNat#BigNat bn Int# -> Int# -> Int# >#Int# 1#)signumNatural ::Natural ->Natural signumNatural :: Natural -> Natural signumNatural (NatS# GmpLimb# 0##)=GmpLimb# -> Natural NatS# GmpLimb# 0##signumNatural Natural _=GmpLimb# -> Natural NatS# GmpLimb# 1##-- {-# CONSTANT_FOLDED signumNatural #-}negateNatural ::Natural ->Natural negateNatural :: Natural -> Natural negateNatural (NatS# GmpLimb# 0##)=GmpLimb# -> Natural NatS# GmpLimb# 0##negateNatural Natural _=Natural forall a. a underflowError -- {-# CONSTANT_FOLDED negateNatural #-}-- | @since 4.10.0.0naturalFromInteger ::Integer->Natural naturalFromInteger :: Integer -> Natural naturalFromInteger (S#Int# i# )|Int# -> Bool isTrue#(Int# i# Int# -> Int# -> Int# >=#Int# 0#)=GmpLimb# -> Natural NatS# (Int# -> GmpLimb# int2Word#Int# i# )naturalFromInteger (Jp#BigNat bn )=BigNat -> Natural bigNatToNatural BigNat bn naturalFromInteger Integer _=Natural forall a. a underflowError {-# CONSTANT_FOLDED naturalFromInteger #-}-- | Compute greatest common divisor.gcdNatural ::Natural ->Natural ->Natural gcdNatural :: Natural -> Natural -> Natural gcdNatural (NatS# GmpLimb# 0##)Natural y =Natural y gcdNatural Natural x (NatS# GmpLimb# 0##)=Natural x gcdNatural (NatS# GmpLimb# 1##)Natural _=GmpLimb# -> Natural NatS# GmpLimb# 1##gcdNatural Natural _(NatS# GmpLimb# 1##)=GmpLimb# -> Natural NatS# GmpLimb# 1##gcdNatural (NatJ# BigNat x )(NatJ# BigNat y )=BigNat -> Natural bigNatToNatural (BigNat -> BigNat -> BigNat gcdBigNatBigNat x BigNat y )gcdNatural (NatJ# BigNat x )(NatS# GmpLimb# y )=GmpLimb# -> Natural NatS# (BigNat -> GmpLimb# -> GmpLimb# gcdBigNatWordBigNat x GmpLimb# y )gcdNatural (NatS# GmpLimb# x )(NatJ# BigNat y )=GmpLimb# -> Natural NatS# (BigNat -> GmpLimb# -> GmpLimb# gcdBigNatWordBigNat y GmpLimb# x )gcdNatural (NatS# GmpLimb# x )(NatS# GmpLimb# y )=GmpLimb# -> Natural NatS# (GmpLimb# -> GmpLimb# -> GmpLimb# gcdWordGmpLimb# x GmpLimb# y )-- | Compute least common multiple.lcmNatural ::Natural ->Natural ->Natural lcmNatural :: Natural -> Natural -> Natural lcmNatural (NatS# GmpLimb# 0##)Natural _=GmpLimb# -> Natural NatS# GmpLimb# 0##lcmNatural Natural _(NatS# GmpLimb# 0##)=GmpLimb# -> Natural NatS# GmpLimb# 0##lcmNatural (NatS# GmpLimb# 1##)Natural y =Natural y lcmNatural Natural x (NatS# GmpLimb# 1##)=Natural x lcmNatural Natural x Natural y =(Natural x Natural -> Natural -> Natural `quotNatural` (Natural -> Natural -> Natural gcdNatural Natural x Natural y ))Natural -> Natural -> Natural `timesNatural` Natural y ----------------------------------------------------------------------------quotRemNatural ::Natural ->Natural ->(Natural ,Natural )quotRemNatural :: Natural -> Natural -> (Natural, Natural) quotRemNatural Natural _(NatS# GmpLimb# 0##)=(Natural, Natural) forall a. a divZeroError quotRemNatural Natural n (NatS# GmpLimb# 1##)=(Natural n ,GmpLimb# -> Natural NatS# GmpLimb# 0##)quotRemNatural n :: Natural n @(NatS# GmpLimb# _)(NatJ# BigNat _)=(GmpLimb# -> Natural NatS# GmpLimb# 0##,Natural n )quotRemNatural (NatS# GmpLimb# n )(NatS# GmpLimb# d )=caseGmpLimb# -> GmpLimb# -> (# GmpLimb#, GmpLimb# #) quotRemWord#GmpLimb# n GmpLimb# d of(#GmpLimb# q ,GmpLimb# r #)->(GmpLimb# -> Natural NatS# GmpLimb# q ,GmpLimb# -> Natural NatS# GmpLimb# r )quotRemNatural (NatJ# BigNat n )(NatS# GmpLimb# d )=caseBigNat -> GmpLimb# -> (# BigNat, GmpLimb# #) quotRemBigNatWordBigNat n GmpLimb# d of(#BigNat q ,GmpLimb# r #)->(BigNat -> Natural bigNatToNatural BigNat q ,GmpLimb# -> Natural NatS# GmpLimb# r )quotRemNatural (NatJ# BigNat n )(NatJ# BigNat d )=caseBigNat -> BigNat -> (# BigNat, BigNat #) quotRemBigNatBigNat n BigNat d of(#BigNat q ,BigNat r #)->(BigNat -> Natural bigNatToNatural BigNat q ,BigNat -> Natural bigNatToNatural BigNat r )-- {-# CONSTANT_FOLDED quotRemNatural #-}quotNatural ::Natural ->Natural ->Natural quotNatural :: Natural -> Natural -> Natural quotNatural Natural _(NatS# GmpLimb# 0##)=Natural forall a. a divZeroError quotNatural Natural n (NatS# GmpLimb# 1##)=Natural n quotNatural (NatS# GmpLimb# _)(NatJ# BigNat _)=GmpLimb# -> Natural NatS# GmpLimb# 0##quotNatural (NatS# GmpLimb# n )(NatS# GmpLimb# d )=GmpLimb# -> Natural NatS# (GmpLimb# -> GmpLimb# -> GmpLimb# quotWord#GmpLimb# n GmpLimb# d )quotNatural (NatJ# BigNat n )(NatS# GmpLimb# d )=BigNat -> Natural bigNatToNatural (BigNat -> GmpLimb# -> BigNat quotBigNatWordBigNat n GmpLimb# d )quotNatural (NatJ# BigNat n )(NatJ# BigNat d )=BigNat -> Natural bigNatToNatural (BigNat -> BigNat -> BigNat quotBigNatBigNat n BigNat d )-- {-# CONSTANT_FOLDED quotNatural #-}remNatural ::Natural ->Natural ->Natural remNatural :: Natural -> Natural -> Natural remNatural Natural _(NatS# GmpLimb# 0##)=Natural forall a. a divZeroError remNatural Natural _(NatS# GmpLimb# 1##)=GmpLimb# -> Natural NatS# GmpLimb# 0##remNatural n :: Natural n @(NatS# GmpLimb# _)(NatJ# BigNat _)=Natural n remNatural (NatS# GmpLimb# n )(NatS# GmpLimb# d )=GmpLimb# -> Natural NatS# (GmpLimb# -> GmpLimb# -> GmpLimb# remWord#GmpLimb# n GmpLimb# d )remNatural (NatJ# BigNat n )(NatS# GmpLimb# d )=GmpLimb# -> Natural NatS# (BigNat -> GmpLimb# -> GmpLimb# remBigNatWordBigNat n GmpLimb# d )remNatural (NatJ# BigNat n )(NatJ# BigNat d )=BigNat -> Natural bigNatToNatural (BigNat -> BigNat -> BigNat remBigNatBigNat n BigNat d )-- {-# CONSTANT_FOLDED remNatural #-}-- | @since 4.X.0.0naturalToInteger ::Natural ->IntegernaturalToInteger :: Natural -> Integer naturalToInteger (NatS# GmpLimb# w )=GmpLimb# -> Integer wordToIntegerGmpLimb# w naturalToInteger (NatJ# BigNat bn )=BigNat -> Integer Jp#BigNat bn {-# CONSTANT_FOLDED naturalToInteger #-}andNatural ::Natural ->Natural ->Natural andNatural :: Natural -> Natural -> Natural andNatural (NatS# GmpLimb# n )(NatS# GmpLimb# m )=GmpLimb# -> Natural NatS# (GmpLimb# n GmpLimb# -> GmpLimb# -> GmpLimb# `and#`GmpLimb# m )andNatural (NatS# GmpLimb# n )(NatJ# BigNat m )=GmpLimb# -> Natural NatS# (GmpLimb# n GmpLimb# -> GmpLimb# -> GmpLimb# `and#`BigNat -> GmpLimb# bigNatToWordBigNat m )andNatural (NatJ# BigNat n )(NatS# GmpLimb# m )=GmpLimb# -> Natural NatS# (BigNat -> GmpLimb# bigNatToWordBigNat n GmpLimb# -> GmpLimb# -> GmpLimb# `and#`GmpLimb# m )andNatural (NatJ# BigNat n )(NatJ# BigNat m )=BigNat -> Natural bigNatToNatural (BigNat -> BigNat -> BigNat andBigNatBigNat n BigNat m )-- {-# CONSTANT_FOLDED andNatural #-}orNatural ::Natural ->Natural ->Natural orNatural :: Natural -> Natural -> Natural orNatural (NatS# GmpLimb# n )(NatS# GmpLimb# m )=GmpLimb# -> Natural NatS# (GmpLimb# n GmpLimb# -> GmpLimb# -> GmpLimb# `or#`GmpLimb# m )orNatural (NatS# GmpLimb# n )(NatJ# BigNat m )=BigNat -> Natural NatJ# (BigNat -> BigNat -> BigNat orBigNat(GmpLimb# -> BigNat wordToBigNatGmpLimb# n )BigNat m )orNatural (NatJ# BigNat n )(NatS# GmpLimb# m )=BigNat -> Natural NatJ# (BigNat -> BigNat -> BigNat orBigNatBigNat n (GmpLimb# -> BigNat wordToBigNatGmpLimb# m ))orNatural (NatJ# BigNat n )(NatJ# BigNat m )=BigNat -> Natural NatJ# (BigNat -> BigNat -> BigNat orBigNatBigNat n BigNat m )-- {-# CONSTANT_FOLDED orNatural #-}xorNatural ::Natural ->Natural ->Natural xorNatural :: Natural -> Natural -> Natural xorNatural (NatS# GmpLimb# n )(NatS# GmpLimb# m )=GmpLimb# -> Natural NatS# (GmpLimb# n GmpLimb# -> GmpLimb# -> GmpLimb# `xor#`GmpLimb# m )xorNatural (NatS# GmpLimb# n )(NatJ# BigNat m )=BigNat -> Natural NatJ# (BigNat -> BigNat -> BigNat xorBigNat(GmpLimb# -> BigNat wordToBigNatGmpLimb# n )BigNat m )xorNatural (NatJ# BigNat n )(NatS# GmpLimb# m )=BigNat -> Natural NatJ# (BigNat -> BigNat -> BigNat xorBigNatBigNat n (GmpLimb# -> BigNat wordToBigNatGmpLimb# m ))xorNatural (NatJ# BigNat n )(NatJ# BigNat m )=BigNat -> Natural bigNatToNatural (BigNat -> BigNat -> BigNat xorBigNatBigNat n BigNat m )-- {-# CONSTANT_FOLDED xorNatural #-}bitNatural ::Int#->Natural bitNatural :: Int# -> Natural bitNatural Int# i# |Int# -> Bool isTrue#(Int# i# Int# -> Int# -> Int# <#WORD_SIZE_IN_BITS#)=NatS#(1##`uncheckedShiftL#`i#)|Bool True=BigNat -> Natural NatJ# (Int# -> BigNat bitBigNatInt# i# )-- {-# CONSTANT_FOLDED bitNatural #-}testBitNatural ::Natural ->Int->BooltestBitNatural :: Natural -> Int -> Bool testBitNatural (NatS# GmpLimb# w )(I#Int# i# )|Int# -> Bool isTrue#(Int# i# Int# -> Int# -> Int# <#WORD_SIZE_IN_BITS#)=Int# -> Bool isTrue#((GmpLimb# w GmpLimb# -> GmpLimb# -> GmpLimb# `and#`(GmpLimb# 1##GmpLimb# -> Int# -> GmpLimb# `uncheckedShiftL#`Int# i# ))GmpLimb# -> GmpLimb# -> Int# `neWord#`GmpLimb# 0##)|Bool True=Bool FalsetestBitNatural (NatJ# BigNat bn )(I#Int# i# )=BigNat -> Int# -> Bool testBitBigNatBigNat bn Int# i# -- {-# CONSTANT_FOLDED testBitNatural #-}popCountNatural ::Natural ->IntpopCountNatural :: Natural -> Int popCountNatural (NatS# GmpLimb# w )=Int# -> Int I#(GmpLimb# -> Int# word2Int#(GmpLimb# -> GmpLimb# popCnt#GmpLimb# w ))popCountNatural (NatJ# BigNat bn )=Int# -> Int I#(BigNat -> Int# popCountBigNatBigNat bn )-- {-# CONSTANT_FOLDED popCountNatural #-}shiftLNatural ::Natural ->Int->Natural shiftLNatural :: Natural -> Int -> Natural shiftLNatural Natural n (I#Int# 0#)=Natural n shiftLNatural (NatS# GmpLimb# 0##)Int _=GmpLimb# -> Natural NatS# GmpLimb# 0##shiftLNatural (NatS# GmpLimb# 1##)(I#Int# i# )=Int# -> Natural bitNatural Int# i# shiftLNatural (NatS# GmpLimb# w )(I#Int# i# )=BigNat -> Natural bigNatToNatural (BigNat -> Int# -> BigNat shiftLBigNat(GmpLimb# -> BigNat wordToBigNatGmpLimb# w )Int# i# )shiftLNatural (NatJ# BigNat bn )(I#Int# i# )=BigNat -> Natural bigNatToNatural (BigNat -> Int# -> BigNat shiftLBigNatBigNat bn Int# i# )-- {-# CONSTANT_FOLDED shiftLNatural #-}shiftRNatural ::Natural ->Int->Natural shiftRNatural :: Natural -> Int -> Natural shiftRNatural Natural n (I#Int# 0#)=Natural n shiftRNatural (NatS# GmpLimb# w )(I#Int# i# )|Int# -> Bool isTrue#(Int# i# Int# -> Int# -> Int# >=#WORD_SIZE_IN_BITS#)=NatS#0##|Bool True=GmpLimb# -> Natural NatS# (GmpLimb# w GmpLimb# -> Int# -> GmpLimb# `uncheckedShiftRL#`Int# i# )shiftRNatural (NatJ# BigNat bn )(I#Int# i# )=BigNat -> Natural bigNatToNatural (BigNat -> Int# -> BigNat shiftRBigNatBigNat bn Int# i# )-- {-# CONSTANT_FOLDED shiftRNatural #-}------------------------------------------------------------------------------ | 'Natural' AdditionplusNatural ::Natural ->Natural ->Natural plusNatural :: Natural -> Natural -> Natural plusNatural (NatS# GmpLimb# 0##)Natural y =Natural y plusNatural Natural x (NatS# GmpLimb# 0##)=Natural x plusNatural (NatS# GmpLimb# x )(NatS# GmpLimb# y )=caseGmpLimb# -> GmpLimb# -> (# GmpLimb#, GmpLimb# #) plusWord2#GmpLimb# x GmpLimb# y of(#GmpLimb# 0##,GmpLimb# l #)->GmpLimb# -> Natural NatS# GmpLimb# l (#GmpLimb# h ,GmpLimb# l #)->BigNat -> Natural NatJ# (GmpLimb# -> GmpLimb# -> BigNat wordToBigNat2GmpLimb# h GmpLimb# l )plusNatural (NatS# GmpLimb# x )(NatJ# BigNat y )=BigNat -> Natural NatJ# (BigNat -> GmpLimb# -> BigNat plusBigNatWordBigNat y GmpLimb# x )plusNatural (NatJ# BigNat x )(NatS# GmpLimb# y )=BigNat -> Natural NatJ# (BigNat -> GmpLimb# -> BigNat plusBigNatWordBigNat x GmpLimb# y )plusNatural (NatJ# BigNat x )(NatJ# BigNat y )=BigNat -> Natural NatJ# (BigNat -> BigNat -> BigNat plusBigNatBigNat x BigNat y ){-# CONSTANT_FOLDED plusNatural #-}-- | 'Natural' multiplicationtimesNatural ::Natural ->Natural ->Natural timesNatural :: Natural -> Natural -> Natural timesNatural Natural _(NatS# GmpLimb# 0##)=GmpLimb# -> Natural NatS# GmpLimb# 0##timesNatural (NatS# GmpLimb# 0##)Natural _=GmpLimb# -> Natural NatS# GmpLimb# 0##timesNatural Natural x (NatS# GmpLimb# 1##)=Natural x timesNatural (NatS# GmpLimb# 1##)Natural y =Natural y timesNatural (NatS# GmpLimb# x )(NatS# GmpLimb# y )=caseGmpLimb# -> GmpLimb# -> (# GmpLimb#, GmpLimb# #) timesWord2#GmpLimb# x GmpLimb# y of(#GmpLimb# 0##,GmpLimb# 0###)->GmpLimb# -> Natural NatS# GmpLimb# 0##(#GmpLimb# 0##,GmpLimb# xy #)->GmpLimb# -> Natural NatS# GmpLimb# xy (#GmpLimb# h ,GmpLimb# l #)->BigNat -> Natural NatJ# (GmpLimb# -> GmpLimb# -> BigNat wordToBigNat2GmpLimb# h GmpLimb# l )timesNatural (NatS# GmpLimb# x )(NatJ# BigNat y )=BigNat -> Natural NatJ# (BigNat -> GmpLimb# -> BigNat timesBigNatWordBigNat y GmpLimb# x )timesNatural (NatJ# BigNat x )(NatS# GmpLimb# y )=BigNat -> Natural NatJ# (BigNat -> GmpLimb# -> BigNat timesBigNatWordBigNat x GmpLimb# y )timesNatural (NatJ# BigNat x )(NatJ# BigNat y )=BigNat -> Natural NatJ# (BigNat -> BigNat -> BigNat timesBigNatBigNat x BigNat y ){-# CONSTANT_FOLDED timesNatural #-}-- | 'Natural' subtraction. May @'Control.Exception.throw'-- 'Control.Exception.Underflow'@.minusNatural ::Natural ->Natural ->Natural minusNatural :: Natural -> Natural -> Natural minusNatural Natural x (NatS# GmpLimb# 0##)=Natural x minusNatural (NatS# GmpLimb# x )(NatS# GmpLimb# y )=caseGmpLimb# -> GmpLimb# -> (# GmpLimb#, Int# #) subWordC#GmpLimb# x GmpLimb# y of(#GmpLimb# l ,Int# 0##)->GmpLimb# -> Natural NatS# GmpLimb# l (# GmpLimb#, Int# #) _->Natural forall a. a underflowError minusNatural (NatS# GmpLimb# _)(NatJ# BigNat _)=Natural forall a. a underflowError minusNatural (NatJ# BigNat x )(NatS# GmpLimb# y )=BigNat -> Natural bigNatToNatural (BigNat -> GmpLimb# -> BigNat minusBigNatWordBigNat x GmpLimb# y )minusNatural (NatJ# BigNat x )(NatJ# BigNat y )=BigNat -> Natural bigNatToNatural (BigNat -> BigNat -> BigNat minusBigNatBigNat x BigNat y ){-# CONSTANT_FOLDED minusNatural #-}-- | 'Natural' subtraction. Returns 'Nothing's for non-positive results.---- @since 4.8.0.0minusNaturalMaybe ::Natural ->Natural ->Maybe Natural minusNaturalMaybe :: Natural -> Natural -> Maybe Natural minusNaturalMaybe Natural x (NatS# GmpLimb# 0##)=Natural -> Maybe Natural forall a. a -> Maybe a Just Natural x minusNaturalMaybe (NatS# GmpLimb# x )(NatS# GmpLimb# y )=caseGmpLimb# -> GmpLimb# -> (# GmpLimb#, Int# #) subWordC#GmpLimb# x GmpLimb# y of(#GmpLimb# l ,Int# 0##)->Natural -> Maybe Natural forall a. a -> Maybe a Just (GmpLimb# -> Natural NatS# GmpLimb# l )(# GmpLimb#, Int# #) _->Maybe Natural forall a. Maybe a Nothing minusNaturalMaybe (NatS# GmpLimb# _)(NatJ# BigNat _)=Maybe Natural forall a. Maybe a Nothing minusNaturalMaybe (NatJ# BigNat x )(NatS# GmpLimb# y )=Natural -> Maybe Natural forall a. a -> Maybe a Just (BigNat -> Natural bigNatToNatural (BigNat -> GmpLimb# -> BigNat minusBigNatWordBigNat x GmpLimb# y ))minusNaturalMaybe (NatJ# BigNat x )(NatJ# BigNat y )|Int# -> Bool isTrue#(BigNat -> Int# isNullBigNat#BigNat res )=Maybe Natural forall a. Maybe a Nothing |Bool True=Natural -> Maybe Natural forall a. a -> Maybe a Just (BigNat -> Natural bigNatToNatural BigNat res )whereres :: BigNat res =BigNat -> BigNat -> BigNat minusBigNatBigNat x BigNat y -- | Convert 'BigNat' to 'Natural'.-- Throws 'Control.Exception.Underflow' if passed a 'nullBigNat'.bigNatToNatural ::BigNat->Natural bigNatToNatural :: BigNat -> Natural bigNatToNatural BigNat bn |Int# -> Bool isTrue#(BigNat -> Int# sizeofBigNat#BigNat bn Int# -> Int# -> Int# ==#Int# 1#)=GmpLimb# -> Natural NatS# (BigNat -> GmpLimb# bigNatToWordBigNat bn )|Int# -> Bool isTrue#(BigNat -> Int# isNullBigNat#BigNat bn )=Natural forall a. a underflowError |Bool True=BigNat -> Natural NatJ# BigNat bn naturalToBigNat ::Natural ->BigNatnaturalToBigNat :: Natural -> BigNat naturalToBigNat (NatS# GmpLimb# w# )=GmpLimb# -> BigNat wordToBigNatGmpLimb# w# naturalToBigNat (NatJ# BigNat bn )=BigNat bn naturalToWord ::Natural ->WordnaturalToWord :: Natural -> Word naturalToWord (NatS# GmpLimb# w# )=GmpLimb# -> Word W#GmpLimb# w# naturalToWord (NatJ# BigNat bn )=GmpLimb# -> Word W#(BigNat -> GmpLimb# bigNatToWordBigNat bn )naturalToInt ::Natural ->IntnaturalToInt :: Natural -> Int naturalToInt (NatS# GmpLimb# w# )=Int# -> Int I#(GmpLimb# -> Int# word2Int#GmpLimb# w# )naturalToInt (NatJ# BigNat bn )=Int# -> Int I#(BigNat -> Int# bigNatToIntBigNat bn )------------------------------------------------------------------------------ | Convert a Word# into a Natural---- Built-in rule ensures that applications of this function to literal Word# are-- lifted into Natural literals.wordToNatural# ::Word#->Natural wordToNatural# :: GmpLimb# -> Natural wordToNatural# GmpLimb# w# =GmpLimb# -> Natural NatS# GmpLimb# w# {-# CONSTANT_FOLDED wordToNatural# #-}-- | Convert a Word# into a Natural---- In base we can't use wordToNatural# as built-in rules transform some of them-- into Natural literals. Use this function instead.wordToNaturalBase ::Word#->Natural wordToNaturalBase :: GmpLimb# -> Natural wordToNaturalBase GmpLimb# w# =GmpLimb# -> Natural NatS# GmpLimb# w# #else /* !defined(MIN_VERSION_integer_gmp) */ ------------------------------------------------------------------------------ Use wrapped 'Integer' as fallback; taken from Edward Kmett's nats package-- | Type representing arbitrary-precision non-negative integers.---- Operations whose result would be negative @'Control.Exception.throw'-- ('Control.Exception.Underflow' :: 'Control.Exception.ArithException')@.---- @since 4.8.0.0newtypeNatural=NaturalInteger-- ^ __Invariant__: non-negative 'Integer'deriving(Eq,Ord)-- | Test whether all internal invariants are satisfied by 'Natural' value---- This operation is mostly useful for test-suites and/or code which-- constructs 'Natural' values directly.---- @since 4.8.0.0isValidNatural::Natural->BoolisValidNatural(Naturali)=i>=wordToInteger0##-- | Convert a 'Word#' into a 'Natural'---- Built-in rule ensures that applications of this function to literal 'Word#'-- are lifted into 'Natural' literals.wordToNatural#::Word#->NaturalwordToNatural#w##=Natural(wordToIntegerw##){-# CONSTANT_FOLDED wordToNatural# #-}-- | Convert a 'Word#' into a Natural---- In base we can't use wordToNatural# as built-in rules transform some of them-- into Natural literals. Use this function instead.wordToNaturalBase::Word#->NaturalwordToNaturalBasew##=Natural(wordToIntegerw##)-- | @since 4.10.0.0naturalFromInteger::Integer->NaturalnaturalFromIntegern|n>=wordToInteger0##=Naturaln|True=underflowError{-# INLINEnaturalFromInteger#-}-- | Compute greatest common divisor.gcdNatural::Natural->Natural->NaturalgcdNatural(Naturaln)(Naturalm)=Natural(n`gcdInteger`m)-- | Compute lowest common multiple.lcmNatural::Natural->Natural->NaturallcmNatural(Naturaln)(Naturalm)=Natural(n`lcmInteger`m)-- | 'Natural' subtraction. Returns 'Nothing's for non-positive results.---- @since 4.8.0.0minusNaturalMaybe::Natural->Natural->MaybeNaturalminusNaturalMaybe(Naturalx)(Naturaly)|x>=y=Just(Natural(x`minusInteger`y))|True=NothingshiftLNatural::Natural->Int->NaturalshiftLNatural(Naturaln)(I#i)=Natural(n`shiftLInteger`i)-- {-# CONSTANT_FOLDED shiftLNatural #-}shiftRNatural::Natural->Int->NaturalshiftRNatural(Naturaln)(I#i)=Natural(n`shiftRInteger`i)-- {-# CONSTANT_FOLDED shiftRNatural #-}plusNatural::Natural->Natural->NaturalplusNatural(Naturalx)(Naturaly)=Natural(x`plusInteger`y){-# CONSTANT_FOLDED plusNatural #-}minusNatural::Natural->Natural->NaturalminusNatural(Naturalx)(Naturaly)=ifz`ltInteger`wordToInteger0##thenunderflowErrorelseNaturalzwherez=x`minusInteger`y{-# CONSTANT_FOLDED minusNatural #-}timesNatural::Natural->Natural->NaturaltimesNatural(Naturalx)(Naturaly)=Natural(x`timesInteger`y){-# CONSTANT_FOLDED timesNatural #-}orNatural::Natural->Natural->NaturalorNatural(Naturalx)(Naturaly)=Natural(x`orInteger`y)-- {-# CONSTANT_FOLDED orNatural #-}xorNatural::Natural->Natural->NaturalxorNatural(Naturalx)(Naturaly)=Natural(x`xorInteger`y)-- {-# CONSTANT_FOLDED xorNatural #-}andNatural::Natural->Natural->NaturalandNatural(Naturalx)(Naturaly)=Natural(x`andInteger`y)-- {-# CONSTANT_FOLDED andNatural #-}naturalToInt::Natural->IntnaturalToInt(Naturali)=I#(integerToInti)naturalToWord::Natural->WordnaturalToWord(Naturali)=W#(integerToWordi)naturalToInteger::Natural->IntegernaturalToInteger(Naturali)=i{-# CONSTANT_FOLDED naturalToInteger #-}testBitNatural::Natural->Int->BooltestBitNatural(Naturaln)(I#i)=testBitIntegerni-- {-# CONSTANT_FOLDED testBitNatural #-}popCountNatural::Natural->IntpopCountNatural(Naturaln)=I#(popCountIntegern)bitNatural::Int#->NaturalbitNaturali#|isTrue#(i#<#WORD_SIZE_IN_BITS#)=wordToNaturalBase(1##`uncheckedShiftL#`i#)|True=Natural(1`shiftLInteger`i#)-- {-# CONSTANT_FOLDED bitNatural #-}quotNatural::Natural->Natural->NaturalquotNaturaln@(Naturalx)(Naturaly)|y==wordToInteger0##=divZeroError|y==wordToInteger1##=n|True=Natural(x`quotInteger`y)-- {-# CONSTANT_FOLDED quotNatural #-}remNatural::Natural->Natural->NaturalremNatural(Naturalx)(Naturaly)|y==wordToInteger0##=divZeroError|y==wordToInteger1##=wordToNaturalBase0##|True=Natural(x`remInteger`y)-- {-# CONSTANT_FOLDED remNatural #-}quotRemNatural::Natural->Natural->(Natural,Natural)quotRemNaturaln@(Naturalx)(Naturaly)|y==wordToInteger0##=divZeroError|y==wordToInteger1##=(n,wordToNaturalBase0##)|True=casequotRemIntegerxyof(#k,r#)->(Naturalk,Naturalr)-- {-# CONSTANT_FOLDED quotRemNatural #-}signumNatural::Natural->NaturalsignumNatural(Naturalx)|x==wordToInteger0##=wordToNaturalBase0##|True=wordToNaturalBase1##-- {-# CONSTANT_FOLDED signumNatural #-}negateNatural::Natural->NaturalnegateNatural(Naturalx)|x==wordToInteger0##=wordToNaturalBase0##|True=underflowError-- {-# CONSTANT_FOLDED negateNatural #-} #endif -- | Construct 'Natural' from 'Word' value.---- @since 4.8.0.0wordToNatural ::Word->Natural wordToNatural :: Word -> Natural wordToNatural (W#GmpLimb# w# )=GmpLimb# -> Natural wordToNatural# GmpLimb# w# -- | Try downcasting 'Natural' to 'Word' value.-- Returns 'Nothing' if value doesn't fit in 'Word'.---- @since 4.8.0.0naturalToWordMaybe ::Natural ->Maybe Word #if defined(MIN_VERSION_integer_gmp) naturalToWordMaybe :: Natural -> Maybe Word naturalToWordMaybe (NatS# GmpLimb# w# )=Word -> Maybe Word forall a. a -> Maybe a Just (GmpLimb# -> Word W#GmpLimb# w# )naturalToWordMaybe (NatJ# BigNat _)=Maybe Word forall a. Maybe a Nothing #else naturalToWordMaybe(Naturali)|i<maxw=Just(W#(integerToWordi))|True=Nothingwheremaxw=1`shiftLInteger`WORD_SIZE_IN_BITS# #endif -- | \"@'powModNatural' /b/ /e/ /m/@\" computes base @/b/@ raised to-- exponent @/e/@ modulo @/m/@.---- @since 4.8.0.0powModNatural ::Natural ->Natural ->Natural ->Natural #if defined(MIN_VERSION_integer_gmp) powModNatural :: Natural -> Natural -> Natural -> Natural powModNatural Natural _Natural _(NatS# GmpLimb# 0##)=Natural forall a. a divZeroError powModNatural Natural _Natural _(NatS# GmpLimb# 1##)=GmpLimb# -> Natural NatS# GmpLimb# 0##powModNatural Natural _(NatS# GmpLimb# 0##)Natural _=GmpLimb# -> Natural NatS# GmpLimb# 1##powModNatural (NatS# GmpLimb# 0##)Natural _Natural _=GmpLimb# -> Natural NatS# GmpLimb# 0##powModNatural (NatS# GmpLimb# 1##)Natural _Natural _=GmpLimb# -> Natural NatS# GmpLimb# 1##powModNatural (NatS# GmpLimb# b )(NatS# GmpLimb# e )(NatS# GmpLimb# m )=GmpLimb# -> Natural NatS# (GmpLimb# -> GmpLimb# -> GmpLimb# -> GmpLimb# powModWordGmpLimb# b GmpLimb# e GmpLimb# m )powModNatural Natural b Natural e (NatS# GmpLimb# m )=GmpLimb# -> Natural NatS# (BigNat -> BigNat -> GmpLimb# -> GmpLimb# powModBigNatWord(Natural -> BigNat naturalToBigNat Natural b )(Natural -> BigNat naturalToBigNat Natural e )GmpLimb# m )powModNatural Natural b Natural e (NatJ# BigNat m )=BigNat -> Natural bigNatToNatural (BigNat -> BigNat -> BigNat -> BigNat powModBigNat(Natural -> BigNat naturalToBigNat Natural b )(Natural -> BigNat naturalToBigNat Natural e )BigNat m ) #else -- Portable reference fallback implementationpowModNatural(Naturalb0)(Naturale0)(Naturalm)|m==wordToInteger0##=divZeroError|m==wordToInteger1##=wordToNaturalBase0##|e0==wordToInteger0##=wordToNaturalBase1##|b0==wordToInteger0##=wordToNaturalBase0##|b0==wordToInteger1##=wordToNaturalBase1##|True=gob0e0(wordToInteger1##)wherego!be!r|e`testBitInteger`0#=gob'e'((r`timesInteger`b)`modInteger`m)|e==wordToInteger0##=naturalFromIntegerr|True=gob'e'rwhereb'=(b`timesInteger`b)`modInteger`me'=e`shiftRInteger`1#-- slightly faster than "e `div` 2" #endif -- | Construct 'Natural' value from list of 'Word's.---- This function is used by GHC for constructing 'Natural' literals.mkNatural ::[Word]-- ^ value expressed in 32 bit chunks, least-- significant first->Natural mkNatural :: [Word] -> Natural mkNatural []=GmpLimb# -> Natural wordToNaturalBase GmpLimb# 0##mkNatural (W#GmpLimb# i :[Word] is' )=GmpLimb# -> Natural wordToNaturalBase (GmpLimb# i GmpLimb# -> GmpLimb# -> GmpLimb# `and#`GmpLimb# 0xffffffff##)Natural -> Natural -> Natural `orNatural` Natural -> Int -> Natural shiftLNatural ([Word] -> Natural mkNatural [Word] is' )Int 32{-# CONSTANT_FOLDED mkNatural #-}-- | Convert 'Int' to 'Natural'.-- Throws 'Control.Exception.Underflow' when passed a negative 'Int'.intToNatural ::Int->Natural intToNatural :: Int -> Natural intToNatural (I#Int# i# )|Int# -> Bool isTrue#(Int# i# Int# -> Int# -> Int# <#Int# 0#)=Natural forall a. a underflowError |Bool True=GmpLimb# -> Natural wordToNaturalBase (Int# -> GmpLimb# int2Word#Int# i# )