Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Bool# = Int#
- (&&#) :: Bool# -> Bool# -> Bool#
- (||#) :: Bool# -> Bool# -> Bool#
- notB# :: Bool# -> Bool#
- testBitI# :: Int# -> Word# -> Bool#
- minI# :: Int# -> Int# -> Int#
- maxI# :: Int# -> Int# -> Int#
- sgnI# :: Int# -> Int#
- absI# :: Int# -> Int#
- cmpI# :: Int# -> Int# -> Int#
- intEncodeDouble# :: Int# -> Int# -> Double#
- popCntI# :: Int# -> Word#
- andNot# :: Word# -> Word# -> Word#
- cmpW# :: Word# -> Word# -> Ordering
- bitW# :: Int# -> Word#
- maxW# :: Word# -> Word# -> Word#
- minW# :: Word# -> Word# -> Word#
- testBitW# :: Word# -> Word# -> Bool#
- shiftRW# :: Word# -> Word# -> Word#
- plusWord3# :: Word# -> Word# -> Word# -> (# Word#, Word# #)
- plusWord12# :: Word# -> (# Word#, Word# #) -> (# Word#, Word# #)
- quotRemWord3# :: (# Word#, Word# #) -> Word# -> (# (# Word#, Word# #), Word# #)
- wordFromAbsInt# :: Int# -> Word#
- wordLog2# :: Word# -> Word#
- wordLogBase# :: Word# -> Word# -> Word#
- wordSizeInBase# :: Word# -> Word# -> Word#
- wordIsPowerOf2# :: Word# -> (# (# #) | Word# #)
- wordEncodeDouble# :: Word# -> Int# -> Double#
- wordReverseBits# :: Word# -> Word#
- wordReverseBits32# :: Word# -> Word#
- wordReverseBytes# :: Word# -> Word#
- wordFromAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Word# #)
- wordFromAddrLE# :: Word# -> Addr# -> State# s -> (# State# s, Word# #)
- wordFromAddrBE# :: Word# -> Addr# -> State# s -> (# State# s, Word# #)
- wordToAddr# :: Word# -> Addr# -> Bool# -> State# s -> (# State# s, Word# #)
- wordToAddrLE# :: Word# -> Addr# -> State# s -> (# State# s, Word# #)
- wordToAddrBE# :: Word# -> Addr# -> State# s -> (# State# s, Word# #)
- wordWriteAddrLE# :: Word# -> Addr# -> State# s -> State# s
- wordWriteAddrBE# :: Word# -> Addr# -> State# s -> State# s
- wordFromByteArray# :: Word# -> ByteArray# -> Word# -> Bool# -> Word#
- wordFromByteArrayLE# :: Word# -> ByteArray# -> Word# -> Word#
- wordFromByteArrayBE# :: Word# -> ByteArray# -> Word# -> Word#
- wordToMutableByteArray# :: Word# -> MutableByteArray# s -> Word# -> Bool# -> State# s -> (# State# s, Word# #)
- wordToMutableByteArrayLE# :: Word# -> MutableByteArray# s -> Word# -> State# s -> (# State# s, Word# #)
- wordToMutableByteArrayBE# :: Word# -> MutableByteArray# s -> Word# -> State# s -> (# State# s, Word# #)
- wordWriteMutableByteArrayLE# :: Word# -> MutableByteArray# s -> Word# -> State# s -> State# s
- wordWriteMutableByteArrayBE# :: Word# -> MutableByteArray# s -> Word# -> State# s -> State# s
- raiseUnderflow :: a
- raiseUnderflow_Word# :: Void# -> Word#
- raiseDivZero :: a
- raiseDivZero_Word# :: Void# -> Word#
- unexpectedValue :: a
- unexpectedValue_Int# :: Void# -> Int#
- unexpectedValue_Word# :: Void# -> Word#
- ioWord# :: IO Word -> State# RealWorld -> (# State# RealWorld, Word# #)
- ioInt# :: IO Int -> State# RealWorld -> (# State# RealWorld, Int# #)
- ioVoid :: IO a -> State# RealWorld -> State# RealWorld
- ioBool :: IO Bool -> State# RealWorld -> (# State# RealWorld, Bool# #)
Bool#
Int#
intEncodeDouble# :: Int# -> Int# -> Double# Source #
Encode (# Int# mantissa, Int# exponent #) into a Double#.
(provided by GHC's RTS)
Word#
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.
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
raiseUnderflow :: a Source #
Raise underflowException
raiseUnderflow_Word# :: Void# -> Word# Source #
raiseDivZero :: a Source #
Raise divZeroException
raiseDivZero_Word# :: Void# -> Word# Source #
unexpectedValue :: a Source #
unexpectedValue_Int# :: Void# -> Int# Source #
unexpectedValue_Word# :: Void# -> Word# Source #