integer-gmp-1.1: Integer library based on GMP
Copyright(c) Herbert Valerio Riedel 2014
LicenseBSD3
Maintainerghc-devs@haskell.org
Stabilityprovisional
Portabilitynon-portable (GHC Extensions)
Safe HaskellNone
LanguageHaskell2010

GHC.Integer.GMP.Internals

Description

 
Synopsis

The Integer type

data Integer where Source #

Arbitrary precision integers. In contrast with fixed-size integral types such as Int, the Integer type represents the entire infinite range of integers.

Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.

If the value is small (i.e., fits into an Int), the IS constructor is used. Otherwise IP and IN constructors are used to store a BigNat representing the positive or the negative value magnitude, respectively.

Invariant: IP and IN are used iff the value does not fit in IS.

Bundled Patterns

pattern S# :: Int# -> Integer

Deprecated: Use IS constructor instead

pattern Jn# :: BigNat -> Integer

Deprecated: Use IN constructor instead

pattern Jp# :: BigNat -> Integer

Deprecated: Use IP constructor instead

Instances

Instances details
PrintfArg Integer

Since: base-2.1

Instance details

Defined in Text.Printf

Bits Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Bits

Data Integer

@since base-4.0.0.0

Instance details

Defined in GHC.Internal.Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer Source #

toConstr :: Integer -> Constr Source #

dataTypeOf :: Integer -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Integer) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) Source #

gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

Enum Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Enum

Ix Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Ix

Num Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Num

Read Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Read

Integral Integer

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Real Integer

@since base-2.0.1

Instance details

Defined in GHC.Internal.Real

Show Integer

@since base-2.01

Instance details

Defined in GHC.Internal.Show

Eq Integer 
Instance details

Defined in GHC.Num.Integer

Ord Integer 
Instance details

Defined in GHC.Num.Integer

isValidInteger# :: Integer -> Int# Source #

Deprecated: Use integerCheck# instead

Basic Integer operations

Additional Integer operations

gcdInteger :: Integer -> Integer -> Integer Source #

Deprecated: Use integerGcd instead

