ghc-bignum-1.2: GHC BigNum library
Safe HaskellNone
LanguageHaskell2010

GHC.Num.Primitives

Synopsis

Bool#

(&&#) :: Bool# -> Bool# -> Bool# infixr 3 Source #

(||#) :: Bool# -> Bool# -> Bool# infixr 2 Source #

Int#

sgnI# :: Int# -> Int# Source #

Branchless signum

absI# :: Int# -> Int# Source #

Branchless abs

cmpI# :: Int# -> Int# -> Int# Source #

Branchless comparison

intEncodeDouble# :: Int# -> Int# -> Double# Source #

Encode (# Int# mantissa, Int# exponent #) into a Double#.

(provided by GHC's RTS)

popCntI# :: Int# -> Word# Source #

Population count

Word#

shiftRW# :: Word# -> Word# -> Word# Source #

Safe right shift for Word#

plusWord3# :: Word# -> Word# -> Word# -> (# Word#, Word# #) Source #

Add 3 values together

plusWord12# :: Word# -> (# Word#, Word# #) -> (# Word#, Word# #) Source #

(h,l) <- a + (hb,lb)

quotRemWord3# :: (# Word#, Word# #) -> Word# -> (# (# Word#, Word# #), Word# #) Source #

2-by-1 large division

Requires: b0 /= 0 a1 >= b0 (not required, but if not q1=0)

wordFromAbsInt# :: Int# -> Word# Source #

Return the absolute value of the Int# in a Word#

wordLog2# :: Word# -> Word# Source #

Compute base-2 log of Word#

This is internally implemented as count-leading-zeros machine instruction.

wordLogBase# :: Word# -> Word# -> Word# Source #

Logarithm for an arbitrary base

wordIsPowerOf2# :: Word# -> (# (# #) | Word# #) Source #

Indicate if the value is a power of two and which one

wordEncodeDouble# :: Word# -> Int# -> Double# Source #

Encode (# Word# mantissa, Int# exponent #) into a Double#.

(provided by GHC's RTS)

wordReverseBits# :: Word# -> Word# Source #

Reverse bits in a Word#

wordReverseBits32# :: Word# -> Word# Source #

Reverse bits in the Word32 subwords composing a Word#

wordReverseBytes# :: Word# -> Word# Source #

Reverse bytes in a Word#

Addr import/export

wordFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Word# #) Source #

Read a Word from addr in base-256 representation.

@n is the number of bytes to read.

The endianness is selected with the Bool# parameter: write most significant byte first (big-endian) if 1# or least significant byte first (little-endian) if 0#.

wordFromAddrLE# :: Word# -> Addr# -> State# s -> (# State# s, Word# #) Source #

Read a Word from addr in base-256 little-endian representation.

@n is the number of bytes to read.

wordFromAddrBE# :: Word# -> Addr# -> State# s -> (# State# s, Word# #) Source #

Read a Word from addr in base-256 big-endian representation.

@n is the number of bytes to read.

wordToAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Word# #) Source #

Write a Word to addr in base-256 representation and return the number of bytes written.

The endianness is selected with the Bool# parameter: write most significant byte first (big-endian) if 1# or least significant byte first (little-endian) if 0#.

wordToAddrLE# :: Word# -> Addr# -> State# s -> (# State# s, Word# #) Source #

Write a Word to addr in base-256 little-endian representation and return the number of bytes written.

wordToAddrBE# :: Word# -> Addr# -> State# s -> (# State# s, Word# #) Source #

Write a Word to addr in base-256 big-endian representation and return the number of bytes written.

wordWriteAddrLE# :: Word# -> Addr# -> State# s -> State# s Source #

Write a full word with little-endian encoding

wordWriteAddrBE# :: Word# -> Addr# -> State# s -> State# s Source #

Write a full word with little-endian encoding

ByteArray import/export

wordFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> Word# Source #

Read a Word from ByteArray in base-256 representation.

@n is the number of bytes to read.

The endianness is selected with the Bool# parameter: write most significant byte first (big-endian) if 1# or least significant byte first (little-endian) if 0#.

wordFromByteArrayLE# :: Word# -> ByteArray# -> Word# -> Word# Source #

Read a Word from ByteArray in base-256 little-endian representation.

@n is the number of bytes to read.

wordFromByteArrayBE# :: Word# -> ByteArray# -> Word# -> Word# Source #

Read a Word from ByteArray in base-256 big-endian representation.

@n is the number of bytes to read.

wordToMutableByteArray# :: Word# -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #) Source #

Write a Word to MutableByteArray in base-256 representation and return the number of bytes written.

The endianness is selected with the Bool# parameter: write most significant byte first (big-endian) if 1# or least significant byte first (little-endian) if 0#.

The offset is in bytes.

wordToMutableByteArrayLE# :: Word# -> MutableByteArray# s -> Word# -> State# s -> (# State# s, Word# #) Source #

Write a Word to MutableByteArray in base-256 little-endian representation and return the number of bytes written.

The offset is in bytes.

wordToMutableByteArrayBE# :: Word# -> MutableByteArray# s -> Word# -> State# s -> (# State# s, Word# #) Source #

Write a Word to MutableByteArray in base-256 big-endian representation and return the number of bytes written.

The offset is in bytes.

wordWriteMutableByteArrayLE# :: Word# -> MutableByteArray# s -> Word# -> State# s -> State# s Source #

Write a full word with little-endian encoding

wordWriteMutableByteArrayBE# :: Word# -> MutableByteArray# s -> Word# -> State# s -> State# s Source #

Write a full word with little-endian encoding

Exception

IO