Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
int8ToInt# :: Int8# -> Int# Source #
intToInt8# :: Int# -> Int8# Source #
negateInt8# :: Int8# -> Int8# Source #
int8ToWord8# :: Int8# -> Word8# Source #
word8ToWord# :: Word8# -> Word# Source #
wordToWord8# :: Word# -> Word8# Source #
word8ToInt8# :: Word8# -> Int8# Source #
int16ToInt# :: Int16# -> Int# Source #
intToInt16# :: Int# -> Int16# Source #
negateInt16# :: Int16# -> Int16# Source #
int16ToWord16# :: Int16# -> Word16# Source #
word16ToWord# :: Word16# -> Word# Source #
wordToWord16# :: Word# -> Word16# Source #
notWord16# :: Word16# -> Word16# Source #
word16ToInt16# :: Word16# -> Int16# Source #
int32ToInt# :: Int32# -> Int# Source #
intToInt32# :: Int# -> Int32# Source #
negateInt32# :: Int32# -> Int32# Source #
int32ToWord32# :: Int32# -> Word32# Source #
word32ToWord# :: Word32# -> Word# Source #
wordToWord32# :: Word# -> Word32# Source #
notWord32# :: Word32# -> Word32# Source #
word32ToInt32# :: Word32# -> Int32# Source #
negateInt# :: Int# -> Int# Source #
int2Float# :: Int# -> Float# Source #
int2Double# :: Int# -> Double# Source #
word2Float# :: Word# -> Float# Source #
word2Double# :: Word# -> Double# Source #
byteSwap16# :: Word# -> Word# Source #
byteSwap32# :: Word# -> Word# Source #
byteSwap64# :: Word# -> Word# Source #
bitReverse8# :: Word# -> Word# Source #
bitReverse16# :: Word# -> Word# Source #
bitReverse32# :: Word# -> Word# Source #
bitReverse64# :: Word# -> Word# Source #
bitReverse# :: Word# -> Word# Source #
narrow8Int# :: Int# -> Int# Source #
narrow16Int# :: Int# -> Int# Source #
narrow32Int# :: Int# -> Int# Source #
narrow8Word# :: Word# -> Word# Source #
narrow16Word# :: Word# -> Word# Source #
narrow32Word# :: Word# -> Word# Source #
negateDouble# :: Double# -> Double# Source #
fabsDouble# :: Double# -> Double# Source #
double2Int# :: Double# -> Int# Source #
double2Float# :: Double# -> Float# Source #
expDouble# :: Double# -> Double# Source #
expm1Double# :: Double# -> Double# Source #
logDouble# :: Double# -> Double# Source #
log1pDouble# :: Double# -> Double# Source #
sqrtDouble# :: Double# -> Double# Source #
sinDouble# :: Double# -> Double# Source #
cosDouble# :: Double# -> Double# Source #
tanDouble# :: Double# -> Double# Source #
asinDouble# :: Double# -> Double# Source #
acosDouble# :: Double# -> Double# Source #
atanDouble# :: Double# -> Double# Source #
sinhDouble# :: Double# -> Double# Source #
coshDouble# :: Double# -> Double# Source #
tanhDouble# :: Double# -> Double# Source #
asinhDouble# :: Double# -> Double# Source #
acoshDouble# :: Double# -> Double# Source #
atanhDouble# :: Double# -> Double# Source #
negateFloat# :: Float# -> Float# Source #
fabsFloat# :: Float# -> Float# Source #
float2Int# :: Float# -> Int# Source #
expm1Float# :: Float# -> Float# Source #
log1pFloat# :: Float# -> Float# Source #
sqrtFloat# :: Float# -> Float# Source #
asinFloat# :: Float# -> Float# Source #
acosFloat# :: Float# -> Float# Source #
atanFloat# :: Float# -> Float# Source #
sinhFloat# :: Float# -> Float# Source #
coshFloat# :: Float# -> Float# Source #
tanhFloat# :: Float# -> Float# Source #
asinhFloat# :: Float# -> Float# Source #
acoshFloat# :: Float# -> Float# Source #
atanhFloat# :: Float# -> Float# Source #
float2Double# :: Float# -> Double# Source #
sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> Int# Source #
readArray# :: MutableArray# s a -> Int# -> State# s -> (# State# s, a #) Source #
writeArray# :: MutableArray# s a -> Int# -> a -> State# s -> State# s Source #
sizeofArray# :: Array# a -> Int# Source #
sizeofMutableArray# :: MutableArray# s a -> Int# Source #
indexArray# :: Array# a -> Int# -> (# a #) Source #
unsafeFreezeArray# :: MutableArray# s a -> State# s -> (# State# s, Array# a #) Source #
unsafeThawArray# :: Array# a -> State# s -> (# State# s, MutableArray# s a #) Source #
copyArray# :: Array# a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s Source #
copyMutableArray# :: MutableArray# s a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s Source #
cloneMutableArray# :: MutableArray# s a -> Int# -> Int# -> State# s -> (# State# s, MutableArray# s a #) Source #
freezeArray# :: MutableArray# s a -> Int# -> Int# -> State# s -> (# State# s, Array# a #) Source #
thawArray# :: Array# a -> Int# -> Int# -> State# s -> (# State# s, MutableArray# s a #) Source #
newSmallArray# :: Int# -> a -> State# s -> (# State# s, SmallMutableArray# s a #) Source #
sameSmallMutableArray# :: SmallMutableArray# s a -> SmallMutableArray# s a -> Int# Source #
shrinkSmallMutableArray# :: SmallMutableArray# s a -> Int# -> State# s -> State# s Source #
readSmallArray# :: SmallMutableArray# s a -> Int# -> State# s -> (# State# s, a #) Source #
writeSmallArray# :: SmallMutableArray# s a -> Int# -> a -> State# s -> State# s Source #
sizeofSmallArray# :: SmallArray# a -> Int# Source #
sizeofSmallMutableArray# :: SmallMutableArray# s a -> Int# Source #
getSizeofSmallMutableArray# :: SmallMutableArray# s a -> State# s -> (# State# s, Int# #) Source #
indexSmallArray# :: SmallArray# a -> Int# -> (# a #) Source #
unsafeFreezeSmallArray# :: SmallMutableArray# s a -> State# s -> (# State# s, SmallArray# a #) Source #
unsafeThawSmallArray# :: SmallArray# a -> State# s -> (# State# s, SmallMutableArray# s a #) Source #
copySmallArray# :: SmallArray# a -> Int# -> SmallMutableArray# s a -> Int# -> Int# -> State# s -> State# s Source #
copySmallMutableArray# :: SmallMutableArray# s a -> Int# -> SmallMutableArray# s a -> Int# -> Int# -> State# s -> State# s Source #
cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a Source #
cloneSmallMutableArray# :: SmallMutableArray# s a -> Int# -> Int# -> State# s -> (# State# s, SmallMutableArray# s a #) Source #
freezeSmallArray# :: SmallMutableArray# s a -> Int# -> Int# -> State# s -> (# State# s, SmallArray# a #) Source #
thawSmallArray# :: SmallArray# a -> Int# -> Int# -> State# s -> (# State# s, SmallMutableArray# s a #) Source #
casSmallArray# :: SmallMutableArray# s a -> Int# -> a -> a -> State# s -> (# State# s, Int#, a #) Source #
newByteArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
newPinnedByteArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
newAlignedPinnedByteArray# :: Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
isByteArrayPinned# :: ByteArray# -> Int# Source #
byteArrayContents# :: ByteArray# -> Addr# Source #
sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int# Source #
shrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
resizeMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (# State# s, ByteArray# #) Source #
sizeofByteArray# :: ByteArray# -> Int# Source #
getSizeofMutableByteArray# :: MutableByteArray# s -> State# s -> (# State# s, Int# #) Source #
indexCharArray# :: ByteArray# -> Int# -> Char# Source #
indexWideCharArray# :: ByteArray# -> Int# -> Char# Source #
indexIntArray# :: ByteArray# -> Int# -> Int# Source #
indexWordArray# :: ByteArray# -> Int# -> Word# Source #
indexAddrArray# :: ByteArray# -> Int# -> Addr# Source #
indexFloatArray# :: ByteArray# -> Int# -> Float# Source #
indexDoubleArray# :: ByteArray# -> Int# -> Double# Source #
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a Source #
indexInt8Array# :: ByteArray# -> Int# -> Int8# Source #
indexInt16Array# :: ByteArray# -> Int# -> Int16# Source #
indexInt32Array# :: ByteArray# -> Int# -> Int32# Source #
indexInt64Array# :: ByteArray# -> Int# -> Int# Source #
indexWord8Array# :: ByteArray# -> Int# -> Word8# Source #
indexWord16Array# :: ByteArray# -> Int# -> Word16# Source #
indexWord32Array# :: ByteArray# -> Int# -> Word32# Source #
indexWord64Array# :: ByteArray# -> Int# -> Word# Source #
indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# Source #
indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# Source #
indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# Source #
indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# Source #
indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# Source #
indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# Source #
indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# Source #
indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a Source #
indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16# Source #
indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32# Source #
indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int# Source #
indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16# Source #
indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32# Source #
indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word# Source #
readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #) Source #
readWideCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #) Source #
readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #) Source #
readWordArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #) Source #
readAddrArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #) Source #
readFloatArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #) Source #
readDoubleArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #) Source #
readStablePtrArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, StablePtr# a #) Source #
readInt8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int8# #) Source #
readInt16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16# #) Source #
readInt32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32# #) Source #
readInt64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #) Source #
readWord8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word8# #) Source #
readWord16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16# #) Source #
readWord32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32# #) Source #
readWord64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #) Source #
readWord8ArrayAsChar# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #) Source #
readWord8ArrayAsWideChar# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #) Source #
readWord8ArrayAsInt# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #) Source #
readWord8ArrayAsWord# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #) Source #
readWord8ArrayAsAddr# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #) Source #
readWord8ArrayAsFloat# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #) Source #
readWord8ArrayAsDouble# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #) Source #
readWord8ArrayAsStablePtr# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, StablePtr# a #) Source #
readWord8ArrayAsInt16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16# #) Source #
readWord8ArrayAsInt32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32# #) Source #
readWord8ArrayAsInt64# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #) Source #
readWord8ArrayAsWord16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16# #) Source #
readWord8ArrayAsWord32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32# #) Source #
readWord8ArrayAsWord64# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #) Source #
writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s Source #
writeWideCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s Source #
writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeWordArray# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeAddrArray# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s Source #
writeFloatArray# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s Source #
writeDoubleArray# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s Source #
writeStablePtrArray# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s Source #
writeInt8Array# :: MutableByteArray# s -> Int# -> Int8# -> State# s -> State# s Source #
writeInt16Array# :: MutableByteArray# s -> Int# -> Int16# -> State# s -> State# s Source #
writeInt32Array# :: MutableByteArray# s -> Int# -> Int32# -> State# s -> State# s Source #
writeInt64Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeWord8Array# :: MutableByteArray# s -> Int# -> Word8# -> State# s -> State# s Source #
writeWord16Array# :: MutableByteArray# s -> Int# -> Word16# -> State# s -> State# s Source #
writeWord32Array# :: MutableByteArray# s -> Int# -> Word32# -> State# s -> State# s Source #
writeWord64Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeWord8ArrayAsChar# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s Source #
writeWord8ArrayAsWideChar# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s Source #
writeWord8ArrayAsInt# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeWord8ArrayAsWord# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeWord8ArrayAsAddr# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s Source #
writeWord8ArrayAsFloat# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s Source #
writeWord8ArrayAsDouble# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s Source #
writeWord8ArrayAsStablePtr# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s Source #
writeWord8ArrayAsInt16# :: MutableByteArray# s -> Int# -> Int16# -> State# s -> State# s Source #
writeWord8ArrayAsInt32# :: MutableByteArray# s -> Int# -> Int32# -> State# s -> State# s Source #
writeWord8ArrayAsInt64# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeWord8ArrayAsWord16# :: MutableByteArray# s -> Int# -> Word16# -> State# s -> State# s Source #
writeWord8ArrayAsWord32# :: MutableByteArray# s -> Int# -> Word32# -> State# s -> State# s Source #
writeWord8ArrayAsWord64# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# Source #
copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
copyMutableByteArray# :: MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# s -> State# s Source #
copyMutableByteArrayToAddr# :: MutableByteArray# s -> Int# -> Addr# -> Int# -> State# s -> State# s Source #
copyAddrToByteArray# :: Addr# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> State# s Source #
atomicReadIntArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #) Source #
atomicWriteIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
casIntArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> (# State# s, Int# #) Source #
fetchAddIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) Source #
fetchSubIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) Source #
fetchAndIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) Source #
fetchNandIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) Source #
fetchOrIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) Source #
fetchXorIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) Source #
newArrayArray# :: Int# -> State# s -> (# State# s, MutableArrayArray# s #) Source #
sameMutableArrayArray# :: MutableArrayArray# s -> MutableArrayArray# s -> Int# Source #
unsafeFreezeArrayArray# :: MutableArrayArray# s -> State# s -> (# State# s, ArrayArray# #) Source #
sizeofArrayArray# :: ArrayArray# -> Int# Source #
indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray# Source #
indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray# Source #
readByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, ByteArray# #) Source #
readMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
readArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, ArrayArray# #) Source #
readMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s, MutableArrayArray# s #) Source #
writeByteArrayArray# :: MutableArrayArray# s -> Int# -> ByteArray# -> State# s -> State# s Source #
writeMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> MutableByteArray# s -> State# s -> State# s Source #
writeArrayArrayArray# :: MutableArrayArray# s -> Int# -> ArrayArray# -> State# s -> State# s Source #
writeMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> State# s -> State# s Source #
copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s Source #
copyMutableArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s Source #
indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source #
readStablePtrOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, StablePtr# a #) Source #
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# s -> State# s Source #
catch# :: (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
maskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
maskUninterruptible# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
unmaskAsyncExceptions# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
atomically# :: (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
catchRetry# :: (State# RealWorld -> (# State# RealWorld, a #)) -> (State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
catchSTM# :: (State# RealWorld -> (# State# RealWorld, a #)) -> (b -> State# RealWorld -> (# State# RealWorld, a #)) -> State# RealWorld -> (# State# RealWorld, a #) Source #
noDuplicate# :: State# s -> State# s Source #
mkWeak# :: o -> b -> (State# RealWorld -> (# State# RealWorld, c #)) -> State# RealWorld -> (# State# RealWorld, Weak# b #) Source #
addCFinalizerToWeak# :: Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# RealWorld -> (# State# RealWorld, Int# #) Source #
finalizeWeak# :: Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) Source #
makeStablePtr# :: a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #) Source #
deRefStablePtr# :: StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #) Source #
eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int# Source #
makeStableName# :: a -> State# RealWorld -> (# State# RealWorld, StableName# a #) Source #
eqStableName# :: StableName# a -> StableName# b -> Int# Source #
stableNameToInt# :: StableName# a -> Int# Source #
compactGetFirstBlock# :: Compact# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) Source #
compactGetNextBlock# :: Compact# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr#, Word# #) Source #
compactAllocateBlock# :: Word# -> Addr# -> State# RealWorld -> (# State# RealWorld, Addr# #) Source #
compactFixupPointers# :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Compact#, Addr# #) Source #
reallyUnsafePtrEquality# :: a -> a -> Int# Source #
dataToTag# :: a -> Int# Source #
addrToAny# :: Addr# -> (# a #) Source #
newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# s -> (# State# s, BCO #) Source #
unpackClosure# :: a -> (# Addr#, ByteArray#, Array# b #) Source #
closureSize# :: a -> Int# Source #
getApStackVal# :: a -> Int# -> (# Int#, b #) Source #
prefetchByteArray3# :: ByteArray# -> Int# -> State# s -> State# s Source #
prefetchMutableByteArray3# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
prefetchValue3# :: a -> State# s -> State# s Source #
prefetchByteArray2# :: ByteArray# -> Int# -> State# s -> State# s Source #
prefetchMutableByteArray2# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
prefetchValue2# :: a -> State# s -> State# s Source #
prefetchByteArray1# :: ByteArray# -> Int# -> State# s -> State# s Source #
prefetchMutableByteArray1# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
prefetchValue1# :: a -> State# s -> State# s Source #
prefetchByteArray0# :: ByteArray# -> Int# -> State# s -> State# s Source #
prefetchMutableByteArray0# :: MutableByteArray# s -> Int# -> State# s -> State# s Source #
prefetchValue0# :: a -> State# s -> State# s Source #