ghc-prim-0.1.0.0: GHC primitivesContentsIndex
GHC.PrimopWrappers
Documentation
gtChar# :: Char# -> Char# -> Bool
geChar# :: Char# -> Char# -> Bool
eqChar# :: Char# -> Char# -> Bool
neChar# :: Char# -> Char# -> Bool
ltChar# :: Char# -> Char# -> Bool
leChar# :: Char# -> Char# -> Bool
ord# :: Char# -> Int#
(+#) :: Int# -> Int# -> Int#
(-#) :: Int# -> Int# -> Int#
(*#) :: Int# -> Int# -> Int#
mulIntMayOflo# :: Int# -> Int# -> Int#
quotInt# :: Int# -> Int# -> Int#
remInt# :: Int# -> Int# -> Int#
gcdInt# :: Int# -> Int# -> Int#
negateInt# :: Int# -> Int#
addIntC# :: Int# -> Int# -> (#Int#, Int##)
subIntC# :: Int# -> Int# -> (#Int#, Int##)
(>#) :: Int# -> Int# -> Bool
(>=#) :: Int# -> Int# -> Bool
(==#) :: Int# -> Int# -> Bool
(/=#) :: Int# -> Int# -> Bool
(<#) :: Int# -> Int# -> Bool
(<=#) :: Int# -> Int# -> Bool
chr# :: Int# -> Char#
int2Word# :: Int# -> Word#
int2Float# :: Int# -> Float#
int2Double# :: Int# -> Double#
int2Integer# :: Int# -> (#Int#, ByteArray##)
uncheckedIShiftL# :: Int# -> Int# -> Int#
uncheckedIShiftRA# :: Int# -> Int# -> Int#
uncheckedIShiftRL# :: Int# -> Int# -> Int#
plusWord# :: Word# -> Word# -> Word#
minusWord# :: Word# -> Word# -> Word#
timesWord# :: Word# -> Word# -> Word#
quotWord# :: Word# -> Word# -> Word#
remWord# :: Word# -> Word# -> Word#
and# :: Word# -> Word# -> Word#
or# :: Word# -> Word# -> Word#
xor# :: Word# -> Word# -> Word#
not# :: Word# -> Word#
uncheckedShiftL# :: Word# -> Int# -> Word#
uncheckedShiftRL# :: Word# -> Int# -> Word#
word2Int# :: Word# -> Int#
word2Integer# :: Word# -> (#Int#, ByteArray##)
gtWord# :: Word# -> Word# -> Bool
geWord# :: Word# -> Word# -> Bool
eqWord# :: Word# -> Word# -> Bool
neWord# :: Word# -> Word# -> Bool
ltWord# :: Word# -> Word# -> Bool
leWord# :: Word# -> Word# -> Bool
narrow8Int# :: Int# -> Int#
narrow16Int# :: Int# -> Int#
narrow32Int# :: Int# -> Int#
narrow8Word# :: Word# -> Word#
narrow16Word# :: Word# -> Word#
narrow32Word# :: Word# -> Word#
int64ToInteger# :: Int64# -> (#Int#, ByteArray##)
word64ToInteger# :: Word64# -> (#Int#, ByteArray##)
plusInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
minusInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
timesInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
gcdInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
gcdIntegerInt# :: Int# -> ByteArray# -> Int# -> Int#
divExactInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
quotInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
remInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
cmpInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> Int#
cmpIntegerInt# :: Int# -> ByteArray# -> Int# -> Int#
quotRemInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray#, Int#, ByteArray##)
divModInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray#, Int#, ByteArray##)
integer2Int# :: Int# -> ByteArray# -> Int#
integer2Word# :: Int# -> ByteArray# -> Word#
andInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
orInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
xorInteger# :: Int# -> ByteArray# -> Int# -> ByteArray# -> (#Int#, ByteArray##)
complementInteger# :: Int# -> ByteArray# -> (#Int#, ByteArray##)
(>##) :: Double# -> Double# -> Bool
(>=##) :: Double# -> Double# -> Bool
(==##) :: Double# -> Double# -> Bool
(/=##) :: Double# -> Double# -> Bool
(<##) :: Double# -> Double# -> Bool
(<=##) :: Double# -> Double# -> Bool
(+##) :: Double# -> Double# -> Double#
(-##) :: Double# -> Double# -> Double#
(*##) :: Double# -> Double# -> Double#
(/##) :: Double# -> Double# -> Double#
negateDouble# :: Double# -> Double#
double2Int# :: Double# -> Int#
double2Float# :: Double# -> Float#
expDouble# :: Double# -> Double#
logDouble# :: Double# -> Double#
sqrtDouble# :: Double# -> Double#
sinDouble# :: Double# -> Double#
cosDouble# :: Double# -> Double#
tanDouble# :: Double# -> Double#
asinDouble# :: Double# -> Double#
acosDouble# :: Double# -> Double#
atanDouble# :: Double# -> Double#
sinhDouble# :: Double# -> Double#
coshDouble# :: Double# -> Double#
tanhDouble# :: Double# -> Double#
(**##) :: Double# -> Double# -> Double#
decodeDouble# :: Double# -> (#Int#, Int#, ByteArray##)
decodeDouble_2Int# :: Double# -> (#Int#, Word#, Word#, Int##)
gtFloat# :: Float# -> Float# -> Bool
geFloat# :: Float# -> Float# -> Bool
eqFloat# :: Float# -> Float# -> Bool
neFloat# :: Float# -> Float# -> Bool
ltFloat# :: Float# -> Float# -> Bool
leFloat# :: Float# -> Float# -> Bool
plusFloat# :: Float# -> Float# -> Float#
minusFloat# :: Float# -> Float# -> Float#
timesFloat# :: Float# -> Float# -> Float#
divideFloat# :: Float# -> Float# -> Float#
negateFloat# :: Float# -> Float#
float2Int# :: Float# -> Int#
expFloat# :: Float# -> Float#
logFloat# :: Float# -> Float#
sqrtFloat# :: Float# -> Float#
sinFloat# :: Float# -> Float#
cosFloat# :: Float# -> Float#
tanFloat# :: Float# -> Float#
asinFloat# :: Float# -> Float#
acosFloat# :: Float# -> Float#
atanFloat# :: Float# -> Float#
sinhFloat# :: Float# -> Float#
coshFloat# :: Float# -> Float#
tanhFloat# :: Float# -> Float#
powerFloat# :: Float# -> Float# -> Float#
float2Double# :: Float# -> Double#
decodeFloat# :: Float# -> (#Int#, Int#, ByteArray##)
decodeFloat_Int# :: Float# -> (#Int#, Int##)
newArray# :: Int# -> a -> State# s -> (#State# s, MutableArray# s a#)
sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> Bool
readArray# :: MutableArray# s a -> Int# -> State# s -> (#State# s, a#)
writeArray# :: MutableArray# s a -> Int# -> a -> State# s -> State# s
indexArray# :: Array# a -> Int# -> (#a#)
unsafeFreezeArray# :: MutableArray# s a -> State# s -> (#State# s, Array# a#)
unsafeThawArray# :: Array# a -> State# s -> (#State# s, MutableArray# s a#)
newByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#)
newPinnedByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#)
byteArrayContents# :: ByteArray# -> Addr#
sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Bool
unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (#State# s, ByteArray##)
sizeofByteArray# :: ByteArray# -> Int#
sizeofMutableByteArray# :: MutableByteArray# s -> Int#
indexCharArray# :: ByteArray# -> Int# -> Char#
indexWideCharArray# :: ByteArray# -> Int# -> Char#
indexIntArray# :: ByteArray# -> Int# -> Int#
indexWordArray# :: ByteArray# -> Int# -> Word#
indexAddrArray# :: ByteArray# -> Int# -> Addr#
indexFloatArray# :: ByteArray# -> Int# -> Float#
indexDoubleArray# :: ByteArray# -> Int# -> Double#
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
indexInt8Array# :: ByteArray# -> Int# -> Int#
indexInt16Array# :: ByteArray# -> Int# -> Int#
indexInt32Array# :: ByteArray# -> Int# -> Int#
indexInt64Array# :: ByteArray# -> Int# -> Int64#
indexWord8Array# :: ByteArray# -> Int# -> Word#
indexWord16Array# :: ByteArray# -> Int# -> Word#
indexWord32Array# :: ByteArray# -> Int# -> Word#
indexWord64Array# :: ByteArray# -> Int# -> Word64#
readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char##)
readWideCharArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char##)
readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
readWordArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
readAddrArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Addr##)
readFloatArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Float##)
readDoubleArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Double##)
readStablePtrArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, StablePtr# a#)
readInt8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
readInt16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
readInt32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int##)
readInt64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Int64##)
readWord8Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
readWord16Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
readWord32Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word##)
readWord64Array# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Word64##)
writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeWideCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeWordArray# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeAddrArray# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
writeFloatArray# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s
writeDoubleArray# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
writeStablePtrArray# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
writeInt8Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeInt16Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeInt32Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeInt64Array# :: MutableByteArray# s -> Int# -> Int64# -> State# s -> State# s
writeWord8Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWord16Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWord32Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWord64Array# :: MutableByteArray# s -> Int# -> Word64# -> State# s -> State# s
plusAddr# :: Addr# -> Int# -> Addr#
minusAddr# :: Addr# -> Addr# -> Int#
remAddr# :: Addr# -> Int# -> Int#
addr2Int# :: Addr# -> Int#
int2Addr# :: Int# -> Addr#
gtAddr# :: Addr# -> Addr# -> Bool
geAddr# :: Addr# -> Addr# -> Bool
eqAddr# :: Addr# -> Addr# -> Bool
neAddr# :: Addr# -> Addr# -> Bool
ltAddr# :: Addr# -> Addr# -> Bool
leAddr# :: Addr# -> Addr# -> Bool
indexCharOffAddr# :: Addr# -> Int# -> Char#
indexWideCharOffAddr# :: Addr# -> Int# -> Char#
indexIntOffAddr# :: Addr# -> Int# -> Int#
indexWordOffAddr# :: Addr# -> Int# -> Word#
indexAddrOffAddr# :: Addr# -> Int# -> Addr#
indexFloatOffAddr# :: Addr# -> Int# -> Float#
indexDoubleOffAddr# :: Addr# -> Int# -> Double#
indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a
indexInt8OffAddr# :: Addr# -> Int# -> Int#
indexInt16OffAddr# :: Addr# -> Int# -> Int#
indexInt32OffAddr# :: Addr# -> Int# -> Int#
indexInt64OffAddr# :: Addr# -> Int# -> Int64#
indexWord8OffAddr# :: Addr# -> Int# -> Word#
indexWord16OffAddr# :: Addr# -> Int# -> Word#
indexWord32OffAddr# :: Addr# -> Int# -> Word#
indexWord64OffAddr# :: Addr# -> Int# -> Word64#
readCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##)
readWideCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##)
readIntOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
readWordOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
readAddrOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Addr##)
readFloatOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Float##)
readDoubleOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Double##)
readStablePtrOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, StablePtr# a#)
readInt8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
readInt16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
readInt32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)
readInt64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int64##)
readWord8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
readWord16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
readWord32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)
readWord64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word64##)
writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# s
writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# s
writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# s -> State# s
writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# s -> State# s
writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# s -> State# s
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# s -> State# s
writeInt8OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeInt16OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeInt32OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeInt64OffAddr# :: Addr# -> Int# -> Int64# -> State# s -> State# s
writeWord8OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeWord16OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeWord32OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeWord64OffAddr# :: Addr# -> Int# -> Word64# -> State# s -> State# s
newMutVar# :: a -> State# s -> (#State# s, MutVar# s a#)
readMutVar# :: MutVar# s a -> State# s -> (#State# s, a#)
writeMutVar# :: MutVar# s a -> a -> State# s -> State# s
sameMutVar# :: MutVar# s a -> MutVar# s a -> Bool
atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (#State# s, c#)
catch# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
raise# :: a -> b
raiseIO# :: a -> State# RealWorld -> (#State# RealWorld, b#)
blockAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
unblockAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
asyncExceptionsBlocked# :: State# RealWorld -> (#State# RealWorld, Int##)
atomically# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
retry# :: State# RealWorld -> (#State# RealWorld, a#)
catchRetry# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
catchSTM# :: (State# RealWorld -> (#State# RealWorld, a#)) -> (b -> State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)
check# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, ()#)
newTVar# :: a -> State# s -> (#State# s, TVar# s a#)
readTVar# :: TVar# s a -> State# s -> (#State# s, a#)
writeTVar# :: TVar# s a -> a -> State# s -> State# s
sameTVar# :: TVar# s a -> TVar# s a -> Bool
newMVar# :: State# s -> (#State# s, MVar# s a#)
takeMVar# :: MVar# s a -> State# s -> (#State# s, a#)
tryTakeMVar# :: MVar# s a -> State# s -> (#State# s, Int#, a#)
putMVar# :: MVar# s a -> a -> State# s -> State# s
tryPutMVar# :: MVar# s a -> a -> State# s -> (#State# s, Int##)
sameMVar# :: MVar# s a -> MVar# s a -> Bool
isEmptyMVar# :: MVar# s a -> State# s -> (#State# s, Int##)
delay# :: Int# -> State# s -> State# s
waitRead# :: Int# -> State# s -> State# s
waitWrite# :: Int# -> State# s -> State# s
fork# :: a -> State# RealWorld -> (#State# RealWorld, ThreadId##)
forkOn# :: Int# -> a -> State# RealWorld -> (#State# RealWorld, ThreadId##)
killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorld
yield# :: State# RealWorld -> State# RealWorld
myThreadId# :: State# RealWorld -> (#State# RealWorld, ThreadId##)
labelThread# :: ThreadId# -> Addr# -> State# RealWorld -> State# RealWorld
isCurrentThreadBound# :: State# RealWorld -> (#State# RealWorld, Int##)
noDuplicate# :: State# RealWorld -> State# RealWorld
threadStatus# :: ThreadId# -> State# RealWorld -> (#State# RealWorld, Int##)
mkWeak# :: o -> b -> c -> State# RealWorld -> (#State# RealWorld, Weak# b#)
deRefWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, a#)
finalizeWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, State# RealWorld -> (#State# RealWorld, ()#)#)
touch# :: o -> State# RealWorld -> State# RealWorld
makeStablePtr# :: a -> State# RealWorld -> (#State# RealWorld, StablePtr# a#)
deRefStablePtr# :: StablePtr# a -> State# RealWorld -> (#State# RealWorld, a#)
eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int#
makeStableName# :: a -> State# RealWorld -> (#State# RealWorld, StableName# a#)
eqStableName# :: StableName# a -> StableName# a -> Int#
stableNameToInt# :: StableName# a -> Int#
reallyUnsafePtrEquality# :: a -> a -> Int#
dataToTag# :: a -> Int#
addrToHValue# :: Addr# -> (#a#)
mkApUpd0# :: BCO# -> (#a#)
newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# s -> (#State# s, BCO##)
unpackClosure# :: a -> (#Addr#, Array# b, ByteArray##)
getApStackVal# :: a -> Int# -> (#Int#, b#)
Produced by Haddock version 2.3.0