ghc-prim-0.2.0.0: GHC primitivesSource codeContentsIndex
GHC.PrimopWrappers
Documentation
gtChar# :: Char# -> Char# -> BoolSource
geChar# :: Char# -> Char# -> BoolSource
eqChar# :: Char# -> Char# -> BoolSource
neChar# :: Char# -> Char# -> BoolSource
ltChar# :: Char# -> Char# -> BoolSource
leChar# :: Char# -> Char# -> BoolSource
ord# :: Char# -> Int#Source
(+#) :: Int# -> Int# -> Int#Source
(-#) :: Int# -> Int# -> Int#Source
(*#) :: Int# -> Int# -> Int#Source
mulIntMayOflo# :: Int# -> Int# -> Int#Source
quotInt# :: Int# -> Int# -> Int#Source
remInt# :: Int# -> Int# -> Int#Source
negateInt# :: Int# -> Int#Source
addIntC# :: Int# -> Int# -> (#Int#, Int##)Source
subIntC# :: Int# -> Int# -> (#Int#, Int##)Source
(>#) :: Int# -> Int# -> BoolSource
(>=#) :: Int# -> Int# -> BoolSource
(==#) :: Int# -> Int# -> BoolSource
(/=#) :: Int# -> Int# -> BoolSource
(<#) :: Int# -> Int# -> BoolSource
(<=#) :: Int# -> Int# -> BoolSource
chr# :: Int# -> Char#Source
int2Word# :: Int# -> Word#Source
int2Float# :: Int# -> Float#Source
int2Double# :: Int# -> Double#Source
uncheckedIShiftL# :: Int# -> Int# -> Int#Source
uncheckedIShiftRA# :: Int# -> Int# -> Int#Source
uncheckedIShiftRL# :: Int# -> Int# -> Int#Source
plusWord# :: Word# -> Word# -> Word#Source
minusWord# :: Word# -> Word# -> Word#Source
timesWord# :: Word# -> Word# -> Word#Source
quotWord# :: Word# -> Word# -> Word#Source
remWord# :: Word# -> Word# -> Word#Source
and# :: Word# -> Word# -> Word#Source
or# :: Word# -> Word# -> Word#Source
xor# :: Word# -> Word# -> Word#Source
not# :: Word# -> Word#Source
uncheckedShiftL# :: Word# -> Int# -> Word#Source
uncheckedShiftRL# :: Word# -> Int# -> Word#Source
word2Int# :: Word# -> Int#Source
gtWord# :: Word# -> Word# -> BoolSource
geWord# :: Word# -> Word# -> BoolSource
eqWord# :: Word# -> Word# -> BoolSource
neWord# :: Word# -> Word# -> BoolSource
ltWord# :: Word# -> Word# -> BoolSource
leWord# :: Word# -> Word# -> BoolSource
narrow8Int# :: Int# -> Int#Source
narrow16Int# :: Int# -> Int#Source
narrow32Int# :: Int# -> Int#Source
narrow8Word# :: Word# -> Word#Source
narrow16Word# :: Word# -> Word#Source
narrow32Word# :: Word# -> Word#Source
(>##) :: Double# -> Double# -> BoolSource
(>=##) :: Double# -> Double# -> BoolSource
(==##) :: Double# -> Double# -> BoolSource
(/=##) :: Double# -> Double# -> BoolSource
(<##) :: Double# -> Double# -> BoolSource
(<=##) :: Double# -> Double# -> BoolSource
(+##) :: Double# -> Double# -> Double#Source
(-##) :: Double# -> Double# -> Double#Source
(*##) :: Double# -> Double# -> Double#Source
(/##) :: Double# -> Double# -> Double#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
(**##) :: Double# -> Double# -> Double#Source
decodeDouble_2Int# :: Double# -> (#Int#, Word#, Word#, Int##)Source
gtFloat# :: Float# -> Float# -> BoolSource
geFloat# :: Float# -> Float# -> BoolSource
eqFloat# :: Float# -> Float# -> BoolSource
neFloat# :: Float# -> Float# -> BoolSource
ltFloat# :: Float# -> Float# -> BoolSource
leFloat# :: Float# -> Float# -> BoolSource
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
expFloat# :: Float# -> Float#Source
logFloat# :: Float# -> Float#Source
sqrtFloat# :: Float# -> Float#Source
sinFloat# :: Float# -> Float#Source
cosFloat# :: Float# -> Float#Source
tanFloat# :: 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
newArray# :: Int# -> a -> State# s -> (#State# s, MutableArray# s a#)Source
sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> BoolSource
readArray# :: MutableArray# s a -> Int# -> State# s -> (#State# s, a#)Source
writeArray# :: MutableArray# s a -> Int# -> a -> State# s -> State# sSource
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
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
byteArrayContents# :: ByteArray# -> Addr#Source
sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> BoolSource
unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (#State# s, ByteArray##)Source
sizeofByteArray# :: ByteArray# -> Int#Source
sizeofMutableByteArray# :: MutableByteArray# 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# aSource
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# sSource
writeWideCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# sSource
writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# sSource
writeWordArray# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# sSource
writeAddrArray# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# sSource
writeFloatArray# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# sSource
writeDoubleArray# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# sSource
writeStablePtrArray# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# sSource
writeInt8Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# sSource
writeInt16Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# sSource
writeInt32Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# sSource
writeInt64Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# sSource
writeWord8Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# sSource
writeWord16Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# sSource
writeWord32Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# sSource
writeWord64Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# sSource
plusAddr# :: Addr# -> Int# -> Addr#Source
minusAddr# :: Addr# -> Addr# -> Int#Source
remAddr# :: Addr# -> Int# -> Int#Source
addr2Int# :: Addr# -> Int#Source
int2Addr# :: Int# -> Addr#Source
gtAddr# :: Addr# -> Addr# -> BoolSource
geAddr# :: Addr# -> Addr# -> BoolSource
eqAddr# :: Addr# -> Addr# -> BoolSource
neAddr# :: Addr# -> Addr# -> BoolSource
ltAddr# :: Addr# -> Addr# -> BoolSource
leAddr# :: Addr# -> Addr# -> BoolSource
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# aSource
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
readCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##)Source
readWideCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##)Source
readIntOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)Source
readWordOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)Source
readAddrOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Addr##)Source
readFloatOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Float##)Source
readDoubleOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Double##)Source
readStablePtrOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, StablePtr# a#)Source
readInt8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)Source
readInt16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)Source
readInt32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)Source
readInt64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Int##)Source
readWord8OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)Source
readWord16OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)Source
readWord32OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)Source
readWord64OffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Word##)Source
writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# sSource
writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# sSource
writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# sSource
writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# sSource
writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# s -> State# sSource
writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# s -> State# sSource
writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# s -> State# sSource
writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# s -> State# sSource
writeInt8OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# sSource
writeInt16OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# sSource
writeInt32OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# sSource
writeInt64OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# sSource
writeWord8OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# sSource
writeWord16OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# sSource
writeWord32OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# sSource
writeWord64OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# sSource
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# sSource
sameMutVar# :: MutVar# s a -> MutVar# s a -> BoolSource
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
raise# :: a -> bSource
raiseIO# :: a -> State# RealWorld -> (#State# RealWorld, b#)Source
blockAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)Source
unblockAsyncExceptions# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)Source
asyncExceptionsBlocked# :: State# RealWorld -> (#State# RealWorld, Int##)Source
atomically# :: (State# RealWorld -> (#State# RealWorld, a#)) -> State# RealWorld -> (#State# RealWorld, a#)Source
retry# :: 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
newTVar# :: a -> State# s -> (#State# s, TVar# s a#)Source
readTVar# :: TVar# s a -> State# s -> (#State# s, a#)Source
readTVarIO# :: TVar# s a -> State# s -> (#State# s, a#)Source
writeTVar# :: TVar# s a -> a -> State# s -> State# sSource
sameTVar# :: TVar# s a -> TVar# s a -> BoolSource
newMVar# :: State# s -> (#State# s, MVar# s a#)Source
takeMVar# :: MVar# s a -> State# s -> (#State# s, a#)Source
tryTakeMVar# :: MVar# s a -> State# s -> (#State# s, Int#, a#)Source
putMVar# :: MVar# s a -> a -> State# s -> State# sSource
tryPutMVar# :: MVar# s a -> a -> State# s -> (#State# s, Int##)Source
sameMVar# :: MVar# s a -> MVar# s a -> BoolSource
isEmptyMVar# :: MVar# s a -> State# s -> (#State# s, Int##)Source
delay# :: Int# -> State# s -> State# sSource
waitRead# :: Int# -> State# s -> State# sSource
waitWrite# :: Int# -> State# s -> State# sSource
fork# :: a -> State# RealWorld -> (#State# RealWorld, ThreadId##)Source
forkOn# :: Int# -> a -> State# RealWorld -> (#State# RealWorld, ThreadId##)Source
killThread# :: ThreadId# -> a -> State# RealWorld -> State# RealWorldSource
yield# :: State# RealWorld -> State# RealWorldSource
myThreadId# :: State# RealWorld -> (#State# RealWorld, ThreadId##)Source
labelThread# :: ThreadId# -> Addr# -> State# RealWorld -> State# RealWorldSource
isCurrentThreadBound# :: State# RealWorld -> (#State# RealWorld, Int##)Source
noDuplicate# :: State# RealWorld -> State# RealWorldSource
threadStatus# :: ThreadId# -> State# RealWorld -> (#State# RealWorld, Int##)Source
mkWeak# :: o -> b -> c -> State# RealWorld -> (#State# RealWorld, Weak# b#)Source
mkWeakForeignEnv# :: o -> b -> Addr# -> Addr# -> Int# -> Addr# -> State# RealWorld -> (#State# RealWorld, Weak# b#)Source
deRefWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, a#)Source
finalizeWeak# :: Weak# a -> State# RealWorld -> (#State# RealWorld, Int#, State# RealWorld -> (#State# RealWorld, ()#)#)Source
touch# :: o -> State# RealWorld -> State# RealWorldSource
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# a -> Int#Source
stableNameToInt# :: StableName# a -> Int#Source
reallyUnsafePtrEquality# :: a -> a -> Int#Source
getSpark# :: State# s -> (#State# s, Int#, a#)Source
dataToTag# :: a -> Int#Source
addrToHValue# :: Addr# -> (#a#)Source
mkApUpd0# :: BCO# -> (#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
traceCcs# :: a -> b -> bSource
traceEvent# :: Addr# -> State# s -> State# sSource
Produced by Haddock version 2.6.1