| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.PrimopWrappers
Documentation
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 #
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 #
logDouble# :: 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 #
negateFloat# :: Float# -> Float# Source #
fabsFloat# :: Float# -> Float# Source #
float2Int# :: Float# -> Int# 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 #
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 #
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 #
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# -> Int# Source #
indexInt16Array# :: ByteArray# -> Int# -> Int# Source #
indexInt32Array# :: ByteArray# -> Int# -> Int# Source #
indexInt64Array# :: ByteArray# -> Int# -> Int# Source #
indexWord8Array# :: ByteArray# -> Int# -> Word# Source #
indexWord16Array# :: ByteArray# -> Int# -> Word# Source #
indexWord32Array# :: ByteArray# -> Int# -> Word# Source #
indexWord64Array# :: 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, Int##) Source #
readInt16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
readInt32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
readInt64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##) Source #
readWord8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##) Source #
readWord16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##) Source #
readWord32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##) Source #
readWord64Array# :: 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# -> Int# -> State# s -> State# s Source #
writeInt16Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeInt32Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeInt64Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
writeWord8Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeWord16Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeWord32Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s Source #
writeWord64Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s 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 #
check# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> State# RealWorld 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 #
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#, Array# b, ByteArray##) 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 #