{-
This is a generated file (generated by genprimopcode).
It is not code to actually be used. Its only purpose is to be
consumed by haddock.
-}

-----------------------------------------------------------------------------
-- |
-- Module      :  GHC.Prim
-- 
-- Maintainer  :  cvs-ghc@haskell.org
-- Stability   :  internal
-- Portability :  non-portable (GHC extensions)
--
-- GHC's primitive types and operations.
-- Use GHC.Exts from the base package instead of importing this
-- module directly.
--
-----------------------------------------------------------------------------
module GHC.Prim (
	
-- * 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.


	Char#,
	gtChar#,
	geChar#,
	eqChar#,
	neChar#,
	ltChar#,
	leChar#,
	ord#,
	
-- * Int#
-- |Operations on native-size integers (30+ bits).


	Int#,
	(+#),
	(-#),
	(*#),
	mulIntMayOflo#,
	quotInt#,
	remInt#,
	negateInt#,
	addIntC#,
	subIntC#,
	(>#),
	(>=#),
	(==#),
	(/=#),
	(<#),
	(<=#),
	chr#,
	int2Word#,
	int2Float#,
	int2Double#,
	uncheckedIShiftL#,
	uncheckedIShiftRA#,
	uncheckedIShiftRL#,
	
-- * Word#
-- |Operations on native-sized unsigned words (30+ bits).


	Word#,
	plusWord#,
	minusWord#,
	timesWord#,
	quotWord#,
	remWord#,
	and#,
	or#,
	xor#,
	not#,
	uncheckedShiftL#,
	uncheckedShiftRL#,
	word2Int#,
	gtWord#,
	geWord#,
	eqWord#,
	neWord#,
	ltWord#,
	leWord#,
	
-- * Narrowings
-- |Explicit narrowing of native-sized ints or words.


	narrow8Int#,
	narrow16Int#,
	narrow32Int#,
	narrow8Word#,
	narrow16Word#,
	narrow32Word#,
	
-- * Double#
-- |Operations on double-precision (64 bit) floating-point numbers.


	Double#,
	(>##),
	(>=##),
	(==##),
	(/=##),
	(<##),
	(<=##),
	(+##),
	(-##),
	(*##),
	(/##),
	negateDouble#,
	double2Int#,
	double2Float#,
	expDouble#,
	logDouble#,
	sqrtDouble#,
	sinDouble#,
	cosDouble#,
	tanDouble#,
	asinDouble#,
	acosDouble#,
	atanDouble#,
	sinhDouble#,
	coshDouble#,
	tanhDouble#,
	(**##),
	decodeDouble_2Int#,
	
-- * Float#
-- |Operations on single-precision (32-bit) floating-point numbers.


	Float#,
	gtFloat#,
	geFloat#,
	eqFloat#,
	neFloat#,
	ltFloat#,
	leFloat#,
	plusFloat#,
	minusFloat#,
	timesFloat#,
	divideFloat#,
	negateFloat#,
	float2Int#,
	expFloat#,
	logFloat#,
	sqrtFloat#,
	sinFloat#,
	cosFloat#,
	tanFloat#,
	asinFloat#,
	acosFloat#,
	atanFloat#,
	sinhFloat#,
	coshFloat#,
	tanhFloat#,
	powerFloat#,
	float2Double#,
	decodeFloat_Int#,
	
-- * Arrays
-- |Operations on @Array\#@.


	Array#,
	MutableArray#,
	newArray#,
	sameMutableArray#,
	readArray#,
	writeArray#,
	indexArray#,
	unsafeFreezeArray#,
	unsafeThawArray#,
	
-- * 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.


	ByteArray#,
	MutableByteArray#,
	newByteArray#,
	newPinnedByteArray#,
	newAlignedPinnedByteArray#,
	byteArrayContents#,
	sameMutableByteArray#,
	unsafeFreezeByteArray#,
	sizeofByteArray#,
	sizeofMutableByteArray#,
	indexCharArray#,
	indexWideCharArray#,
	indexIntArray#,
	indexWordArray#,
	indexAddrArray#,
	indexFloatArray#,
	indexDoubleArray#,
	indexStablePtrArray#,
	indexInt8Array#,
	indexInt16Array#,
	indexInt32Array#,
	indexInt64Array#,
	indexWord8Array#,
	indexWord16Array#,
	indexWord32Array#,
	indexWord64Array#,
	readCharArray#,
	readWideCharArray#,
	readIntArray#,
	readWordArray#,
	readAddrArray#,
	readFloatArray#,
	readDoubleArray#,
	readStablePtrArray#,
	readInt8Array#,
	readInt16Array#,
	readInt32Array#,
	readInt64Array#,
	readWord8Array#,
	readWord16Array#,
	readWord32Array#,
	readWord64Array#,
	writeCharArray#,
	writeWideCharArray#,
	writeIntArray#,
	writeWordArray#,
	writeAddrArray#,
	writeFloatArray#,
	writeDoubleArray#,
	writeStablePtrArray#,
	writeInt8Array#,
	writeInt16Array#,
	writeInt32Array#,
	writeInt64Array#,
	writeWord8Array#,
	writeWord16Array#,
	writeWord32Array#,
	writeWord64Array#,
	
-- * Addr#
-- |


	Addr#,
	nullAddr#,
	plusAddr#,
	minusAddr#,
	remAddr#,
	addr2Int#,
	int2Addr#,
	gtAddr#,
	geAddr#,
	eqAddr#,
	neAddr#,
	ltAddr#,
	leAddr#,
	indexCharOffAddr#,
	indexWideCharOffAddr#,
	indexIntOffAddr#,
	indexWordOffAddr#,
	indexAddrOffAddr#,
	indexFloatOffAddr#,
	indexDoubleOffAddr#,
	indexStablePtrOffAddr#,
	indexInt8OffAddr#,
	indexInt16OffAddr#,
	indexInt32OffAddr#,
	indexInt64OffAddr#,
	indexWord8OffAddr#,
	indexWord16OffAddr#,
	indexWord32OffAddr#,
	indexWord64OffAddr#,
	readCharOffAddr#,
	readWideCharOffAddr#,
	readIntOffAddr#,
	readWordOffAddr#,
	readAddrOffAddr#,
	readFloatOffAddr#,
	readDoubleOffAddr#,
	readStablePtrOffAddr#,
	readInt8OffAddr#,
	readInt16OffAddr#,
	readInt32OffAddr#,
	readInt64OffAddr#,
	readWord8OffAddr#,
	readWord16OffAddr#,
	readWord32OffAddr#,
	readWord64OffAddr#,
	writeCharOffAddr#,
	writeWideCharOffAddr#,
	writeIntOffAddr#,
	writeWordOffAddr#,
	writeAddrOffAddr#,
	writeFloatOffAddr#,
	writeDoubleOffAddr#,
	writeStablePtrOffAddr#,
	writeInt8OffAddr#,
	writeInt16OffAddr#,
	writeInt32OffAddr#,
	writeInt64OffAddr#,
	writeWord8OffAddr#,
	writeWord16OffAddr#,
	writeWord32OffAddr#,
	writeWord64OffAddr#,
	
-- * Mutable variables
-- |Operations on MutVar\#s.


	MutVar#,
	newMutVar#,
	readMutVar#,
	writeMutVar#,
	sameMutVar#,
	atomicModifyMutVar#,
	
-- * Exceptions
-- |


	catch#,
	raise#,
	raiseIO#,
	maskAsyncExceptions#,
	maskUninterruptible#,
	unmaskAsyncExceptions#,
	getMaskingState#,
	
-- * STM-accessible Mutable Variables
-- |


	TVar#,
	atomically#,
	retry#,
	catchRetry#,
	catchSTM#,
	check#,
	newTVar#,
	readTVar#,
	readTVarIO#,
	writeTVar#,
	sameTVar#,
	
-- * Synchronized Mutable Variables
-- |Operations on @MVar\#@s. 


	MVar#,
	newMVar#,
	takeMVar#,
	tryTakeMVar#,
	putMVar#,
	tryPutMVar#,
	sameMVar#,
	isEmptyMVar#,
	
-- * Delay\/wait operations
-- |


	delay#,
	waitRead#,
	waitWrite#,
	
-- * Concurrency primitives
-- |


	State#,
	RealWorld,
	ThreadId#,
	fork#,
	forkOn#,
	killThread#,
	yield#,
	myThreadId#,
	labelThread#,
	isCurrentThreadBound#,
	noDuplicate#,
	threadStatus#,
	
-- * Weak pointers
-- |


	Weak#,
	mkWeak#,
	mkWeakForeignEnv#,
	deRefWeak#,
	finalizeWeak#,
	touch#,
	
-- * Stable pointers and names
-- |


	StablePtr#,
	StableName#,
	makeStablePtr#,
	deRefStablePtr#,
	eqStablePtr#,
	makeStableName#,
	eqStableName#,
	stableNameToInt#,
	
-- * Unsafe pointer equality
-- |


	reallyUnsafePtrEquality#,
	
-- * Parallelism
-- |


	par#,
	getSpark#,
	numSparks#,
	parGlobal#,
	parLocal#,
	parAt#,
	parAtAbs#,
	parAtRel#,
	parAtForNow#,
	
-- * Tag to enum stuff
-- |Convert back and forth between values of enumerated types
-- 	and small integers.


	dataToTag#,
	tagToEnum#,
	
-- * Bytecode operations
-- |Support for the bytecode interpreter and linker.


	BCO#,
	addrToHValue#,
	mkApUpd0#,
	newBCO#,
	unpackClosure#,
	getApStackVal#,
	
-- * Misc
-- |These aren\'t nearly as wired in as Etc...


	traceCcs#,
	
-- * Etc
-- |Miscellaneous built-ins


	seq,
	inline,
	lazy,
	Any,
	unsafeCoerce#,
	traceEvent#,
) where

import GHC.Bool

{-
has_side_effects = False
out_of_line = False
commutable = False
needs_wrapper = False
can_fail = False
strictness = {  \ arity -> mkStrictSig (mkTopDmdType (replicate arity lazyDmd) TopRes) }
-}

data Char#

gtChar# :: Char# -> Char# -> Bool
gtChar# = let x = x in x

geChar# :: Char# -> Char# -> Bool
geChar# = let x = x in x

eqChar# :: Char# -> Char# -> Bool
eqChar# = let x = x in x

neChar# :: Char# -> Char# -> Bool
neChar# = let x = x in x

ltChar# :: Char# -> Char# -> Bool
ltChar# = let x = x in x

leChar# :: Char# -> Char# -> Bool
leChar# = let x = x in x

ord# :: Char# -> Int#
ord# = let x = x in x

data Int#

(+#) :: Int# -> Int# -> Int#
(+#) = let x = x in x

(-#) :: Int# -> Int# -> Int#
(-#) = let x = x in x

-- |Low word of signed integer multiply.

(*#) :: Int# -> Int# -> Int#
(*#) = let x = x in x

-- |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.
--    

mulIntMayOflo# :: Int# -> Int# -> Int#
mulIntMayOflo# = let x = x in x

-- |Rounds towards zero.

quotInt# :: Int# -> Int# -> Int#
quotInt# = let x = x in x

-- |Satisfies @(quotInt\# x y) *\# y +\# (remInt\# x y) == x@.

remInt# :: Int# -> Int# -> Int#
remInt# = let x = x in x

negateInt# :: Int# -> Int#
negateInt# = let x = x in x

-- |Add with carry.  First member of result is (wrapped) sum; 
--           second member is 0 iff no overflow occured.

addIntC# :: Int# -> Int# -> (# Int#,Int# #)
addIntC# = let x = x in x

-- |Subtract with carry.  First member of result is (wrapped) difference; 
--           second member is 0 iff no overflow occured.

subIntC# :: Int# -> Int# -> (# Int#,Int# #)
subIntC# = let x = x in x

(>#) :: Int# -> Int# -> Bool
(>#) = let x = x in x

(>=#) :: Int# -> Int# -> Bool
(>=#) = let x = x in x

(==#) :: Int# -> Int# -> Bool
(==#) = let x = x in x

(/=#) :: Int# -> Int# -> Bool
(/=#) = let x = x in x

(<#) :: Int# -> Int# -> Bool
(<#) = let x = x in x

(<=#) :: Int# -> Int# -> Bool
(<=#) = let x = x in x

chr# :: Int# -> Char#
chr# = let x = x in x

int2Word# :: Int# -> Word#
int2Word# = let x = x in x

int2Float# :: Int# -> Float#
int2Float# = let x = x in x

int2Double# :: Int# -> Double#
int2Double# = let x = x in x

-- |Shift left.  Result undefined if shift amount is not
--           in the range 0 to word size - 1 inclusive.

uncheckedIShiftL# :: Int# -> Int# -> Int#
uncheckedIShiftL# = let x = x in x

-- |Shift right arithmetic.  Result undefined if shift amount is not
--           in the range 0 to word size - 1 inclusive.

uncheckedIShiftRA# :: Int# -> Int# -> Int#
uncheckedIShiftRA# = let x = x in x

-- |Shift right logical.  Result undefined if shift amount is not
--           in the range 0 to word size - 1 inclusive.

uncheckedIShiftRL# :: Int# -> Int# -> Int#
uncheckedIShiftRL# = let x = x in x

data Word#

plusWord# :: Word# -> Word# -> Word#
plusWord# = let x = x in x

minusWord# :: Word# -> Word# -> Word#
minusWord# = let x = x in x

timesWord# :: Word# -> Word# -> Word#
timesWord# = let x = x in x

quotWord# :: Word# -> Word# -> Word#
quotWord# = let x = x in x

remWord# :: Word# -> Word# -> Word#
remWord# = let x = x in x

and# :: Word# -> Word# -> Word#
and# = let x = x in x

or# :: Word# -> Word# -> Word#
or# = let x = x in x

xor# :: Word# -> Word# -> Word#
xor# = let x = x in x

not# :: Word# -> Word#
not# = let x = x in x

-- |Shift left logical.   Result undefined if shift amount is not
--           in the range 0 to word size - 1 inclusive.

uncheckedShiftL# :: Word# -> Int# -> Word#
uncheckedShiftL# = let x = x in x

-- |Shift right logical.   Result undefined if shift  amount is not
--           in the range 0 to word size - 1 inclusive.

uncheckedShiftRL# :: Word# -> Int# -> Word#
uncheckedShiftRL# = let x = x in x

word2Int# :: Word# -> Int#
word2Int# = let x = x in x

gtWord# :: Word# -> Word# -> Bool
gtWord# = let x = x in x

geWord# :: Word# -> Word# -> Bool
geWord# = let x = x in x

eqWord# :: Word# -> Word# -> Bool
eqWord# = let x = x in x

neWord# :: Word# -> Word# -> Bool
neWord# = let x = x in x

ltWord# :: Word# -> Word# -> Bool
ltWord# = let x = x in x

leWord# :: Word# -> Word# -> Bool
leWord# = let x = x in x

narrow8Int# :: Int# -> Int#
narrow8Int# = let x = x in x

narrow16Int# :: Int# -> Int#
narrow16Int# = let x = x in x

narrow32Int# :: Int# -> Int#
narrow32Int# = let x = x in x

narrow8Word# :: Word# -> Word#
narrow8Word# = let x = x in x

narrow16Word# :: Word# -> Word#
narrow16Word# = let x = x in x

narrow32Word# :: Word# -> Word#
narrow32Word# = let x = x in x

data Double#

(>##) :: Double# -> Double# -> Bool
(>##) = let x = x in x

(>=##) :: Double# -> Double# -> Bool
(>=##) = let x = x in x

(==##) :: Double# -> Double# -> Bool
(==##) = let x = x in x

(/=##) :: Double# -> Double# -> Bool
(/=##) = let x = x in x

(<##) :: Double# -> Double# -> Bool
(<##) = let x = x in x

(<=##) :: Double# -> Double# -> Bool
(<=##) = let x = x in x

(+##) :: Double# -> Double# -> Double#
(+##) = let x = x in x

(-##) :: Double# -> Double# -> Double#
(-##) = let x = x in x

(*##) :: Double# -> Double# -> Double#
(*##) = let x = x in x

(/##) :: Double# -> Double# -> Double#
(/##) = let x = x in x

negateDouble# :: Double# -> Double#
negateDouble# = let x = x in x

-- |Truncates a @Double#@ value to the nearest @Int#@.
--     Results are undefined if the truncation if truncation yields
--     a value outside the range of @Int#@.

double2Int# :: Double# -> Int#
double2Int# = let x = x in x

double2Float# :: Double# -> Float#
double2Float# = let x = x in x

expDouble# :: Double# -> Double#
expDouble# = let x = x in x

logDouble# :: Double# -> Double#
logDouble# = let x = x in x

sqrtDouble# :: Double# -> Double#
sqrtDouble# = let x = x in x

sinDouble# :: Double# -> Double#
sinDouble# = let x = x in x

cosDouble# :: Double# -> Double#
cosDouble# = let x = x in x

tanDouble# :: Double# -> Double#
tanDouble# = let x = x in x

asinDouble# :: Double# -> Double#
asinDouble# = let x = x in x

acosDouble# :: Double# -> Double#
acosDouble# = let x = x in x

atanDouble# :: Double# -> Double#
atanDouble# = let x = x in x

sinhDouble# :: Double# -> Double#
sinhDouble# = let x = x in x

coshDouble# :: Double# -> Double#
coshDouble# = let x = x in x

tanhDouble# :: Double# -> Double#
tanhDouble# = let x = x in x

-- |Exponentiation.

(**##) :: Double# -> Double# -> Double#
(**##) = let x = x in x

-- |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.

decodeDouble_2Int# :: Double# -> (# Int#,Word#,Word#,Int# #)
decodeDouble_2Int# = let x = x in x

data Float#

gtFloat# :: Float# -> Float# -> Bool
gtFloat# = let x = x in x

geFloat# :: Float# -> Float# -> Bool
geFloat# = let x = x in x

eqFloat# :: Float# -> Float# -> Bool
eqFloat# = let x = x in x

neFloat# :: Float# -> Float# -> Bool
neFloat# = let x = x in x

ltFloat# :: Float# -> Float# -> Bool
ltFloat# = let x = x in x

leFloat# :: Float# -> Float# -> Bool
leFloat# = let x = x in x

plusFloat# :: Float# -> Float# -> Float#
plusFloat# = let x = x in x

minusFloat# :: Float# -> Float# -> Float#
minusFloat# = let x = x in x

timesFloat# :: Float# -> Float# -> Float#
timesFloat# = let x = x in x

divideFloat# :: Float# -> Float# -> Float#
divideFloat# = let x = x in x

negateFloat# :: Float# -> Float#
negateFloat# = let x = x in x

-- |Truncates a @Float#@ value to the nearest @Int#@.
--     Results are undefined if the truncation if truncation yields
--     a value outside the range of @Int#@.

float2Int# :: Float# -> Int#
float2Int# = let x = x in x

expFloat# :: Float# -> Float#
expFloat# = let x = x in x

logFloat# :: Float# -> Float#
logFloat# = let x = x in x

sqrtFloat# :: Float# -> Float#
sqrtFloat# = let x = x in x

sinFloat# :: Float# -> Float#
sinFloat# = let x = x in x

cosFloat# :: Float# -> Float#
cosFloat# = let x = x in x

tanFloat# :: Float# -> Float#
tanFloat# = let x = x in x

asinFloat# :: Float# -> Float#
asinFloat# = let x = x in x

acosFloat# :: Float# -> Float#
acosFloat# = let x = x in x

atanFloat# :: Float# -> Float#
atanFloat# = let x = x in x

sinhFloat# :: Float# -> Float#
sinhFloat# = let x = x in x

coshFloat# :: Float# -> Float#
coshFloat# = let x = x in x

tanhFloat# :: Float# -> Float#
tanhFloat# = let x = x in x

powerFloat# :: Float# -> Float# -> Float#
powerFloat# = let x = x in x

float2Double# :: Float# -> Double#
float2Double# = let x = x in x

-- |Convert to integers.
--     First @Int\#@ in result is the mantissa; second is the exponent.

decodeFloat_Int# :: Float# -> (# Int#,Int# #)
decodeFloat_Int# = let x = x in x

data Array# a

data MutableArray# s a

-- |Create a new mutable array with the specified number of elements,
--     in the specified state thread,
--     with each element containing the specified initial value.

newArray# :: Int# -> a -> State# s -> (# State# s,MutableArray# s a #)
newArray# = let x = x in x

sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> Bool
sameMutableArray# = let x = x in x

-- |Read from specified index of mutable array. Result is not yet evaluated.

readArray# :: MutableArray# s a -> Int# -> State# s -> (# State# s,a #)
readArray# = let x = x in x

-- |Write to specified index of mutable array.

writeArray# :: MutableArray# s a -> Int# -> a -> State# s -> State# s
writeArray# = let x = x in x

-- |Read from specified index of immutable array. Result is packaged into
--     an unboxed singleton; the result itself is not yet evaluated.

indexArray# :: Array# a -> Int# -> (# a #)
indexArray# = let x = x in x

-- |Make a mutable array immutable, without copying.

unsafeFreezeArray# :: MutableArray# s a -> State# s -> (# State# s,Array# a #)
unsafeFreezeArray# = let x = x in x

-- |Make an immutable array mutable, without copying.

unsafeThawArray# :: Array# a -> State# s -> (# State# s,MutableArray# s a #)
unsafeThawArray# = let x = x in x

data ByteArray#

data MutableByteArray# s

-- |Create a new mutable byte array of specified size (in bytes), in
--     the specified state thread.

newByteArray# :: Int# -> State# s -> (# State# s,MutableByteArray# s #)
newByteArray# = let x = x in x

-- |Create a mutable byte array that the GC guarantees not to move.

newPinnedByteArray# :: Int# -> State# s -> (# State# s,MutableByteArray# s #)
newPinnedByteArray# = let x = x in x

-- |Create a mutable byte array, aligned by the specified amount, that the GC guarantees not to move.

newAlignedPinnedByteArray# :: Int# -> Int# -> State# s -> (# State# s,MutableByteArray# s #)
newAlignedPinnedByteArray# = let x = x in x

-- |Intended for use with pinned arrays; otherwise very unsafe!

byteArrayContents# :: ByteArray# -> Addr#
byteArrayContents# = let x = x in x

sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Bool
sameMutableByteArray# = let x = x in x

-- |Make a mutable byte array immutable, without copying.

unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (# State# s,ByteArray# #)
unsafeFreezeByteArray# = let x = x in x

-- |Return the size of the array in bytes.

sizeofByteArray# :: ByteArray# -> Int#
sizeofByteArray# = let x = x in x

-- |Return the size of the array in bytes.

sizeofMutableByteArray# :: MutableByteArray# s -> Int#
sizeofMutableByteArray# = let x = x in x

-- |Read 8-bit character; offset in bytes.

indexCharArray# :: ByteArray# -> Int# -> Char#
indexCharArray# = let x = x in x

-- |Read 31-bit character; offset in 4-byte words.

indexWideCharArray# :: ByteArray# -> Int# -> Char#
indexWideCharArray# = let x = x in x

indexIntArray# :: ByteArray# -> Int# -> Int#
indexIntArray# = let x = x in x

indexWordArray# :: ByteArray# -> Int# -> Word#
indexWordArray# = let x = x in x

indexAddrArray# :: ByteArray# -> Int# -> Addr#
indexAddrArray# = let x = x in x

indexFloatArray# :: ByteArray# -> Int# -> Float#
indexFloatArray# = let x = x in x

indexDoubleArray# :: ByteArray# -> Int# -> Double#
indexDoubleArray# = let x = x in x

indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
indexStablePtrArray# = let x = x in x

indexInt8Array# :: ByteArray# -> Int# -> Int#
indexInt8Array# = let x = x in x

indexInt16Array# :: ByteArray# -> Int# -> Int#
indexInt16Array# = let x = x in x

indexInt32Array# :: ByteArray# -> Int# -> Int#
indexInt32Array# = let x = x in x

indexInt64Array# :: ByteArray# -> Int# -> Int#
indexInt64Array# = let x = x in x

indexWord8Array# :: ByteArray# -> Int# -> Word#
indexWord8Array# = let x = x in x

indexWord16Array# :: ByteArray# -> Int# -> Word#
indexWord16Array# = let x = x in x

indexWord32Array# :: ByteArray# -> Int# -> Word#
indexWord32Array# = let x = x in x

indexWord64Array# :: ByteArray# -> Int# -> Word#
indexWord64Array# = let x = x in x

-- |Read 8-bit character; offset in bytes.

readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #)
readCharArray# = let x = x in x

-- |Read 31-bit character; offset in 4-byte words.

readWideCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #)
readWideCharArray# = let x = x in x

readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #)
readIntArray# = let x = x in x

readWordArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #)
readWordArray# = let x = x in x

readAddrArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Addr# #)
readAddrArray# = let x = x in x

readFloatArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Float# #)
readFloatArray# = let x = x in x

readDoubleArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Double# #)
readDoubleArray# = let x = x in x

readStablePtrArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,StablePtr# a #)
readStablePtrArray# = let x = x in x

readInt8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #)
readInt8Array# = let x = x in x

readInt16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #)
readInt16Array# = let x = x in x

readInt32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #)
readInt32Array# = let x = x in x

readInt64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #)
readInt64Array# = let x = x in x

readWord8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #)
readWord8Array# = let x = x in x

readWord16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #)
readWord16Array# = let x = x in x

readWord32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #)
readWord32Array# = let x = x in x

readWord64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #)
readWord64Array# = let x = x in x

-- |Write 8-bit character; offset in bytes.

writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeCharArray# = let x = x in x

-- |Write 31-bit character; offset in 4-byte words.

writeWideCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeWideCharArray# = let x = x in x

writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeIntArray# = let x = x in x

writeWordArray# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWordArray# = let x = x in x

writeAddrArray# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
writeAddrArray# = let x = x in x

writeFloatArray# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s
writeFloatArray# = let x = x in x

writeDoubleArray# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
writeDoubleArray# = let x = x in x

writeStablePtrArray# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
writeStablePtrArray# = let x = x in x

writeInt8Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeInt8Array# = let x = x in x

writeInt16Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeInt16Array# = let x = x in x

writeInt32Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeInt32Array# = let x = x in x

writeInt64Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeInt64Array# = let x = x in x

writeWord8Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWord8Array# = let x = x in x

writeWord16Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWord16Array# = let x = x in x

writeWord32Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWord32Array# = let x = x in x

writeWord64Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWord64Array# = let x = x in x

-- | An arbitrary machine address assumed to point outside
-- 	 the garbage-collected heap. 

data Addr#

-- | The null address. 

nullAddr# :: Addr#
nullAddr# = let x = x in x

plusAddr# :: Addr# -> Int# -> Addr#
plusAddr# = let x = x in x

-- |Result is meaningless if two @Addr\#@s are so far apart that their
-- 	 difference doesn\'t fit in an @Int\#@.

minusAddr# :: Addr# -> Addr# -> Int#
minusAddr# = let x = x in x

-- |Return the remainder when the @Addr\#@ arg, treated like an @Int\#@,
-- 	  is divided by the @Int\#@ arg.

remAddr# :: Addr# -> Int# -> Int#
remAddr# = let x = x in x

-- |Coerce directly from address to int. Strongly deprecated.

addr2Int# :: Addr# -> Int#
addr2Int# = let x = x in x

-- |Coerce directly from int to address. Strongly deprecated.

int2Addr# :: Int# -> Addr#
int2Addr# = let x = x in x

gtAddr# :: Addr# -> Addr# -> Bool
gtAddr# = let x = x in x

geAddr# :: Addr# -> Addr# -> Bool
geAddr# = let x = x in x

eqAddr# :: Addr# -> Addr# -> Bool
eqAddr# = let x = x in x

neAddr# :: Addr# -> Addr# -> Bool
neAddr# = let x = x in x

ltAddr# :: Addr# -> Addr# -> Bool
ltAddr# = let x = x in x

leAddr# :: Addr# -> Addr# -> Bool
leAddr# = let x = x in x

-- |Reads 8-bit character; offset in bytes.

indexCharOffAddr# :: Addr# -> Int# -> Char#
indexCharOffAddr# = let x = x in x

-- |Reads 31-bit character; offset in 4-byte words.

indexWideCharOffAddr# :: Addr# -> Int# -> Char#
indexWideCharOffAddr# = let x = x in x

indexIntOffAddr# :: Addr# -> Int# -> Int#
indexIntOffAddr# = let x = x in x

indexWordOffAddr# :: Addr# -> Int# -> Word#
indexWordOffAddr# = let x = x in x

indexAddrOffAddr# :: Addr# -> Int# -> Addr#
indexAddrOffAddr# = let x = x in x

indexFloatOffAddr# :: Addr# -> Int# -> Float#
indexFloatOffAddr# = let x = x in x

indexDoubleOffAddr# :: Addr# -> Int# -> Double#
indexDoubleOffAddr# = let x = x in x

indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a
indexStablePtrOffAddr# = let x = x in x

indexInt8OffAddr# :: Addr# -> Int# -> Int#
indexInt8OffAddr# = let x = x in x

indexInt16OffAddr# :: Addr# -> Int# -> Int#
indexInt16OffAddr# = let x = x in x

indexInt32OffAddr# :: Addr# -> Int# -> Int#
indexInt32OffAddr# = let x = x in x

indexInt64OffAddr# :: Addr# -> Int# -> Int#
indexInt64OffAddr# = let x = x in x

indexWord8OffAddr# :: Addr# -> Int# -> Word#
indexWord8OffAddr# = let x = x in x

indexWord16OffAddr# :: Addr# -> Int# -> Word#
indexWord16OffAddr# = let x = x in x

indexWord32OffAddr# :: Addr# -> Int# -> Word#
indexWord32OffAddr# = let x = x in x

indexWord64OffAddr# :: Addr# -> Int# -> Word#
indexWord64OffAddr# = let x = x in x

-- |Reads 8-bit character; offset in bytes.

readCharOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Char# #)
readCharOffAddr# = let x = x in x

-- |Reads 31-bit character; offset in 4-byte words.

readWideCharOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Char# #)
readWideCharOffAddr# = let x = x in x

readIntOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #)
readIntOffAddr# = let x = x in x

readWordOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #)
readWordOffAddr# = let x = x in x

readAddrOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Addr# #)
readAddrOffAddr# = let x = x in x

readFloatOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Float# #)
readFloatOffAddr# = let x = x in x

readDoubleOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Double# #)
readDoubleOffAddr# = let x = x in x

readStablePtrOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,StablePtr# a #)
readStablePtrOffAddr# = let x = x in x

readInt8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #)
readInt8OffAddr# = let x = x in x

readInt16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #)
readInt16OffAddr# = let x = x in x

readInt32OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #)
readInt32OffAddr# = let x = x in x

readInt64OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #)
readInt64OffAddr# = let x = x in x

readWord8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #)
readWord8OffAddr# = let x = x in x

readWord16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #)
readWord16OffAddr# = let x = x in x

readWord32OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #)
readWord32OffAddr# = let x = x in x

readWord64OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #)
readWord64OffAddr# = let x = x in x

writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# s
writeCharOffAddr# = let x = x in x

writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# s
writeWideCharOffAddr# = let x = x in x

writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeIntOffAddr# = let x = x in x

writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeWordOffAddr# = let x = x in x

writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# s -> State# s
writeAddrOffAddr# = let x = x in x

writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# s -> State# s
writeFloatOffAddr# = let x = x in x

writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# s -> State# s
writeDoubleOffAddr# = let x = x in x

writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# s -> State# s
writeStablePtrOffAddr# = let x = x in x

writeInt8OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeInt8OffAddr# = let x = x in x

writeInt16OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeInt16OffAddr# = let x = x in x

writeInt32OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeInt32OffAddr# = let x = x in x

writeInt64OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s
writeInt64OffAddr# = let x = x in x

writeWord8OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeWord8OffAddr# = let x = x in x

writeWord16OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeWord16OffAddr# = let x = x in x

writeWord32OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeWord32OffAddr# = let x = x in x

writeWord64OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s
writeWord64OffAddr# = let x = x in x

-- |A @MutVar\#@ behaves like a single-element mutable array.

data MutVar# s a

-- |Create @MutVar\#@ with specified initial value in specified state thread.

newMutVar# :: a -> State# s -> (# State# s,MutVar# s a #)
newMutVar# = let x = x in x

-- |Read contents of @MutVar\#@. Result is not yet evaluated.

readMutVar# :: MutVar# s a -> State# s -> (# State# s,a #)
readMutVar# = let x = x in x

-- |Write contents of @MutVar\#@.

writeMutVar# :: MutVar# s a -> a -> State# s -> State# s
writeMutVar# = let x = x in x

sameMutVar# :: MutVar# s a -> MutVar# s a -> Bool
sameMutVar# = let x = x in x

atomicModifyMutVar# :: MutVar# s a -> (a -> b) -> State# s -> (# State# s,c #)
atomicModifyMutVar# = let x = x in x

catch# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> (b -> State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #)
catch# = let x = x in x

raise# :: a -> b
raise# = let x = x in x

raiseIO# :: a -> State# (RealWorld) -> (# State# (RealWorld),b #)
raiseIO# = let x = x in x

maskAsyncExceptions# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #)
maskAsyncExceptions# = let x = x in x

maskUninterruptible# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #)
maskUninterruptible# = let x = x in x

unmaskAsyncExceptions# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #)
unmaskAsyncExceptions# = let x = x in x

getMaskingState# :: State# (RealWorld) -> (# State# (RealWorld),Int# #)
getMaskingState# = let x = x in x

data TVar# s a

atomically# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #)
atomically# = let x = x in x

retry# :: State# (RealWorld) -> (# State# (RealWorld),a #)
retry# = let x = x in x

catchRetry# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #)
catchRetry# = let x = x in x

catchSTM# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> (b -> State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #)
catchSTM# = let x = x in x

check# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),() #)
check# = let x = x in x

-- |Create a new @TVar\#@ holding a specified initial value.

newTVar# :: a -> State# s -> (# State# s,TVar# s a #)
newTVar# = let x = x in x

-- |Read contents of @TVar\#@.  Result is not yet evaluated.

readTVar# :: TVar# s a -> State# s -> (# State# s,a #)
readTVar# = let x = x in x

-- |Read contents of @TVar\#@ outside an STM transaction

readTVarIO# :: TVar# s a -> State# s -> (# State# s,a #)
readTVarIO# = let x = x in x

-- |Write contents of @TVar\#@.

writeTVar# :: TVar# s a -> a -> State# s -> State# s
writeTVar# = let x = x in x

sameTVar# :: TVar# s a -> TVar# s a -> Bool
sameTVar# = let x = x in x

-- | 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))@.) 

data MVar# s a

-- |Create new @MVar\#@; initially empty.

newMVar# :: State# s -> (# State# s,MVar# s a #)
newMVar# = let x = x in x

-- |If @MVar\#@ is empty, block until it becomes full.
--    Then remove and return its contents, and set it empty.

takeMVar# :: MVar# s a -> State# s -> (# State# s,a #)
takeMVar# = let x = x in x

-- |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.

tryTakeMVar# :: MVar# s a -> State# s -> (# State# s,Int#,a #)
tryTakeMVar# = let x = x in x

-- |If @MVar\#@ is full, block until it becomes empty.
--    Then store value arg as its new contents.

putMVar# :: MVar# s a -> a -> State# s -> State# s
putMVar# = let x = x in x

-- |If @MVar\#@ is full, immediately return with integer 0.
--     Otherwise, store value arg as @MVar\#@\'s new contents, and return with integer 1.

tryPutMVar# :: MVar# s a -> a -> State# s -> (# State# s,Int# #)
tryPutMVar# = let x = x in x

sameMVar# :: MVar# s a -> MVar# s a -> Bool
sameMVar# = let x = x in x

-- |Return 1 if @MVar\#@ is empty; 0 otherwise.

isEmptyMVar# :: MVar# s a -> State# s -> (# State# s,Int# #)
isEmptyMVar# = let x = x in x

-- |Sleep specified number of microseconds.

delay# :: Int# -> State# s -> State# s
delay# = let x = x in x

-- |Block until input is available on specified file descriptor.

waitRead# :: Int# -> State# s -> State# s
waitRead# = let x = x in x

-- |Block until output is possible on specified file descriptor.

waitWrite# :: Int# -> State# s -> State# s
waitWrite# = let x = x in x

-- | @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 State# s

-- | @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 RealWorld

-- |(In a non-concurrent implementation, this can be a singleton
-- 	type, whose (unique) value is returned by @myThreadId\#@.  The 
-- 	other operations can be omitted.)

data ThreadId#

fork# :: a -> State# (RealWorld) -> (# State# (RealWorld),ThreadId# #)
fork# = let x = x in x

forkOn# :: Int# -> a -> State# (RealWorld) -> (# State# (RealWorld),ThreadId# #)
forkOn# = let x = x in x

killThread# :: ThreadId# -> a -> State# (RealWorld) -> State# (RealWorld)
killThread# = let x = x in x

yield# :: State# (RealWorld) -> State# (RealWorld)
yield# = let x = x in x

myThreadId# :: State# (RealWorld) -> (# State# (RealWorld),ThreadId# #)
myThreadId# = let x = x in x

labelThread# :: ThreadId# -> Addr# -> State# (RealWorld) -> State# (RealWorld)
labelThread# = let x = x in x

isCurrentThreadBound# :: State# (RealWorld) -> (# State# (RealWorld),Int# #)
isCurrentThreadBound# = let x = x in x

noDuplicate# :: State# (RealWorld) -> State# (RealWorld)
noDuplicate# = let x = x in x

threadStatus# :: ThreadId# -> State# (RealWorld) -> (# State# (RealWorld),Int# #)
threadStatus# = let x = x in x

data Weak# b

mkWeak# :: o -> b -> c -> State# (RealWorld) -> (# State# (RealWorld),Weak# b #)
mkWeak# = let x = x in x

mkWeakForeignEnv# :: o -> b -> Addr# -> Addr# -> Int# -> Addr# -> State# (RealWorld) -> (# State# (RealWorld),Weak# b #)
mkWeakForeignEnv# = let x = x in x

deRefWeak# :: Weak# a -> State# (RealWorld) -> (# State# (RealWorld),Int#,a #)
deRefWeak# = let x = x in x

finalizeWeak# :: Weak# a -> State# (RealWorld) -> (# State# (RealWorld),Int#,State# (RealWorld) -> (# State# (RealWorld),() #) #)
finalizeWeak# = let x = x in x

touch# :: o -> State# (RealWorld) -> State# (RealWorld)
touch# = let x = x in x

data StablePtr# a

data StableName# a

makeStablePtr# :: a -> State# (RealWorld) -> (# State# (RealWorld),StablePtr# a #)
makeStablePtr# = let x = x in x

deRefStablePtr# :: StablePtr# a -> State# (RealWorld) -> (# State# (RealWorld),a #)
deRefStablePtr# = let x = x in x

eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int#
eqStablePtr# = let x = x in x

makeStableName# :: a -> State# (RealWorld) -> (# State# (RealWorld),StableName# a #)
makeStableName# = let x = x in x

eqStableName# :: StableName# a -> StableName# a -> Int#
eqStableName# = let x = x in x

stableNameToInt# :: StableName# a -> Int#
stableNameToInt# = let x = x in x

reallyUnsafePtrEquality# :: a -> a -> Int#
reallyUnsafePtrEquality# = let x = x in x

par# :: a -> Int#
par# = let x = x in x

getSpark# :: State# s -> (# State# s,Int#,a #)
getSpark# = let x = x in x

-- | Returns the number of sparks in the local spark pool. 

numSparks# :: State# s -> (# State# s,Int# #)
numSparks# = let x = x in x

parGlobal# :: a -> Int# -> Int# -> Int# -> Int# -> b -> Int#
parGlobal# = let x = x in x

parLocal# :: a -> Int# -> Int# -> Int# -> Int# -> b -> Int#
parLocal# = let x = x in x

parAt# :: b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int#
parAt# = let x = x in x

parAtAbs# :: a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int#
parAtAbs# = let x = x in x

parAtRel# :: a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int#
parAtRel# = let x = x in x

parAtForNow# :: b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int#
parAtForNow# = let x = x in x

dataToTag# :: a -> Int#
dataToTag# = let x = x in x

tagToEnum# :: Int# -> a
tagToEnum# = let x = x in x

-- |Primitive bytecode type.

data BCO#

-- |Convert an @Addr\#@ to a followable type.

addrToHValue# :: Addr# -> (# a #)
addrToHValue# = let x = x in x

mkApUpd0# :: BCO# -> (# a #)
mkApUpd0# = let x = x in x

newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# s -> (# State# s,BCO# #)
newBCO# = let x = x in x

unpackClosure# :: a -> (# Addr#,Array# b,ByteArray# #)
unpackClosure# = let x = x in x

getApStackVal# :: a -> Int# -> (# Int#,b #)
getApStackVal# = let x = x in x

traceCcs# :: a -> b -> b
traceCcs# = let x = x in x

-- | Evaluates its first argument to head normal form, and then returns its second
-- 	argument as the result. 

seq :: a -> b -> b
seq = let x = x in x

-- | 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.
-- 
-- 	It is good practice to mark the function with an INLINABLE pragma at
--         its definition, (a) so that GHC guarantees to expose its unfolding regardless
--         of size, and (b) so that you have control over exactly what is inlined. 

inline :: a -> a
inline = let x = x in x

-- | 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. 

lazy :: a -> a
lazy = let x = x in x

-- | 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 @Any@s 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. 

data Any a

-- | 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.
-- 	
--         

unsafeCoerce# :: a -> b
unsafeCoerce# = let x = x in x

-- | 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. 

traceEvent# :: Addr# -> State# s -> State# s
traceEvent# = let x = x in x