gcdExtInteger :: Integer -> Integer -> (# Integer, Integer #) Source #

Deprecated: Use integerGcde instead

lcmInteger :: Integer -> Integer -> Integer Source #

Deprecated: Use integerLcm instead

sqrInteger :: Integer -> Integer Source #

Deprecated: Use integerSqr instead

powModInteger :: Integer -> Integer -> Integer -> Integer Source #

Deprecated: Use integerPowMod# instead

recipModInteger :: Integer -> Integer -> Integer Source #

Deprecated: Use integerRecipMod# instead

Additional conversion operations to Integer

wordToNegInteger :: Word# -> Integer Source #

Deprecated: Use integerFromWordNeg# instead

bigNatToInteger :: BigNat -> Integer Source #

Deprecated: Use integerFromBigNat# instead

bigNatToNegInteger :: BigNat -> Integer Source #

Deprecated: Use integerFromBigNatNeg# instead

The BigNat type

data BigNat Source #

A lifted BigNat

Represented as an array of limbs (Word#) stored in little-endian order (Word# themselves use machine order).

Invariant (canonical representation): higher Word# is non-zero.

As a consequence, zero is represented with a WordArray# whose size is 0.

Constructors

BN# 

Fields

Instances

Instances details
Eq BigNat 
Instance details

Defined in GHC.Num.BigNat

Ord BigNat 
Instance details

Defined in GHC.Num.BigNat

isValidBigNat# :: BigNat -> Int# Source #

Deprecated: Use bigNatCheck# instead

sizeofBigNat# :: BigNat -> GmpSize# Source #

Deprecated: Use bigNatSize# instead

zeroBigNat :: BigNat Source #

Deprecated: Use bigNatZero instead

oneBigNat :: BigNat Source #

Deprecated: Use bigNatOne instead

Conversions to/from BigNat

byteArrayToBigNat# :: ByteArray# -> GmpSize# -> BigNat Source #

Deprecated: Use bigNatFromWordArray instead

indexBigNat# :: BigNat -> GmpSize# -> GmpLimb# Source #

Deprecated: Use bigNatIndex# instead

BigNat arithmetic operations

plusBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatAdd instead

plusBigNatWord :: BigNat -> GmpLimb# -> BigNat Source #

Deprecated: Use bigNatAddWord# instead

minusBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatSub instead

minusBigNatWord :: BigNat -> GmpLimb# -> BigNat Source #

Deprecated: Use bigNatSubWord# instead

timesBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatMul instead

timesBigNatWord :: BigNat -> GmpLimb# -> BigNat Source #

Deprecated: Use bigNatMulWord# instead

sqrBigNat :: BigNat -> BigNat Source #

Deprecated: Use bigNatSqr instead

quotRemBigNat :: BigNat -> BigNat -> (# BigNat, BigNat #) Source #

Deprecated: Use bigNatQuotRem# instead

quotRemBigNatWord :: BigNat -> GmpLimb# -> (# BigNat, GmpLimb# #) Source #

Deprecated: Use bigNatQuotRemWord# instead

quotBigNatWord :: BigNat -> GmpLimb# -> BigNat Source #

Deprecated: Use bigNatQuotWord# instead

quotBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatQuot instead

remBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatRem instead

remBigNatWord :: BigNat -> GmpLimb# -> Word# Source #

Deprecated: Use bigNatRemWord# instead

gcdBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatGcd instead

gcdBigNatWord :: BigNat -> Word# -> Word# Source #

Deprecated: Use bigNatGcdWord# instead

BigNat logic operations

shiftRBigNat :: BigNat -> Int# -> BigNat Source #

Deprecated: Use bigNatShiftR# instead

shiftLBigNat :: BigNat -> Int# -> BigNat Source #

Deprecated: Use bigNatShiftL# instead

testBitBigNat :: BigNat -> Int# -> Bool Source #

Deprecated: Use bigNatTestBit# instead

clearBitBigNat :: BigNat -> Int# -> BigNat Source #

Deprecated: Use bigNatClearBit# instead

complementBitBigNat :: BigNat -> Int# -> BigNat Source #

Deprecated: Use bigNatComplementBit# instead

setBitBigNat :: BigNat -> Int# -> BigNat Source #

Deprecated: Use bigNatSetBit# instead

andBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatAnd instead

xorBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatXor instead

popCountBigNat :: BigNat -> Int# Source #

Deprecated: Use bigNatPopCount# instead

orBigNat :: BigNat -> BigNat -> BigNat Source #

Deprecated: Use bigNatOr instead

bitBigNat :: Int# -> BigNat Source #

Deprecated: Use bigNatBit# instead

BigNat comparison predicates

isZeroBigNat :: BigNat -> Bool Source #

Deprecated: Use bigNatIsZero instead

compareBigNatWord :: BigNat -> GmpLimb# -> Ordering Source #

Deprecated: Use bigNatCompareWord# instead

compareBigNat :: BigNat -> BigNat -> Ordering Source #

Deprecated: Use bigNatCompare instead

eqBigNatWord :: BigNat -> GmpLimb# -> Bool Source #

Deprecated: Use bigNatEqWord# instead

eqBigNatWord# :: BigNat -> GmpLimb# -> Int# Source #

Deprecated: Use bigNatEqWord# instead

eqBigNat :: BigNat -> BigNat -> Bool Source #

Deprecated: Use bigNatEq instead

eqBigNat# :: BigNat -> BigNat -> Int# Source #

Deprecated: Use bigNatEq# instead

gtBigNatWord# :: BigNat -> GmpLimb# -> Int# Source #

Deprecated: Use bigNatGtWord# instead

Import/export functions

Compute size of serialisation

sizeInBaseBigNat :: BigNat -> Int# -> Word# Source #

Deprecated: Use bigNatSizeInBase# instead

sizeInBaseInteger :: Integer -> Int# -> Word# Source #

Deprecated: Use integerSizeInBase# instead

sizeInBaseWord# :: Word# -> Int# -> Word# Source #

Deprecated: Use wordSizeInBase# instead

Export

exportBigNatToAddr :: BigNat -> Addr# -> Int# -> IO Word Source #

Deprecated: Use bigNatToAddr# instead

exportIntegerToAddr :: Integer -> Addr# -> Int# -> IO Word Source #

Deprecated: Use integerToAddr# instead

exportBigNatToMutableByteArray :: BigNat -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word Source #

Deprecated: Use bigNatToMutableByteArray# instead

exportIntegerToMutableByteArray :: Integer -> MutableByteArray# RealWorld -> Word# -> Int# -> IO Word Source #

Deprecated: Use integerToMutableByteArray# instead

Import

importBigNatFromAddr :: Addr# -> Word# -> Int# -> IO BigNat Source #

Deprecated: Use bigNatFromAddr# instead

importIntegerFromAddr :: Addr# -> Word# -> Int# -> IO Integer Source #

Deprecated: Use integerFromAddr# instead

importBigNatFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> BigNat Source #

Deprecated: Use bigNatFromByteArray# instead

importIntegerFromByteArray :: ByteArray# -> Word# -> Word# -> Int# -> Integer Source #

Deprecated: Use integerFromByteArray# instead