Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
mulIntMayOflo# :: Int# -> Int# -> Int# Source
negateInt# :: Int# -> Int# Source
int2Float# :: Int# -> Float# Source
int2Double# :: Int# -> Double# Source
word2Float# :: Word# -> Float# Source
word2Double# :: Word# -> Double# Source
uncheckedIShiftL# :: Int# -> Int# -> Int# Source
uncheckedIShiftRA# :: Int# -> Int# -> Int# Source
uncheckedIShiftRL# :: Int# -> Int# -> Int# Source
minusWord# :: Word# -> Word# -> Word# Source
timesWord# :: Word# -> Word# -> Word# Source
uncheckedShiftL# :: Word# -> Int# -> Word# Source
uncheckedShiftRL# :: Word# -> Int# -> Word# 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
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
plusFloat# :: Float# -> Float# -> Float# Source
minusFloat# :: Float# -> Float# -> Float# Source
timesFloat# :: Float# -> Float# -> Float# Source
divideFloat# :: Float# -> Float# -> Float# Source
negateFloat# :: 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
powerFloat# :: Float# -> Float# -> Float# Source
float2Double# :: Float# -> Double# Source
decodeFloat_Int# :: Float# -> (#Int#, Int##) 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
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
sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int# Source
unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (#State# s, ByteArray##) Source
sizeofByteArray# :: ByteArray# -> 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
casIntArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> (#State# s, Int##) Source
fetchAddIntArray# :: 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
indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray# 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
minusAddr# :: Addr# -> Addr# -> Int# Source
indexCharOffAddr# :: Addr# -> Int# -> Char# Source
indexWideCharOffAddr# :: Addr# -> Int# -> Char# Source
indexIntOffAddr# :: Addr# -> Int# -> Int# Source
indexWordOffAddr# :: Addr# -> Int# -> Word# Source
indexAddrOffAddr# :: Addr# -> Int# -> Addr# Source
indexFloatOffAddr# :: Addr# -> Int# -> Float# Source
indexDoubleOffAddr# :: Addr# -> Int# -> Double# Source
indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a Source
indexInt8OffAddr# :: Addr# -> Int# -> Int# Source
indexInt16OffAddr# :: Addr# -> Int# -> Int# Source
indexInt32OffAddr# :: Addr# -> Int# -> Int# Source
indexInt64OffAddr# :: Addr# -> Int# -> Int# Source
indexWord8OffAddr# :: Addr# -> Int# -> Word# Source
indexWord16OffAddr# :: Addr# -> Int# -> Word# Source
indexWord32OffAddr# :: Addr# -> Int# -> Word# Source
indexWord64OffAddr# :: Addr# -> Int# -> Word# Source
readStablePtrOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, StablePtr# a#) Source
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# s -> State# s Source
newMutVar# :: a -> State# s -> (#State# s, MutVar# s a#) Source
readMutVar# :: MutVar# s a -> State# s -> (#State# s, a#) Source
writeMutVar# :: MutVar# s a -> a -> State# s -> State# s Source
sameMutVar# :: MutVar# s a -> MutVar# s a -> Int# Source
atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (#State# s, c#) 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
readTVarIO# :: TVar# s a -> State# s -> (#State# s, a#) Source
writeTVar# :: TVar# s a -> a -> State# s -> State# s Source
waitWrite# :: Int# -> State# s -> State# s 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, ()#)#) 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
reallyUnsafePtrEquality# :: a -> a -> Int# Source
numSparks# :: State# s -> (#State# s, 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
getCurrentCCS# :: a -> State# s -> (#State# s, Addr##) Source
traceEvent# :: Addr# -> State# s -> State# s Source
traceMarker# :: Addr# -> State# s -> State# s Source
prefetchByteArray3# :: ByteArray# -> Int# -> ByteArray# Source
prefetchMutableByteArray3# :: MutableByteArray# s -> Int# -> State# s -> State# s Source
prefetchAddr3# :: Addr# -> Int# -> Addr# Source
prefetchByteArray2# :: ByteArray# -> Int# -> ByteArray# Source
prefetchMutableByteArray2# :: MutableByteArray# s -> Int# -> State# s -> State# s Source
prefetchAddr2# :: Addr# -> Int# -> Addr# Source
prefetchByteArray1# :: ByteArray# -> Int# -> ByteArray# Source
prefetchMutableByteArray1# :: MutableByteArray# s -> Int# -> State# s -> State# s Source
prefetchAddr1# :: Addr# -> Int# -> Addr# Source
prefetchByteArray0# :: ByteArray# -> Int# -> ByteArray# Source
prefetchMutableByteArray0# :: MutableByteArray# s -> Int# -> State# s -> State# s Source
prefetchAddr0# :: Addr# -> Int# -> Addr# Source