ghc-prim-0.2.0.0: GHC primitivesSource codeContentsIndex
GHC.Prim
Portabilitynon-portable (GHC extensions)
Stabilityinternal
Maintainercvs-ghc@haskell.org
Contents
The word size story.
Char#
Int#
Word#
Narrowings
Int64#
Word64#
Double#
Float#
Arrays
Byte Arrays
Addr#
Mutable variables
Exceptions
STM-accessible Mutable Variables
Synchronized Mutable Variables
Delay/wait operations
Concurrency primitives
Weak pointers
Stable pointers and names
Unsafe pointer equality
Parallelism
Tag to enum stuff
Bytecode operations
Misc
Etc
Description
GHC's primitive types and operations. Use GHC.Exts from the base package instead of importing this module directly.
Synopsis
data Char#
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#
data Int#
(+#) :: Int# -> Int# -> Int#
(-#) :: Int# -> Int# -> Int#
(*#) :: Int# -> Int# -> Int#
mulIntMayOflo# :: Int# -> Int# -> Int#
quotInt# :: Int# -> Int# -> Int#
remInt# :: 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#
uncheckedIShiftL# :: Int# -> Int# -> Int#
uncheckedIShiftRA# :: Int# -> Int# -> Int#
uncheckedIShiftRL# :: Int# -> Int# -> Int#
data Word#
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#
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#
data Int64#
data Word64#
data Double#
(>##) :: 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_2Int# :: Double# -> (#Int#, Word#, Word#, Int##)
data Float#
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_Int# :: Float# -> (#Int#, Int##)
data Array# a
data MutableArray# s a
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#)
data ByteArray#
data MutableByteArray# s
newByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#)
newPinnedByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#)
newAlignedPinnedByteArray# :: Int# -> 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
data Addr#
nullAddr# :: Addr#
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
data MutVar# s a
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##)
data TVar# s a
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#)
readTVarIO# :: 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
data MVar# s a
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
data State# s
data RealWorld
data ThreadId#
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##)
data Weak# b
mkWeak# :: o -> b -> c -> State# RealWorld -> (#State# RealWorld, Weak# b#)
mkWeakForeignEnv# :: o -> b -> Addr# -> Addr# -> Int# -> Addr# -> 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
data StablePtr# a
data StableName# a
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#
par# :: a -> Int#
getSpark# :: State# s -> (#State# s, Int#, a#)
parGlobal# :: a -> Int# -> Int# -> Int# -> Int# -> b -> Int#
parLocal# :: a -> Int# -> Int# -> Int# -> Int# -> b -> Int#
parAt# :: b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int#
parAtAbs# :: a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int#
parAtRel# :: a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int#
parAtForNow# :: b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int#
dataToTag# :: a -> Int#
tagToEnum# :: Int# -> a
data BCO#
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#)
traceCcs# :: a -> b -> b
seq :: a -> b -> b
inline :: a -> a
lazy :: a -> a
data Any a
unsafeCoerce# :: a -> b
traceEvent# :: Addr# -> State# s -> State# s
The word size story.

Haskell98 specifies that signed integers (type Int) must contain at least 30 bits. GHC always implements Int using the primitive type Int#, whose size equals the MachDeps.h constant WORD_SIZE_IN_BITS. This is normally set based on the config.h parameter SIZEOF_HSWORD, i.e., 32 bits on 32-bit machines, 64 bits on 64-bit machines. However, it can also be explicitly set to a smaller number, e.g., 31 bits, to allow the possibility of using tag bits. Currently GHC itself has only 32-bit and 64-bit variants, but 30 or 31-bit code can be exported as an external core file for use in other back ends.

GHC also implements a primitive unsigned integer type Word# which always has the same number of bits as Int#.

In addition, GHC supports families of explicit-sized integers and words at 8, 16, 32, and 64 bits, with the usual arithmetic operations, comparisons, and a range of conversions. The 8-bit and 16-bit sizes are always represented as Int# and Word#, and the operations implemented in terms of the the primops on these types, with suitable range restrictions on the results (using the narrow$n$Int# and narrow$n$Word# families of primops. The 32-bit sizes are represented using Int# and Word# when WORD_SIZE_IN_BITS $geq$ 32; otherwise, these are represented using distinct primitive types Int32# and Word32#. These (when needed) have a complete set of corresponding operations; however, nearly all of these are implemented as external C functions rather than as primops. Exactly the same story applies to the 64-bit sizes. All of these details are hidden under the PrelInt and PrelWord modules, which use #if-defs to invoke the appropriate types and operators.

Word size also matters for the families of primops for indexing/reading/writing fixed-size quantities at offsets from an array base, address, or foreign pointer. Here, a slightly different approach is taken. The names of these primops are fixed, but their types vary according to the value of WORD_SIZE_IN_BITS. For example, if word size is at least 32 bits then an operator like indexInt32Array# has type ByteArray# -> Int# -> Int#; otherwise it has type ByteArray# -> Int# -> Int32#. This approach confines the necessary #if-defs to this file; no conditional compilation is needed in the files that expose these primops.

Finally, there are strongly deprecated primops for coercing between Addr#, the primitive type of machine addresses, and Int#. These are pretty bogus anyway, but will work on existing 32-bit and 64-bit GHC targets; they are completely bogus when tag bits are used in Int#, so are not available in this case.

Char#
Operations on 31-bit characters.
data Char# Source
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#
Operations on native-size integers (30+ bits).
data Int# Source
(+#) :: Int# -> Int# -> Int#Source
(-#) :: Int# -> Int# -> Int#Source
(*#) :: Int# -> Int# -> Int#Source
Low word of signed integer multiply.
mulIntMayOflo# :: Int# -> Int# -> Int#Source

Return non-zero if there is any possibility that the upper word of a signed integer multiply might contain useful information. Return zero only if you are completely sure that no overflow can occur. On a 32-bit platform, the recommmended implementation is to do a 32 x 32 -> 64 signed multiply, and subtract result[63:32] from (result[31] >>signed 31). If this is zero, meaning that the upper word is merely a sign extension of the lower one, no overflow can occur.

On a 64-bit platform it is not always possible to acquire the top 64 bits of the result. Therefore, a recommended implementation is to take the absolute value of both operands, and return 0 iff bits[63:31] of them are zero, since that means that their magnitudes fit within 31 bits, so the magnitude of the product must fit into 62 bits.

If in doubt, return non-zero, but do make an effort to create the correct answer for small args, since otherwise the performance of (*) :: Integer -> Integer -> Integer will be poor.

quotInt# :: Int# -> Int# -> Int#Source
Rounds towards zero.
remInt# :: Int# -> Int# -> Int#Source
Satisfies (quotInt# x y) *# y +# (remInt# x y) == x.
negateInt# :: Int# -> Int#Source
addIntC# :: Int# -> Int# -> (#Int#, Int##)Source
Add with carry. First member of result is (wrapped) sum; second member is 0 iff no overflow occured.
subIntC# :: Int# -> Int# -> (#Int#, Int##)Source
Subtract with carry. First member of result is (wrapped) difference; second member is 0 iff no overflow occured.
(>#) :: 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
Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRA# :: Int# -> Int# -> Int#Source
Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedIShiftRL# :: Int# -> Int# -> Int#Source
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
Word#
Operations on native-sized unsigned words (30+ bits).
data Word# 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
Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
uncheckedShiftRL# :: Word# -> Int# -> Word#Source
Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.
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
Narrowings
Explicit narrowing of native-sized ints or words.
narrow8Int# :: Int# -> Int#Source
narrow16Int# :: Int# -> Int#Source
narrow32Int# :: Int# -> Int#Source
narrow8Word# :: Word# -> Word#Source
narrow16Word# :: Word# -> Word#Source
narrow32Word# :: Word# -> Word#Source
Int64#
Operations on 64-bit unsigned words. This type is only used if plain Int# has less than 64 bits. In any case, the operations are not primops; they are implemented (if needed) as ccalls instead.
data Int64# Source
Word64#
Operations on 64-bit unsigned words. This type is only used if plain Word# has less than 64 bits. In any case, the operations are not primops; they are implemented (if needed) as ccalls instead.
data Word64# Source
Double#
Operations on double-precision (64 bit) floating-point numbers.
data Double# 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
Truncates a Double. Results are undefined if the truncation if truncation yields a value outside the range of Int#.
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
Exponentiation.
decodeDouble_2Int# :: Double# -> (#Int#, Word#, Word#, Int##)Source
Convert to integer. First component of the result is -1 or 1, indicating the sign of the mantissa. The next two are the high and low 32 bits of the mantissa respectively, and the last is the exponent.
Float#
Operations on single-precision (32-bit) floating-point numbers.
data Float# 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
Truncates a Float. Results are undefined if the truncation if truncation yields a value outside the range of Int#.
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
Convert to integers. First Int# in result is the mantissa; second is the exponent.
Arrays
Operations on Array#.
data Array# a Source
data MutableArray# s a Source
newArray# :: Int# -> a -> State# s -> (#State# s, MutableArray# s a#)Source
Create a new mutable array of specified size (in bytes), in the specified state thread, with each element containing the specified initial value.
sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> BoolSource
readArray# :: MutableArray# s a -> Int# -> State# s -> (#State# s, a#)Source
Read from specified index of mutable array. Result is not yet evaluated.
writeArray# :: MutableArray# s a -> Int# -> a -> State# s -> State# sSource
Write to specified index of mutable array.
indexArray# :: Array# a -> Int# -> (#a#)Source
Read from specified index of immutable array. Result is packaged into an unboxed singleton; the result itself is not yet evaluated.
unsafeFreezeArray# :: MutableArray# s a -> State# s -> (#State# s, Array# a#)Source
Make a mutable array immutable, without copying.
unsafeThawArray# :: Array# a -> State# s -> (#State# s, MutableArray# s a#)Source
Make an immutable array mutable, without copying.
Byte Arrays
Operations on ByteArray#. A ByteArray# is a just a region of raw memory in the garbage-collected heap, which is not scanned for pointers. It carries its own size (in bytes). There are three sets of operations for accessing byte array contents: index for reading from immutable byte arrays, and read/write for mutable byte arrays. Each set contains operations for a range of useful primitive data types. Each operation takes an offset measured in terms of the size fo the primitive type being read or written.
data ByteArray# Source
data MutableByteArray# s Source
newByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#)Source
Create a new mutable byte array of specified size (in bytes), in the specified state thread.
newPinnedByteArray# :: Int# -> State# s -> (#State# s, MutableByteArray# s#)Source
Create a mutable byte array that the GC guarantees not to move.
newAlignedPinnedByteArray# :: Int# -> Int# -> State# s -> (#State# s, MutableByteArray# s#)Source
Create a mutable byte array, aligned by the specified amount, that the GC guarantees not to move.
byteArrayContents# :: ByteArray# -> Addr#Source
Intended for use with pinned arrays; otherwise very unsafe!
sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> BoolSource
unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (#State# s, ByteArray##)Source
Make a mutable byte array immutable, without copying.
sizeofByteArray# :: ByteArray# -> Int#Source
sizeofMutableByteArray# :: MutableByteArray# s -> Int#Source
indexCharArray# :: ByteArray# -> Int# -> Char#Source
Read 8-bit character; offset in bytes.
indexWideCharArray# :: ByteArray# -> Int# -> Char#Source
Read 31-bit character; offset in 4-byte words.
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# -> Int64#Source
indexWord8Array# :: ByteArray# -> Int# -> Word#Source
indexWord16Array# :: ByteArray# -> Int# -> Word#Source
indexWord32Array# :: ByteArray# -> Int# -> Word#Source
indexWord64Array# :: ByteArray# -> Int# -> Word64#Source
readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char##)Source
Read 8-bit character; offset in bytes.
readWideCharArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Char##)Source
Read 31-bit character; offset in 4-byte words.
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, Int64##)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, Word64##)Source
writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# sSource
Write 8-bit character; offset in bytes.
writeWideCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# sSource
Write 31-bit character; offset in 4-byte words.
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# -> Int64# -> 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# -> Word64# -> State# s -> State# sSource
Addr#
data Addr# Source
An arbitrary machine address assumed to point outside the garbage-collected heap.
nullAddr# :: Addr#Source
The null address.
plusAddr# :: Addr# -> Int# -> Addr#Source
minusAddr# :: Addr# -> Addr# -> Int#Source
Result is meaningless if two Addr#s are so far apart that their difference doesn't fit in an Int#.
remAddr# :: Addr# -> Int# -> Int#Source
Return the remainder when the Addr# arg, treated like an Int#, is divided by the Int# arg.
addr2Int# :: Addr# -> Int#Source
Coerce directly from address to int. Strongly deprecated.
int2Addr# :: Int# -> Addr#Source
Coerce directly from int to address. Strongly deprecated.
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
Reads 8-bit character; offset in bytes.
indexWideCharOffAddr# :: Addr# -> Int# -> Char#Source
Reads 31-bit character; offset in 4-byte words.
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# -> Int64#Source
indexWord8OffAddr# :: Addr# -> Int# -> Word#Source
indexWord16OffAddr# :: Addr# -> Int# -> Word#Source
indexWord32OffAddr# :: Addr# -> Int# -> Word#Source
indexWord64OffAddr# :: Addr# -> Int# -> Word64#Source
readCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##)Source
Reads 8-bit character; offset in bytes.
readWideCharOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Char##)Source
Reads 31-bit character; offset in 4-byte words.
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, Int64##)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, Word64##)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# -> Int64# -> 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# -> Word64# -> State# s -> State# sSource
Mutable variables
Operations on MutVar#s.
data MutVar# s a Source
A MutVar# behaves like a single-element mutable array.
newMutVar# :: a -> State# s -> (#State# s, MutVar# s a#)Source
Create MutVar# with specified initial value in specified state thread.
readMutVar# :: MutVar# s a -> State# s -> (#State# s, a#)Source
Read contents of MutVar#. Result is not yet evaluated.
writeMutVar# :: MutVar# s a -> a -> State# s -> State# sSource
Write contents of MutVar#.
sameMutVar# :: MutVar# s a -> MutVar# s a -> BoolSource
atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (#State# s, c#)Source
Exceptions
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
STM-accessible Mutable Variables
data TVar# s a 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
Create a new TVar# holding a specified initial value.
readTVar# :: TVar# s a -> State# s -> (#State# s, a#)Source
Read contents of TVar#. Result is not yet evaluated.
readTVarIO# :: TVar# s a -> State# s -> (#State# s, a#)Source
Read contents of TVar# outside an STM transaction
writeTVar# :: TVar# s a -> a -> State# s -> State# sSource
Write contents of TVar#.
sameTVar# :: TVar# s a -> TVar# s a -> BoolSource
Synchronized Mutable Variables
Operations on MVar#s.
data MVar# s a Source
A shared mutable variable (not the same as a MutVar#!). (Note: in a non-concurrent implementation, (MVar# a) can be represented by (MutVar# (Maybe a)).)
newMVar# :: State# s -> (#State# s, MVar# s a#)Source
Create new MVar#; initially empty.
takeMVar# :: MVar# s a -> State# s -> (#State# s, a#)Source
If MVar# is empty, block until it becomes full. Then remove and return its contents, and set it empty.
tryTakeMVar# :: MVar# s a -> State# s -> (#State# s, Int#, a#)Source
If MVar# is empty, immediately return with integer 0 and value undefined. Otherwise, return with integer 1 and contents of MVar#, and set MVar# empty.
putMVar# :: MVar# s a -> a -> State# s -> State# sSource
If MVar# is full, block until it becomes empty. Then store value arg as its new contents.
tryPutMVar# :: MVar# s a -> a -> State# s -> (#State# s, Int##)Source
If MVar# is full, immediately return with integer 0. Otherwise, store value arg as MVar#'s new contents, and return with integer 1.
sameMVar# :: MVar# s a -> MVar# s a -> BoolSource
isEmptyMVar# :: MVar# s a -> State# s -> (#State# s, Int##)Source
Return 1 if MVar# is empty; 0 otherwise.
Delay/wait operations
delay# :: Int# -> State# s -> State# sSource
Sleep specified number of microseconds.
waitRead# :: Int# -> State# s -> State# sSource
Block until input is available on specified file descriptor.
waitWrite# :: Int# -> State# s -> State# sSource
Block until output is possible on specified file descriptor.
Concurrency primitives
data State# s Source
State# is the primitive, unlifted type of states. It has one type parameter, thus State# RealWorld, or State# s, where s is a type variable. The only purpose of the type parameter is to keep different state threads separate. It is represented by nothing at all.
data RealWorld Source
RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.
data ThreadId# Source
(In a non-concurrent implementation, this can be a singleton type, whose (unique) value is returned by myThreadId#. The other operations can be omitted.)
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
Weak pointers
data Weak# b 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
Stable pointers and names
data StablePtr# a Source
data StableName# a 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# a -> Int#Source
stableNameToInt# :: StableName# a -> Int#Source
Unsafe pointer equality
reallyUnsafePtrEquality# :: a -> a -> Int#Source
Parallelism
par# :: a -> Int#Source
getSpark# :: State# s -> (#State# s, Int#, a#)Source
parGlobal# :: a -> Int# -> Int# -> Int# -> Int# -> b -> Int#Source
parLocal# :: a -> Int# -> Int# -> Int# -> Int# -> b -> Int#Source
parAt# :: b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int#Source
parAtAbs# :: a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int#Source
parAtRel# :: a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int#Source
parAtForNow# :: b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int#Source
Tag to enum stuff
Convert back and forth between values of enumerated types and small integers.
dataToTag# :: a -> Int#Source
tagToEnum# :: Int# -> aSource
Bytecode operations
Support for the bytecode interpreter and linker.
data BCO# Source
Primitive bytecode type.
addrToHValue# :: Addr# -> (#a#)Source
Convert an Addr# to a followable type.
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
Misc
These aren't nearly as wired in as Etc...
traceCcs# :: a -> b -> bSource
Etc
Miscellaneous built-ins
seq :: a -> b -> bSource
Evaluates its first argument to head normal form, and then returns its second argument as the result.
inline :: a -> aSource

The call (inline f) arranges that f is inlined, regardless of its size. More precisely, the call (inline f) rewrites to the right-hand side of f's definition. This allows the programmer to control inlining from a particular call site rather than the definition site of the function (c.f. INLINE pragmas in User's Guide, Section 7.10.3, "INLINE and NOINLINE pragmas").

This inlining occurs regardless of the argument to the call or the size of f's definition; it is unconditional. The main caveat is that f's definition must be visible to the compiler. That is, f must be let-bound in the current scope. If no inlining takes place, the inline function expands to the identity function in Phase zero; so its use imposes no overhead.

If the function is defined in another module, GHC only exposes its inlining in the interface file if the function is sufficiently small that it might be inlined by the automatic mechanism. There is currently no way to tell GHC to expose arbitrarily-large functions in the interface file. (This shortcoming is something that could be fixed, with some kind of pragma.)

lazy :: a -> aSource

The lazy function restrains strictness analysis a little. The call (lazy e) means the same as e, but lazy has a magical property so far as strictness analysis is concerned: it is lazy in its first argument, even though its semantics is strict. After strictness analysis has run, calls to lazy are inlined to be the identity function.

This behaviour is occasionally useful when controlling evaluation order. Notably, lazy is used in the library definition of Control.Parallel.par:

par :: a -> b -> b
par x y = case (par# x) of _ -> lazy y

If lazy were not lazy, par would look strict in y which would defeat the whole purpose of par.

Like seq, the argument of lazy can have an unboxed type.

data Any a Source

The type constructor Any is type to which you can unsafely coerce any lifted type, and back.

  • It is lifted, and hence represented by a pointer
  • It does not claim to be a data type, and that's important for the code generator, because the code gen may enter a data value but never enters a function value.

It's also used to instantiate un-constrained type variables after type checking. For example

length Any []

Annoyingly, we sometimes need Anys of other kinds, such as (* -> *) etc. This is a bit like tuples. We define a couple of useful ones here, and make others up on the fly. If any of these others end up being exported into interface files, we'll get a crash; at least until we add interface-file syntax to support them.

unsafeCoerce# :: a -> bSource

The function unsafeCoerce# allows you to side-step the typechecker entirely. That is, it allows you to coerce any type into any other type. If you use this function, you had better get it right, otherwise segmentation faults await. It is generally used when you want to write a program that you know is well-typed, but where Haskell's type system is not expressive enough to prove that it is well typed.

The following uses of unsafeCoerce# are supposed to work (i.e. not lead to spurious compile-time or run-time crashes):

  • Casting any lifted type to Any
  • Casting Any back to the real type
  • Casting an unboxed type to another unboxed type of the same size (but not coercions between floating-point and integral types)
  • Casting between two types that have the same runtime representation. One case is when the two types differ only in "phantom" type parameters, for example Ptr Int to Ptr Float, or [Int] to [Float] when the list is known to be empty. Also, a newtype of a type T has the same representation at runtime as T.

Other uses of unsafeCoerce# are undefined. In particular, you should not use unsafeCoerce# to cast a T to an algebraic data type D, unless T is also an algebraic data type. For example, do not cast Int->Int to Bool, even if you later cast that Bool back to Int->Int before applying it. The reasons have to do with GHC's internal representation details (for the congnoscenti, data values can be entered but function closures cannot). If you want a safe type to cast things to, use Any, which is not an algebraic data type.

traceEvent# :: Addr# -> State# s -> State# sSource
Emits an event via the RTS tracing framework. The contents of the event is the zero-terminated byte string passed as the first argument. The event will be emitted either to the .eventlog file, or to stderr, depending on the runtime RTS flags.
Produced by Haddock version 2.6.0