[[project @ 2000-04-06 15:05:37 by simonmar]
simonmar**20000406150538
Kill the libraries chapter, and move the material on
PrelGHC into the section on language extensions.
] {
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 115
-sloshing MutableByteArray#s around your program), you may wish to
-check if there are system libraries that provide a “Haskellised
-veneer” over the features you want. See .
+sloshing MutableByteArray#s around your
+program), you may wish to check if there are libraries that provide a
+“Haskellised veneer” over the features you want. See the
+accompanying library documentation.
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 121
-
+
+Unboxed types and primitive operations
+
+PrelGHC module
+
+
+This module defines all the types which are primitive in Glasgow
+Haskell, and the operations provided for them.
+
+
+
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 139
+Most types in GHC are boxed, which means
+that values of that type are represented by a pointer to a heap
+object. The representation of a Haskell Int, for
+example, is a two-word heap object. An unboxed
+type, however, is represented by the value itself, no pointers or heap
+allocation are involved.
+
+
+
+Unboxed types correspond to the “raw machine” types you
+would use in C: Int# (long int),
+Double# (double), Addr#
+(void *), etc. The primitive operations
+(PrimOps) on these types are what you might expect; e.g.,
+(+#) is addition on
+Int#s, and is the machine-addition that we all
+know and love—usually one instruction.
+
+
+
+Primitive (unboxed) types cannot be defined in Haskell, and are
+therefore built into the language and compiler. Primitive types are
+always unlifted; that is, a value of a primitive type cannot be
+bottom. We use the convention that primitive types, values, and
+operations have a # suffix.
+
+
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 167
-These types correspond to the “raw machine” types you would use in
-C: Int# (long int), Double# (double), Addr# (void *), etc. The
-primitive operations (PrimOps) on these types are what you
-might expect; e.g., (+#) is addition on Int#s, and is the
-machine-addition that we all know and love—usually one instruction.
+Primitive values are often represented by a simple bit-pattern, such
+as Int#, Float#,
+Double#. But this is not necessarily the case:
+a primitive value might be represented by a pointer to a
+heap-allocated object. Examples include
+Array#, the type of primitive arrays. A
+primitive array is heap-allocated because it is too big a value to fit
+in a register, and would be too expensive to copy around; in a sense,
+it is accidental that it is represented by a pointer. If a pointer
+represents a primitive value, then it really does point to that value:
+no unevaluated thunks, no indirections…nothing can be at the
+other end of the pointer than the primitive value.
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 182
-There are some restrictions on the use of unboxed types, the main one
-being that you can't pass an unboxed value to a polymorphic function
-or store one in a polymorphic data type. This rules out things like
-[Int#] (i.e. lists of unboxed integers). The reason for this
-restriction is that polymorphic arguments and constructor fields are
-assumed to be pointers: if an unboxed integer is stored in one of
-these, the garbage collector would attempt to follow it, leading to
-unpredictable space leaks. Or a seq operation on the polymorphic
-component may attempt to dereference the pointer, with disastrous
-results. Even worse, the unboxed value might be larger than a pointer
+There are some restrictions on the use of primitive types, the main
+one being that you can't pass a primitive value to a polymorphic
+function or store one in a polymorphic data type. This rules out
+things like [Int#] (i.e. lists of primitive
+integers). The reason for this restriction is that polymorphic
+arguments and constructor fields are assumed to be pointers: if an
+unboxed integer is stored in one of these, the garbage collector would
+attempt to follow it, leading to unpredictable space leaks. Or a
+seq operation on the polymorphic component may
+attempt to dereference the pointer, with disastrous results. Even
+worse, the unboxed value might be larger than a pointer
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 198
-go a lot faster than its “standard” counterpart—we saw a
-threefold speedup on one example.
+go a lot faster than its “standard”
+counterpart—we saw a threefold speedup on one example.
+
+
+
+
+
+Unboxed Tuples
+
+
+
+Unboxed tuples aren't really exported by PrelGHC,
+they're available by default with . An
+unboxed tuple looks like this:
+
+
+
+
+
+(# e_1, ..., e_n #)
+
+
+
+
+
+where e_1..e_n are expressions of any
+type (primitive or non-primitive). The type of an unboxed tuple looks
+the same.
+
+
+
+Unboxed tuples are used for functions that need to return multiple
+values, but they avoid the heap allocation normally associated with
+using fully-fledged tuples. When an unboxed tuple is returned, the
+components are put directly into registers or on the stack; the
+unboxed tuple itself does not have a composite representation. Many
+of the primitive operations listed in this section return unboxed
+tuples.
+
+
+
+There are some pretty stringent restrictions on the use of unboxed tuples:
+
+
+
+
+
+
+
+
+ Unboxed tuple types are subject to the same restrictions as
+other unboxed types; i.e. they may not be stored in polymorphic data
+structures or passed to polymorphic functions.
+
+
+
+
+
+
+ Unboxed tuples may only be constructed as the direct result of
+a function, and may only be deconstructed with a case expression.
+eg. the following are valid:
+
+
+
+f x y = (# x+1, y-1 #)
+g x = case f x x of { (# a, b #) -> a + b }
+
+
+
+but the following are invalid:
+
+
+
+f x y = g (# x, y #)
+g (# x, y #) = x + y
+
+
+
+
+
+
+
+
+ No variable can have an unboxed tuple type. This is illegal:
+
+
+
+f :: (# Int, Int #) -> (# Int, Int #)
+f x = x
+
+
+
+because x has an unboxed tuple type.
+
+
+
+
+
+
+
+
+
+Note: we may relax some of these restrictions in the future.
+
+
+
+The IO and ST monads use unboxed tuples to avoid unnecessary
+allocation during sequences of operations.
+
+
+
+
+
+Character and numeric types
+
+
+character types, primitive
+numeric types, primitive
+integer types, primitive
+floating point types, primitive
+There are the following obvious primitive types:
+
+
+
+
+
+type Char#
+type Int#
+type Word#
+type Addr#
+type Float#
+type Double#
+type Int64#
+type Word64#
+
+
+Char#
+Int#
+Word#
+Addr#
+Float#
+Double#
+Int64#
+Word64#
+
+
+
+If you really want to know their exact equivalents in C, see
+ghc/includes/StgTypes.h in the GHC source tree.
+
+
+
+Literals for these types may be written as follows:
+
+
+
+
+
+1# an Int#
+1.2# a Float#
+1.34## a Double#
+'a'# a Char#; for weird characters, use '\o<octal>'#
+"a"# an Addr# (a `char *')
+
+
+literals, primitive
+constants, primitive
+numbers, primitive
+
+
+
+
+
+Comparison operations
+
+
+comparisons, primitive
+operators, comparison
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 380
-Please see for the details of unboxed types and the
-operations on them.
+
+
+{>,>=,==,/=,<,<=}# :: Int# -> Int# -> Bool
+
+{gt,ge,eq,ne,lt,le}Char# :: Char# -> Char# -> Bool
+ -- ditto for Word# and Addr#
+
+
+>#
+>=#
+==#
+/=#
+<#
+<=#
+gt{Char,Word,Addr}#
+ge{Char,Word,Addr}#
+eq{Char,Word,Addr}#
+ne{Char,Word,Addr}#
+lt{Char,Word,Addr}#
+le{Char,Word,Addr}#
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 402
+
+
+
+Primitive-character operations
+
+
+characters, primitive operations
+operators, primitive character
+
+
+
+
+
+ord# :: Char# -> Int#
+chr# :: Int# -> Char#
+
+
+ord#
+chr#
+
+
+
+
+
+Primitive-Int operations
+
+
+integers, primitive operations
+operators, primitive integer
+
+
+
+
+
+{+,-,*,quotInt,remInt,gcdInt}# :: Int# -> Int# -> Int#
+negateInt# :: Int# -> Int#
+
+iShiftL#, iShiftRA#, iShiftRL# :: Int# -> Int# -> Int#
+ -- shift left, right arithmetic, right logical
+
+addIntC#, subIntC#, mulIntC# :: Int# -> Int# -> (# Int#, Int# #)
+ -- add, subtract, multiply with carry
+
+
++#
+-#
+*#
+quotInt#
+remInt#
+gcdInt#
+iShiftL#
+iShiftRA#
+iShiftRL#
+addIntC#
+subIntC#
+mulIntC#
+shift operations, integer
+
+
+
+Note: No error/overflow checking!
+
+
+
+
+
+Primitive-Double and Float operations
+
+
+floating point numbers, primitive
+operators, primitive floating point
+
+
+
+
+
+{+,-,*,/}## :: Double# -> Double# -> Double#
+{<,<=,==,/=,>=,>}## :: Double# -> Double# -> Bool
+negateDouble# :: Double# -> Double#
+double2Int# :: Double# -> Int#
+int2Double# :: Int# -> Double#
+
+{plus,minux,times,divide}Float# :: Float# -> Float# -> Float#
+{gt,ge,eq,ne,lt,le}Float# :: Float# -> Float# -> Bool
+negateFloat# :: Float# -> Float#
+float2Int# :: Float# -> Int#
+int2Float# :: Int# -> Float#
+
+
+
+
+
++##
+-##
+*##
+/##
+<##
+<=##
+==##
+=/##
+>=##
+>##
+negateDouble#
+double2Int#
+int2Double#
+
+
+
+plusFloat#
+minusFloat#
+timesFloat#
+divideFloat#
+gtFloat#
+geFloat#
+eqFloat#
+neFloat#
+ltFloat#
+leFloat#
+negateFloat#
+float2Int#
+int2Float#
+
+
+
+And a full complement of trigonometric functions:
+
+
+
+
+
+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#
+powerDouble# :: Double# -> Double# -> Double#
+
+
+trigonometric functions, primitive
+
+
+
+similarly for Float#.
+
+
+
+There are two coercion functions for Float#/Double#:
+
+
+
+
+
+float2Double# :: Float# -> Double#
+double2Float# :: Double# -> Float#
+
+
+float2Double#
+double2Float#
+
+
+
+The primitive version of decodeDouble
+(encodeDouble is implemented as an external C
+function):
+
+
+
+
+
+decodeDouble# :: Double# -> PrelNum.ReturnIntAndGMP
+
+
+encodeDouble#
+decodeDouble#
+
+
+
+(And the same for Float#s.)
+
+
+
+
+
+Operations on/for Integers (interface to GMP)
+
+
+
+arbitrary precision integers
+Integer, operations on
+
+
+
+We implement Integers (arbitrary-precision
+integers) using the GNU multiple-precision (GMP) package (version
+2.0.2).
+
+
+
+The data type for Integer is either a small
+integer, represented by an Int, or a large integer
+represented using the pieces required by GMP's
+MP_INT in gmp.h (see
+gmp.info in
+ghc/includes/runtime/gmp). It comes out as:
+
+
+
+
+
+data Integer = S# Int# -- small integers
+ | J# Int# ByteArray# -- large integers
+
+
+Integer type The primitive
+ops to support large Integers use the
+“pieces” of the representation, and are as follows:
+
+
+
+
+
+negateInteger# :: Int# -> ByteArray# -> Integer
+
+{plus,minus,times}Integer#, gcdInteger#,
+ quotInteger#, remInteger#, divExactInteger#
+ :: Int# -> ByteArray#
+ -> Int# -> ByteArray#
+ -> (# Int#, ByteArray# #)
+
+cmpInteger#
+ :: Int# -> ByteArray#
+ -> Int# -> ByteArray#
+ -> Int# -- -1 for <; 0 for ==; +1 for >
+
+cmpIntegerInt#
+ :: Int# -> ByteArray#
+ -> Int#
+ -> Int# -- -1 for <; 0 for ==; +1 for >
+
+gcdIntegerInt# ::
+ :: Int# -> ByteArray#
+ -> Int#
+ -> Int#
+
+divModInteger#, quotRemInteger#
+ :: Int# -> ByteArray#
+ -> Int# -> ByteArray#
+ -> (# Int#, ByteArray#,
+ Int#, ByteArray# #)
+
+integer2Int# :: Int# -> ByteArray# -> Int#
+
+int2Integer# :: Int# -> Integer -- NB: no error-checking on these two!
+word2Integer# :: Word# -> Integer
+
+addr2Integer# :: Addr# -> Integer
+ -- the Addr# is taken to be a `char *' string
+ -- to be converted into an Integer.
+
+
+negateInteger#
+plusInteger#
+minusInteger#
+timesInteger#
+quotInteger#
+remInteger#
+gcdInteger#
+gcdIntegerInt#
+divExactInteger#
+cmpInteger#
+divModInteger#
+quotRemInteger#
+integer2Int#
+int2Integer#
+word2Integer#
+addr2Integer#
+
+
+
+
+
+Words and addresses
+
+
+word, primitive type
+address, primitive type
+unsigned integer, primitive type
+pointer, primitive type
+
+
+
+A Word# is used for bit-twiddling operations.
+It is the same size as an Int#, but has no sign
+nor any arithmetic operations.
+
+
+type Word# -- Same size/etc as Int# but *unsigned*
+type Addr# -- A pointer from outside the "Haskell world" (from C, probably);
+ -- described under "arrays"
+
+
+Word#
+Addr#
+
+
+
+Word#s and Addr#s have
+the usual comparison operations. Other
+unboxed-Word ops (bit-twiddling and coercions):
+
+
+
+
+
+{gt,ge,eq,ne,lt,le}Word# :: Word# -> Word# -> Bool
+
+and#, or#, xor# :: Word# -> Word# -> Word#
+ -- standard bit ops.
+
+quotWord#, remWord# :: Word# -> Word# -> Word#
+ -- word (i.e. unsigned) versions are different from int
+ -- versions, so we have to provide these explicitly.
+
+not# :: Word# -> Word#
+
+shiftL#, shiftRL# :: Word# -> Int# -> Word#
+ -- shift left, right logical
+
+int2Word# :: Int# -> Word# -- just a cast, really
+word2Int# :: Word# -> Int#
+
+
+bit operations, Word and Addr
+gtWord#
+geWord#
+eqWord#
+neWord#
+ltWord#
+leWord#
+and#
+or#
+xor#
+not#
+quotWord#
+remWord#
+shiftL#
+shiftRA#
+shiftRL#
+int2Word#
+word2Int#
+
+
+
+Unboxed-Addr ops (C casts, really):
+
+
+{gt,ge,eq,ne,lt,le}Addr# :: Addr# -> Addr# -> Bool
+
+int2Addr# :: Int# -> Addr#
+addr2Int# :: Addr# -> Int#
+addr2Integer# :: Addr# -> (# Int#, ByteArray# #)
+
+
+gtAddr#
+geAddr#
+eqAddr#
+neAddr#
+ltAddr#
+leAddr#
+int2Addr#
+addr2Int#
+addr2Integer#
+
+
+
+The casts between Int#,
+Word# and Addr#
+correspond to null operations at the machine level, but are required
+to keep the Haskell type checker happy.
+
+
+
+Operations for indexing off of C pointers
+(Addr#s) to snatch values are listed under
+“arrays”.
+
+
+
+
+
+Arrays
+
+
+arrays, primitive
+
+
+
+The type Array# elt is the type of primitive,
+unpointed arrays of values of type elt.
+
+
+
+
+
+type Array# elt
+
+
+Array#
+
+
+
+Array# is more primitive than a Haskell
+array—indeed, the Haskell Array interface is
+implemented using Array#—in that an
+Array# is indexed only by
+Int#s, starting at zero. It is also more
+primitive by virtue of being unboxed. That doesn't mean that it isn't
+a heap-allocated object—of course, it is. Rather, being unboxed
+means that it is represented by a pointer to the array itself, and not
+to a thunk which will evaluate to the array (or to bottom). The
+components of an Array# are themselves boxed.
+
+
+
+The type ByteArray# is similar to
+Array#, except that it contains just a string
+of (non-pointer) bytes.
+
+
+
+
+
+type ByteArray#
+
+
+ByteArray#
+
+
+
+Arrays of these types are useful when a Haskell program wishes to
+construct a value to pass to a C procedure. It is also possible to use
+them to build (say) arrays of unboxed characters for internal use in a
+Haskell program. Given these uses, ByteArray#
+is deliberately a bit vague about the type of its components.
+Operations are provided to extract values of type
+Char#, Int#,
+Float#, Double#, and
+Addr# from arbitrary offsets within a
+ByteArray#. (For type
+Foo#, the $i$th offset gets you the $i$th
+Foo#, not the Foo# at
+byte-position $i$. Mumble.) (If you want a
+Word#, grab an Int#,
+then coerce it.)
+
+
+
+Lastly, we have static byte-arrays, of type
+Addr# [mentioned previously]. (Remember
+the duality between arrays and pointers in C.) Arrays of this types
+are represented by a pointer to an array in the world outside Haskell,
+so this pointer is not followed by the garbage collector. In other
+respects they are just like ByteArray#. They
+are only needed in order to pass values from C to Haskell.
+
+
+
+
+
+Reading and writing
+
+
+Primitive arrays are linear, and indexed starting at zero.
+
+
+
+The size and indices of a ByteArray#, Addr#, and
+MutableByteArray# are all in bytes. It's up to the program to
+calculate the correct byte offset from the start of the array. This
+allows a ByteArray# to contain a mixture of values of different
+type, which is often needed when preparing data for and unpicking
+results from C. (Umm…not true of indices…WDP 95/09)
+
+
+
+Should we provide some sizeOfDouble# constants?
+
+
+
+Out-of-range errors on indexing should be caught by the code which
+uses the primitive operation; the primitive operations themselves do
+not check for out-of-range indexes. The intention is that the
+primitive ops compile to one machine instruction or thereabouts.
+
+
+
+We use the terms “reading” and “writing” to refer to accessing
+mutable arrays (see ), and
+“indexing” to refer to reading a value from an immutable
+array.
+
+
+
+Immutable byte arrays are straightforward to index (all indices in bytes):
+
+
+indexCharArray# :: ByteArray# -> Int# -> Char#
+indexIntArray# :: ByteArray# -> Int# -> Int#
+indexAddrArray# :: ByteArray# -> Int# -> Addr#
+indexFloatArray# :: ByteArray# -> Int# -> Float#
+indexDoubleArray# :: ByteArray# -> Int# -> Double#
+
+indexCharOffAddr# :: Addr# -> Int# -> Char#
+indexIntOffAddr# :: Addr# -> Int# -> Int#
+indexFloatOffAddr# :: Addr# -> Int# -> Float#
+indexDoubleOffAddr# :: Addr# -> Int# -> Double#
+indexAddrOffAddr# :: Addr# -> Int# -> Addr#
+ -- Get an Addr# from an Addr# offset
+
+
+indexCharArray#
+indexIntArray#
+indexAddrArray#
+indexFloatArray#
+indexDoubleArray#
+indexCharOffAddr#
+indexIntOffAddr#
+indexFloatOffAddr#
+indexDoubleOffAddr#
+indexAddrOffAddr#
+
+
+
+The last of these, indexAddrOffAddr#, extracts an Addr# using an offset
+from another Addr#, thereby providing the ability to follow a chain of
+C pointers.
+
+
+
+Something a bit more interesting goes on when indexing arrays of boxed
+objects, because the result is simply the boxed object. So presumably
+it should be entered—we never usually return an unevaluated
+object! This is a pain: primitive ops aren't supposed to do
+complicated things like enter objects. The current solution is to
+return a single element unboxed tuple (see ).
+
+
+
+
+
+indexArray# :: Array# elt -> Int# -> (# elt #)
+
+
+indexArray#
+
+
+
+
+
+The state type
+
+
+state, primitive type
+State#
+
+
+
+The primitive type State# represents the state of a state
+transformer. It is parameterised on the desired type of state, which
+serves to keep states from distinct threads distinct from one another.
+But the only effect of this parameterisation is in the type
+system: all values of type State# are represented in the same way.
+Indeed, they are all represented by nothing at all! The code
+generator “knows” to generate no code, and allocate no registers
+etc, for primitive states.
+
+
+
+
+
+type State# s
+
+
+
+
+
+The type GHC.RealWorld is truly opaque: there are no values defined
+of this type, and no operations over it. It is “primitive” in that
+sense - but it is not unlifted! Its only role in life is to be
+the type which distinguishes the IO state transformer.
+
+
+
+
+
+data RealWorld
+
+
+
+
+
+
+
+State of the world
+
+
+A single, primitive, value of type State# RealWorld is provided.
+
+
+
+
+
+realWorld# :: State# RealWorld
+
+
+realWorld# state object
+
+
+
+(Note: in the compiler, not a PrimOp; just a mucho magic
+Id. Exported from GHC, though).
+
+
+
+
+
+Mutable arrays
+
+
+mutable arrays
+arrays, mutable
+Corresponding to Array# and ByteArray#, we have the types of
+mutable versions of each. In each case, the representation is a
+pointer to a suitable block of (mutable) heap-allocated storage.
+
+
+
+
+
+type MutableArray# s elt
+type MutableByteArray# s
+
+
+MutableArray#
+MutableByteArray#
+
+
+
+Allocation
+
+
+mutable arrays, allocation
+arrays, allocation
+allocation, of mutable arrays
+
+
+
+Mutable arrays can be allocated. Only pointer-arrays are initialised;
+arrays of non-pointers are filled in by “user code” rather than by
+the array-allocation primitive. Reason: only the pointer case has to
+worry about GC striking with a partly-initialised array.
+
+
+
+
+
+newArray# :: Int# -> elt -> State# s -> (# State# s, MutableArray# s elt #)
+
+newCharArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
+newIntArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
+newAddrArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
+newFloatArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
+newDoubleArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
+
+
+newArray#
+newCharArray#
+newIntArray#
+newAddrArray#
+newFloatArray#
+newDoubleArray#
+
+
+
+The size of a ByteArray# is given in bytes.
+
+
+
+
+
+Reading and writing
+
+
+arrays, reading and writing
+
+
+
+
+
+readArray# :: MutableArray# s elt -> Int# -> State# s -> (# State# s, elt #)
+readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
+readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
+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# #)
+
+writeArray# :: MutableArray# s elt -> Int# -> elt -> State# s -> State# s
+writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
+writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> 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
+
+
+readArray#
+readCharArray#
+readIntArray#
+readAddrArray#
+readFloatArray#
+readDoubleArray#
+writeArray#
+writeCharArray#
+writeIntArray#
+writeAddrArray#
+writeFloatArray#
+writeDoubleArray#
+
+
+
+
+
+Equality
+
+
+arrays, testing for equality
+
+
+
+One can take “equality” of mutable arrays. What is compared is the
+name or reference to the mutable array, not its contents.
+
+
+
+
+
+sameMutableArray# :: MutableArray# s elt -> MutableArray# s elt -> Bool
+sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Bool
+
+
+sameMutableArray#
+sameMutableByteArray#
+
+
+
+
+
+Freezing mutable arrays
+
+
+arrays, freezing mutable
+freezing mutable arrays
+mutable arrays, freezing
+
+
+
+Only unsafe-freeze has a primitive. (Safe freeze is done directly in Haskell
+by copying the array and then using unsafeFreeze.)
+
+
+
+
+
+unsafeFreezeArray# :: MutableArray# s elt -> State# s -> (# State# s, Array# s elt #)
+unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
+
+
+unsafeFreezeArray#
+unsafeFreezeByteArray#
+
+
+
+
+
+
+
+Synchronizing variables (M-vars)
+
+
+synchronising variables (M-vars)
+M-Vars
+
+
+
+Synchronising variables are the primitive type used to implement
+Concurrent Haskell's MVars (see the Concurrent Haskell paper for
+the operational behaviour of these operations).
+
+
+
+
+
+type MVar# s elt -- primitive
+
+newMVar# :: State# s -> (# State# s, MVar# s elt #)
+takeMVar# :: SynchVar# s elt -> State# s -> (# State# s, elt #)
+putMVar# :: SynchVar# s elt -> State# s -> State# s
+
+
+SynchVar#
+newSynchVar#
+takeMVar
+putMVar
+
+
+
+
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1340
-The libraries section gives more details on all these “primitive
-array” types and the operations on them, . Some of these extensions
-are also supported by Hugs, and the supporting libraries are described
-in the GHC/Hugs Extension Libraries
-document.
+The libraries documentatation gives more details on all these
+“primitive array” types and the operations on them.
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1386
-fooH :: Char -> Int -> Double -> Word -> IO Double
+fooH :: Char -> Int -> Double -> Word -> IO Double
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1411
- = _casm_ “%r = getenv((char *) %0);” name >>= \ litstring ->
+ = _casm_ “%r = getenv((char *) %0);” name >>= \ litstring ->
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1469
-fooH :: Char -> Int -> Double -> Word -> IO Double
+fooH :: Char -> Int -> Double -> Word -> IO Double
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1671
-storeH :: Int -> IO ()
-storeH x = makeStablePtr x >>= \ stable_x ->
+storeH :: Int -> IO ()
+storeH x = makeStablePtr x >>= \ stable_x ->
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1676
-fetchH x = _ccall_ fetchC >>= \ stable_x ->
- deRefStablePtr stable_x >>= \ x ->
- freeStablePtr stable_x >>
+fetchH x = _ccall_ fetchC >>= \ stable_x ->
+ deRefStablePtr stable_x >>= \ x ->
+ freeStablePtr stable_x >>
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1693
-freeStablePtr :: StablePtr a -> IO ()
+freeStablePtr :: StablePtr a -> IO ()
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1824
-atan2d :: Double -> Double -> Double
+atan2d :: Double -> Double -> Double
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1827
-sincosd :: Double -> (Double, Double)
+sincosd :: Double -> (Double, Double)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1851
-update :: EFS x -> Int -> x -> EFS x
-lookup :: EFS a -> Int -> a
+update :: EFS x -> Int -> x -> EFS x
+lookup :: EFS a -> Int -> a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1857
- makeStablePtr x >>= \ stable_x ->
+ makeStablePtr x >>= \ stable_x ->
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1861
- _ccall_ lookupEFS a i >>= \ stable_x ->
+ _ccall_ lookupEFS a i >>= \ stable_x ->
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1878
-trace :: String -> a -> a
+trace :: String -> a -> a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1881
- ((_ccall_ PreTraceHook sTDERR{-msg-}):: IO ()) >>
- fputs sTDERR string >>
- ((_ccall_ PostTraceHook sTDERR{-msg-}):: IO ()) >>
+ ((_ccall_ PreTraceHook sTDERR{-msg-}):: IO ()) >>
+ fputs sTDERR string >>
+ ((_ccall_ PostTraceHook sTDERR{-msg-}):: IO ()) >>
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 1977
-f :: Int -> IO Double
+f :: Int -> IO Double
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2247
- forall tv1..tvn (c1, ...,cn) => type
+ forall tv1..tvn (c1, ...,cn) => type
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2275
- forall a. Eq a => Int
+ forall a. Eq a => Int
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2299
- forall a. C a b => burble
+ forall a. C a b => burble
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2308
- forall a. Eq b => burble
+ forall a. Eq b => burble
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2340
- f :: Eq (m a) => [m a] -> [m a]
- g :: Eq [a] => ...
+ f :: Eq (m a) => [m a] -> [m a]
+ g :: Eq [a] => ...
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2366
- union :: c a -> c a -> c a
+ union :: c a -> c a -> c a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2384
- op :: D b => a -> b -> b
+ op :: D b => a -> b -> b
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2387
- class C a => D a where { ... }
+ class C a => D a where { ... }
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2406
- class Functor (m k) => FiniteMap m k where
+ class Functor (m k) => FiniteMap m k where
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2409
- class (Monad m, Monad (t m)) => Transform t m where
- lift :: m a -> (t m) a
+ class (Monad m, Monad (t m)) => Transform t m where
+ lift :: m a -> (t m) a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2428
- mapC :: Collection c b => (a->b) -> c a -> c b
+ mapC :: Collection c b => (a->b) -> c a -> c b
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2439
- op :: Eq a => (a,b) -> (a,b)
+ op :: Eq a => (a,b) -> (a,b)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2450
- class Eq a => C a where
- op ::(a,b) -> (a,b)
+ class Eq a => C a where
+ op ::(a,b) -> (a,b)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2471
- insert :: s -> a -> s
+ insert :: s -> a -> s
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2486
- insert :: s a -> a -> s a
+ insert :: s a -> a -> s a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2500
- class CollE s => Coll s a where
- insert :: s -> a -> s
+ class CollE s => Coll s a where
+ insert :: s -> a -> s
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2528
- instance context1 => C type1 where ...
- instance context2 => C type2 where ...
+ instance context1 => C type1 where ...
+ instance context2 => C type2 where ...
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2605
-The instance "head" is the bit after the "=>" in an instance decl. For
+The instance "head" is the bit after the "=>" in an instance decl. For
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2634
- instance C a => C a where ...
+ instance C a => C a where ...
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2655
- class (C1 a, C2 a, C3 a) => C a where { }
+ class (C1 a, C2 a, C3 a) => C a where { }
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2657
- instance (C1 a, C2 a, C3 a) => C a where { }
+ instance (C1 a, C2 a, C3 a) => C a where { }
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2665
- f :: C a => ...
+ f :: C a => ...
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2673
- f :: (C1 a, C2 a, C3 a) => ...
+ f :: (C1 a, C2 a, C3 a) => ...
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2732
-instance C a b => Eq (a,b) where ...
+instance C a b => Eq (a,b) where ...
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2740
-instance C Int b => Foo b where ...
+instance C Int b => Foo b where ...
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2778
- forall a b. (Ord a, Eq b) => a -> b -> a
+ forall a b. (Ord a, Eq b) => a -> b -> a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2796
- g :: b -> b
+ g :: b -> b
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2808
- g :: forall b. (b -> b)
+ g :: forall b. (b -> b)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2829
-data T a = T1 (forall b. b -> b -> b) a
+data T a = T1 (forall b. b -> b -> b) a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2831
-data MonadT m = MkMonad { return :: forall a. a -> m a,
- bind :: forall a b. m a -> (a -> m b) -> m b
+data MonadT m = MkMonad { return :: forall a. a -> m a,
+ bind :: forall a b. m a -> (a -> m b) -> m b
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2835
-newtype Swizzle = MkSwizzle (Ord a => [a] -> [a])
+newtype Swizzle = MkSwizzle (Ord a => [a] -> [a])
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2848
-T1 :: forall a. (forall b. b -> b -> b) -> a -> T a
-MkMonad :: forall m. (forall a. a -> m a)
- -> (forall a b. m a -> (a -> m b) -> m b)
- -> MonadT m
-MkSwizzle :: (Ord a => [a] -> [a]) -> Swizzle
+T1 :: forall a. (forall b. b -> b -> b) -> a -> T a
+MkMonad :: forall m. (forall a. a -> m a)
+ -> (forall a b. m a -> (a -> m b) -> m b)
+ -> MonadT m
+MkSwizzle :: (Ord a => [a] -> [a]) -> Swizzle
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2871
- data T a = MkT (Either a b) (b -> b)
+ data T a = MkT (Either a b) (b -> b)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2877
- data T a = MkT (forall b. Either a b) (forall b. b -> b)
+ data T a = MkT (forall b. Either a b) (forall b. b -> b)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2899
-(T1 (\xy->x) 3) :: T Int
+(T1 (\xy->x) 3) :: T Int
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2906
- Just y -> k y
- Nothing -> Nothing
+ Just y -> k y
+ Nothing -> Nothing
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2933
- f :: T a -> a -> (a, Char)
+ f :: T a -> a -> (a, Char)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2936
- g :: (Ord a, Ord b) => Swizzle -> [a] -> (a -> b) -> [b]
+ g :: (Ord a, Ord b) => Swizzle -> [a] -> (a -> b) -> [b]
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2939
- h :: MonadT m -> [m a] -> m [a]
+ h :: MonadT m -> [m a] -> m [a]
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2941
- h m (x:xs) = bind m x $ \y ->
- bind m (h m xs) $ \ys ->
+ h m (x:xs) = bind m x $ \y ->
+ bind m (h m xs) $ \ys ->
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2962
- runTIM :: (forall s. TIM s a) -> Maybe a
+ runTIM :: (forall s. TIM s a) -> Maybe a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 2974
- runTIM :: (forall s. TIM s a) -> Maybe a
- runTIM tm = case tm of { TIM m -> runST m }
+ runTIM :: (forall s. TIM s a) -> Maybe a
+ runTIM tm = case tm of { TIM m -> runST m }
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3011
-polymorphic type (Ord b => [b] -> [b]) -> Swizzle and is not
+polymorphic type (Ord b => [b] -> [b]) -> Swizzle and is not
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3019
- map (T1 (\a b -> a)) [1,2,3]
+ map (T1 (\a b -> a)) [1,2,3]
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3026
-the sub-expression T1 (\a b -> a) has type Int -> T
+the sub-expression T1 (\a b -> a) has type Int -> T
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3071
- mkTs :: (forall b. b -> b -> b) -> a -> [T a]
+ mkTs :: (forall b. b -> b -> b) -> a -> [T a]
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3079
-the polymorphic type (forall b. b -> b -> b) when type
+the polymorphic type (forall b. b -> b -> b) when type
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3099
-rank2type ::= [forall tyvars .] [context =>] funty
-funty ::= ([forall tyvars .] [context =>] ty) -> funty
+rank2type ::= [forall tyvars .] [context =>] funty
+funty ::= ([forall tyvars .] [context =>] ty) -> funty
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3121
-mkTs :: (forall b. b -> b -> b) -> a -> [T a]
-mkTs = \ f x y -> [T1 f x, T1 f y]
+mkTs :: (forall b. b -> b -> b) -> a -> [T a]
+mkTs = \ f x y -> [T1 f x, T1 f y]
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3203
- data Foo = forall a. MkFoo a (a -> Bool)
+ data Foo = forall a. MkFoo a (a -> Bool)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3216
- MkFoo :: forall a. a -> (a -> Bool) -> Foo
+ MkFoo :: forall a. a -> (a -> Bool) -> Foo
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3265
- f :: Foo -> Bool
+ f :: Foo -> Bool
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3290
- MkFoo :: (exists a . (a, a -> Bool)) -> Foo
+ MkFoo :: (exists a . (a, a -> Bool)) -> Foo
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3314
-data Baz = forall a. Eq a => Baz1 a a
- | forall b. Show b => Baz2 b (b -> b)
+data Baz = forall a. Eq a => Baz1 a a
+ | forall b. Show b => Baz2 b (b -> b)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3327
-Baz1 :: forall a. Eq a => a -> a -> Baz
-Baz2 :: forall b. Show b => b -> (b -> b) -> Baz
+Baz1 :: forall a. Eq a => a -> a -> Baz
+Baz2 :: forall b. Show b => b -> (b -> b) -> Baz
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3343
- f :: Baz -> String
+ f :: Baz -> String
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3396
- f1 :: Foo -> a -- Weird!
+ f1 :: Foo -> a -- Weird!
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3405
- f1 :: forall a. Foo -> a -- Wrong!
+ f1 :: forall a. Foo -> a -- Wrong!
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3459
- newtype T = forall a. Ord a => MkT a
+ newtype T = forall a. Ord a => MkT a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3526
-assert :: Bool -> a -> a
+assert :: Bool -> a -> a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3553
-kelvinToC :: Double -> Double
+kelvinToC :: Double -> Double
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3567
-assert pred val ==> assertError "Main.hs|15" pred val
+assert pred val ==> assertError "Main.hs|15" pred val
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3682
- f :: a -> a
+ f :: a -> a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3712
- op :: [a] -> a
+ op :: [a] -> a
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3746
- f :: [a] -> [a]
+ f :: [a] -> [a]
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3799
- w :: [b] -> [b]
+ w :: [b] -> [b]
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3852
- f :: Int -> [a] -> [a]
- f n :: ([a] -> [a]) = let g (x::a, y::a) = (y,x)
- in \xs -> map g (reverse xs `zip` xs)
+ f :: Int -> [a] -> [a]
+ f n :: ([a] -> [a]) = let g (x::a, y::a) = (y,x)
+ in \xs -> map g (reverse xs `zip` xs)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3899
- (\ (x::a, y) :: a -> x)
+ (\ (x::a, y) :: a -> x)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3910
- f2 = \(x::c) -> f2 x -- not ok
+ f2 = \(x::c) -> f2 x -- not ok
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3929
- case e of { (x::a, y) :: a -> x }
+ case e of { (x::a, y) :: a -> x }
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3940
- case (True,False) of { (x::a, y) -> x }
+ case (True,False) of { (x::a, y) -> x }
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3950
- case (True,False) of { (x::Bool, y) -> x }
+ case (True,False) of { (x::Bool, y) -> x }
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 3966
- \ x :: a -> b -> x
+ \ x :: a -> b -> x
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4000
- f :: (b->b) = \(x::b) -> x
+ f :: (b->b) = \(x::b) -> x
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4016
- g :: a -> a -> Bool = \x y. x==y
+ g :: a -> a -> Bool = \x y. x==y
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4045
- f :: T -> T
+ f :: T -> T
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4101
-key_function :: Int -> String -> (Bool, Double)
+key_function :: Int -> String -> (Bool, Double)
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4175
-hammeredLookup :: Ord key => [(key, value)] -> key -> value
+hammeredLookup :: Ord key => [(key, value)] -> key -> value
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4185
-{-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-}
+{-# SPECIALIZE hammeredLookup :: [(Widget, value)] -> Widget -> value #-}
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4210
-toDouble :: Real a => a -> Double
+toDouble :: Real a => a -> Double
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4213
-{-# SPECIALIZE toDouble :: Int -> Double = i2d #-}
+{-# SPECIALIZE toDouble :: Int -> Double = i2d #-}
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4244
-instance (Eq a) => Eq (Foo a) where { ... usual stuff ... }
+instance (Eq a) => Eq (Foo a) where { ... usual stuff ... }
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4366
-"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) .
+"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) .
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4381
-"wrong1" forall e1 e2. case True of { True -> e1; False -> e2 } = e1
+"wrong1" forall e1 e2. case True of { True -> e1; False -> e2 } = e1
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4760
- {-# SPECIALIZE fromIntegral :: Int8 -> Int16 = int8ToInt16 #-}
+ {-# SPECIALIZE fromIntegral :: Int8 -> Int16 = int8ToInt16 #-}
hunk ./ghc/docs/users_guide/glasgow_exts.sgml 4821
- build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
+ build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
hunk ./ghc/docs/users_guide/libraries.sgml 1
-
-The GHC prelude and libraries
-
-
-
-This document describes GHC's prelude and libraries. The basic story is that of the Haskell 1.4 Report and Libraries document (which we do not reproduce here), but this document describes in addition:
-
-
-
-
-
-
-
-
-GHC's additional non-standard libraries and types, such as state
-transformers, packed strings, foreign objects, stable pointers, and so on.
-
-
-
-
-
-GHC's primitive types and operations. The standard Haskell functions are
-implemented on top of these, and it is sometimes useful to use them
-directly.
-
-
-
-
-
-The organisation of these libraries into directories.
-
-
-
-
-
-Short description of programmer interface to the non-standard
-libraries provided in addition to the standard prelude.
-
-
-
-
-
-
-
-A number of the libraries that provide access to GHC's language
-extensions are shared by Hugs, and are described in the GHC/Hugs Extension Libraries document.
-
-
-
-Prelude extensions
-
-
-
-GHC's prelude contains the following non-standard extensions:
-
-
-
-
-
-
-fromInt method in class Num:
-
-
-It's there. Converts from
-an Int to the type.
-
-
-
-
-toInt method in class Integral:
-
-
-Converts from Integral
-type to an Int.
-
-
-
-
-
-
-
-GHC also internally uses a number of modules that begin with the
-string PrelPrel module prefix: for this reason, we
-don't recommend that you use any module names beginning with Prel in
-your own programs. The Prel modules are always available: in fact,
-you can get access to several extensions this way (for some you might
-need to give the -fglasgow-exts option
-flag).
-
-
-
-
-
-
-GHC-only Extension Libraries
-
-
-libraries, ghc-only
-extension libraries, ghc-only
-
-
-
-If you rely on the implicit import Prelude that GHC normally does
-for you, and if you don't use any weird flags (notably
-), and if you don't import the Glasgow extensions
-interface, GlaExts, then GHC should work exactly as the
-Haskell report says (modulo a few minor issues, see ).
-
-
-
-If you turn on , a new world opens up to you and the compiler
-will recognise and parse unboxed values properly, and provide access to the
-various interfaces libraries described here (and piles of other goodies.)
-
-
-
-
-
-The module PrelGHC: really primitive stuff
-
-
-
-PrelGHC module
-
-
-
-This module defines all the types which are primitive in Glasgow
-Haskell, and the operations provided for them.
-
-
-
-A primitive type is one which cannot be defined in Haskell, and which
-is therefore built into the language and compiler. Primitive types
-are always unlifted; that is, a value of primitive type cannot be
-bottom. We use the convention that primitive types, values, and
-operations have a # suffix.
-
-
-
-Primitive values are often represented by a simple bit-pattern, such
-as Int#, Float#, Double#. But this is not necessarily the case:
-a primitive value might be represented by a pointer to a
-heap-allocated object. Examples include Array#, the type of
-primitive arrays. A primitive array is heap-allocated because it is
-too big a value to fit in a register, and would be too expensive to
-copy around; in a sense, it is accidental that it is represented by a
-pointer. If a pointer represents a primitive value, then it really
-does point to that value: no unevaluated thunks, no
-indirections…nothing can be at the other end of the pointer than the
-primitive value.
-
-
-
-Unboxed Tuples
-
-
-
-Unboxed tuples aren't really exported by PrelGHC, they're available
-by default with . An unboxed tuple looks like this:
-
-
-
-
-
-(# e_1, ..., e_n #)
-
-
-
-
-
-where e_1..e_n are expressions of any type (primitive or
-non-primitive). The type of an unboxed tuple looks the same.
-
-
-
-Unboxed tuples are used for functions that need to return multiple
-values, but they avoid the heap allocation normally associated with
-using fully-fledged tuples. When an unboxed tuple is returned, the
-components are put directly into registers or on the stack; the
-unboxed tuple itself does not have a composite representation. Many
-of the primitive operations listed in this section return unboxed
-tuples.
-
-
-
-There are some pretty stringent restrictions on the use of unboxed tuples:
-
-
-
-
-
-
-
-
- Unboxed tuple types are subject to the same restrictions as
-other unboxed types; i.e. they may not be stored in polymorphic data
-structures or passed to polymorphic functions.
-
-
-
-
-
-
- Unboxed tuples may only be constructed as the direct result of
-a function, and may only be deconstructed with a case expression.
-eg. the following are valid:
-
-
-
-f x y = (# x+1, y-1 #)
-g x = case f x x of { (# a, b #) -> a + b }
-
-
-
-but the following are invalid:
-
-
-
-f x y = g (# x, y #)
-g (# x, y #) = x + y
-
-
-
-
-
-
-
-
- No variable can have an unboxed tuple type. This is illegal:
-
-
-
-f :: (# Int, Int #) -> (# Int, Int #)
-f x = x
-
-
-
-because x has an unboxed tuple type.
-
-
-
-
-
-
-
-
-
-Note: we may relax some of these restrictions in the future.
-
-
-
-The IO and ST monads use unboxed tuples to avoid unnecessary
-allocation during sequences of operations.
-
-
-
-
-
-Character and numeric types
-
-
-character types, primitive
-numeric types, primitive
-integer types, primitive
-floating point types, primitive
-There are the following obvious primitive types:
-
-
-
-
-
-type Char#
-type Int# -- see also Word# and Addr#, later
-type Float#
-type Double#
-
-
-Char#
-Int#
-Float#
-Double#
-
-
-
-If you really want to know their exact equivalents in C, see
-ghc/includes/StgTypes.h in the GHC source tree.
-
-
-
-Literals for these types may be written as follows:
-
-
-
-
-
-1# an Int#
-1.2# a Float#
-1.34## a Double#
-'a'# a Char#; for weird characters, use '\o<octal>'#
-"a"# an Addr# (a `char *')
-
-
-literals, primitive
-constants, primitive
-numbers, primitive
-
-
-
-
-
-Comparison operations
-
-
-comparisons, primitive
-operators, comparison
-
-
-
-
-
-{>,>=,==,/=,<,<=}# :: Int# -> Int# -> Bool
-
-{gt,ge,eq,ne,lt,le}Char# :: Char# -> Char# -> Bool
- -- ditto for Word# and Addr#
-
-
->#
->=#
-==#
-/=#
-<#
-<=#
-gt{Char,Word,Addr}#
-ge{Char,Word,Addr}#
-eq{Char,Word,Addr}#
-ne{Char,Word,Addr}#
-lt{Char,Word,Addr}#
-le{Char,Word,Addr}#
-
-
-
-
-
-Primitive-character operations
-
-
-characters, primitive operations
-operators, primitive character
-
-
-
-
-
-ord# :: Char# -> Int#
-chr# :: Int# -> Char#
-
-
-ord#
-chr#
-
-
-
-
-
-Primitive-Int operations
-
-
-integers, primitive operations
-operators, primitive integer
-
-
-
-
-
-{+,-,*,quotInt,remInt}# :: Int# -> Int# -> Int#
-negateInt# :: Int# -> Int#
-
-iShiftL#, iShiftRA#, iShiftRL# :: Int# -> Int# -> Int#
- -- shift left, right arithmetic, right logical
-
-
-+#
--#
-*#
-quotInt#
-remInt#
-iShiftL#
-iShiftRA#
-iShiftRL#
-shift operations, integer
-
-
-
-Note: No error/overflow checking!
-
-
-
-
-
-Primitive-Double and Float operations
-
-
-floating point numbers, primitive
-operators, primitive floating point
-
-
-
-
-
-{+,-,*,/}## :: Double# -> Double# -> Double#
-{<,<=,==,/=,>=,>}## :: Double# -> Double# -> Bool
-negateDouble# :: Double# -> Double#
-double2Int# :: Double# -> Int#
-int2Double# :: Int# -> Double#
-
-{plus,minux,times,divide}Float# :: Float# -> Float# -> Float#
-{gt,ge,eq,ne,lt,le}Float# :: Float# -> Float# -> Bool
-negateFloat# :: Float# -> Float#
-float2Int# :: Float# -> Int#
-int2Float# :: Int# -> Float#
-
-
-
-
-
-+##
--##
-*##
-/##
-<##
-<=##
-==##
-=/##
->=##
->##
-negateDouble#
-double2Int#
-int2Double#
-
-
-
-plusFloat#
-minusFloat#
-timesFloat#
-divideFloat#
-gtFloat#
-geFloat#
-eqFloat#
-neFloat#
-ltFloat#
-leFloat#
-negateFloat#
-float2Int#
-int2Float#
-
-
-
-And a full complement of trigonometric functions:
-
-
-
-
-
- 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#
-powerDouble# :: Double# -> Double# -> Double#
-
-
-trigonometric functions, primitive
-
-
-
-similarly for Float#.
-
-
-
-There are two coercion functions for Float#/Double#:
-
-
-
-
-
-float2Double# :: Float# -> Double#
-double2Float# :: Double# -> Float#
-
-
-float2Double#
-double2Float#
-
-
-
-The primitive versions of encodeDouble/decodeDouble:
-
-
-
-
-
-encodeDouble# :: Int# -> Int# -> ByteArray# -- Integer mantissa
- -> Int# -- Int exponent
- -> Double#
-
-decodeDouble# :: Double# -> PrelNum.ReturnIntAndGMP
-
-
-encodeDouble#
-decodeDouble#
-
-
-
-(And the same for Float#s.)
-
-
-
-
-
-Operations on/for Integers (interface to GMP)
-
-
-
-arbitrary precision integers
-Integer, operations on
-
-
-
-We implement Integers (arbitrary-precision integers) using the GNU
-multiple-precision (GMP) package (version 2.0.2).
-
-
-
-The data type for Integer is either a small integer,
-represented by an Int, or a large integer represented
-using the pieces required by GMP's MP_INT in gmp.h
-(see gmp.info in ghc/includes/runtime/gmp). It comes out as:
-
-
-
-
-
-data Integer = S# Int# -- small integers
- | J# Int# ByteArray# -- large integers
-
-
-Integer type
-The primitive ops to support large Integers use the “pieces” of the
-representation, and are as follows:
-
-
-
-
-
-negateInteger# :: Int# -> ByteArray# -> Integer
-
-{plus,minus,times}Integer# :: Int# -> ByteArray#
- -> Int# -> ByteArray#
- -> Integer
-
-cmpInteger# :: Int# -> ByteArray#
- -> Int# -> ByteArray#
- -> Int# -- -1 for <; 0 for ==; +1 for >
-
-divModInteger#, quotRemInteger#
- :: Int# -> ByteArray#
- -> Int# -> ByteArray#
- -> PrelNum.Return2GMPs
-
-integer2Int# :: Int# -> ByteArray# -> Int#
-
-int2Integer# :: Int# -> Integer -- NB: no error-checking on these two!
-word2Integer# :: Word# -> Integer
-
-addr2Integer# :: Addr# -> Integer
- -- the Addr# is taken to be a `char *' string
- -- to be converted into an Integer.
-
-
-negateInteger#
-plusInteger#
-minusInteger#
-timesInteger#
-cmpInteger#
-divModInteger#
-quotRemInteger#
-integer2Int#
-int2Integer#
-word2Integer#
-addr2Integer#
-
-
-
-
-
-Words and addresses
-
-
-word, primitive type
-address, primitive type
-unsigned integer, primitive type
-pointer, primitive type
-
-
-
-A Word# is used for bit-twiddling operations. It is the same size as
-an Int#, but has no sign nor any arithmetic operations.
-
-
-type Word# -- Same size/etc as Int# but *unsigned*
-type Addr# -- A pointer from outside the "Haskell world" (from C, probably);
- -- described under "arrays"
-
-
-Word#
-Addr#
-
-
-
-Word#s and Addr#s have the usual comparison operations.
-Other unboxed-Word ops (bit-twiddling and coercions):
-
-
-
-
-
-and#, or#, xor# :: Word# -> Word# -> Word#
- -- standard bit ops.
-
-quotWord#, remWord# :: Word# -> Word# -> Word#
- -- word (i.e. unsigned) versions are different from int
- -- versions, so we have to provide these explicitly.
-
-not# :: Word# -> Word#
-
-shiftL#, shiftRA#, shiftRL# :: Word# -> Int# -> Word#
- -- shift left, right arithmetic, right logical
-
-int2Word# :: Int# -> Word# -- just a cast, really
-word2Int# :: Word# -> Int#
-
-
-bit operations, Word and Addr
-and#
-or#
-xor#
-not#
-quotWord#
-remWord#
-shiftL#
-shiftRA#
-shiftRL#
-int2Word#
-word2Int#
-
-
-
-Unboxed-Addr ops (C casts, really):
-
-
-int2Addr# :: Int# -> Addr#
-addr2Int# :: Addr# -> Int#
-
-
-int2Addr#
-addr2Int#
-
-
-
-The casts between Int#, Word# and Addr# correspond to null
-operations at the machine level, but are required to keep the Haskell
-type checker happy.
-
-
-
-Operations for indexing off of C pointers (Addr#s) to snatch values
-are listed under “arrays”.
-
-
-
-
-
-Arrays
-
-
-arrays, primitive
-
-
-
-The type Array# elt is the type of primitive, unpointed arrays of
-values of type elt.
-
-
-
-
-
-type Array# elt
-
-
-Array#
-
-
-
-Array# is more primitive than a Haskell array—indeed, the
-Haskell Array interface is implemented using Array#—in that an
-Array# is indexed only by Int#s, starting at zero. It is also
-more primitive by virtue of being unboxed. That doesn't mean that it
-isn't a heap-allocated object—of course, it is. Rather, being
-unboxed means that it is represented by a pointer to the array itself,
-and not to a thunk which will evaluate to the array (or to bottom).
-The components of an Array# are themselves boxed.
-
-
-
-The type ByteArray# is similar to Array#, except that it contains
-just a string of (non-pointer) bytes.
-
-
-
-
-
-type ByteArray#
-
-
-ByteArray#
-
-
-
-Arrays of these types are useful when a Haskell program wishes to
-construct a value to pass to a C procedure. It is also possible to
-use them to build (say) arrays of unboxed characters for internal use
-in a Haskell program. Given these uses, ByteArray# is deliberately
-a bit vague about the type of its components. Operations are provided
-to extract values of type Char#, Int#, Float#, Double#, and
-Addr# from arbitrary offsets within a ByteArray#. (For type
-Foo#, the $i$th offset gets you the $i$th Foo#, not the Foo# at
-byte-position $i$. Mumble.) (If you want a Word#, grab an Int#,
-then coerce it.)
-
-
-
-Lastly, we have static byte-arrays, of type Addr# [mentioned
-previously]. (Remember the duality between arrays and pointers in C.)
-Arrays of this types are represented by a pointer to an array in the
-world outside Haskell, so this pointer is not followed by the garbage
-collector. In other respects they are just like ByteArray#. They
-are only needed in order to pass values from C to Haskell.
-
-
-
-
-
-Reading and writing
-
-
-Primitive arrays are linear, and indexed starting at zero.
-
-
-
-The size and indices of a ByteArray#, Addr#, and
-MutableByteArray# are all in bytes. It's up to the program to
-calculate the correct byte offset from the start of the array. This
-allows a ByteArray# to contain a mixture of values of different
-type, which is often needed when preparing data for and unpicking
-results from C. (Umm…not true of indices…WDP 95/09)
-
-
-
-Should we provide some sizeOfDouble# constants?
-
-
-
-Out-of-range errors on indexing should be caught by the code which
-uses the primitive operation; the primitive operations themselves do
-not check for out-of-range indexes. The intention is that the
-primitive ops compile to one machine instruction or thereabouts.
-
-
-
-We use the terms “reading” and “writing” to refer to accessing
-mutable arrays (see ), and
-“indexing” to refer to reading a value from an immutable
-array.
-
-
-
-Immutable byte arrays are straightforward to index (all indices in bytes):
-
-
-indexCharArray# :: ByteArray# -> Int# -> Char#
-indexIntArray# :: ByteArray# -> Int# -> Int#
-indexAddrArray# :: ByteArray# -> Int# -> Addr#
-indexFloatArray# :: ByteArray# -> Int# -> Float#
-indexDoubleArray# :: ByteArray# -> Int# -> Double#
-
-indexCharOffAddr# :: Addr# -> Int# -> Char#
-indexIntOffAddr# :: Addr# -> Int# -> Int#
-indexFloatOffAddr# :: Addr# -> Int# -> Float#
-indexDoubleOffAddr# :: Addr# -> Int# -> Double#
-indexAddrOffAddr# :: Addr# -> Int# -> Addr#
- -- Get an Addr# from an Addr# offset
-
-
-indexCharArray#
-indexIntArray#
-indexAddrArray#
-indexFloatArray#
-indexDoubleArray#
-indexCharOffAddr#
-indexIntOffAddr#
-indexFloatOffAddr#
-indexDoubleOffAddr#
-indexAddrOffAddr#
-
-
-
-The last of these, indexAddrOffAddr#, extracts an Addr# using an offset
-from another Addr#, thereby providing the ability to follow a chain of
-C pointers.
-
-
-
-Something a bit more interesting goes on when indexing arrays of boxed
-objects, because the result is simply the boxed object. So presumably
-it should be entered—we never usually return an unevaluated
-object! This is a pain: primitive ops aren't supposed to do
-complicated things like enter objects. The current solution is to
-return a single element unboxed tuple (see ).
-
-
-
-
-
-indexArray# :: Array# elt -> Int# -> (# elt #)
-
-
-indexArray#
-
-
-
-
-
-The state type
-
-
-state, primitive type
-State#
-
-
-
-The primitive type State# represents the state of a state
-transformer. It is parameterised on the desired type of state, which
-serves to keep states from distinct threads distinct from one another.
-But the only effect of this parameterisation is in the type
-system: all values of type State# are represented in the same way.
-Indeed, they are all represented by nothing at all! The code
-generator “knows” to generate no code, and allocate no registers
-etc, for primitive states.
-
-
-
-
-
-type State# s
-
-
-
-
-
-The type GHC.RealWorld is truly opaque: there are no values defined
-of this type, and no operations over it. It is “primitive” in that
-sense - but it is not unlifted! Its only role in life is to be
-the type which distinguishes the IO state transformer.
-
-
-
-
-
-data RealWorld
-
-
-
-
-
-
-
-State of the world
-
-
-A single, primitive, value of type State# RealWorld is provided.
-
-
-
-
-
-realWorld# :: State# RealWorld
-
-
-realWorld# state object
-
-
-
-(Note: in the compiler, not a PrimOp; just a mucho magic
-Id. Exported from GHC, though).
-
-
-
-
-
-Mutable arrays
-
-
-mutable arrays
-arrays, mutable
-Corresponding to Array# and ByteArray#, we have the types of
-mutable versions of each. In each case, the representation is a
-pointer to a suitable block of (mutable) heap-allocated storage.
-
-
-
-
-
-type MutableArray# s elt
-type MutableByteArray# s
-
-
-MutableArray#
-MutableByteArray#
-
-
-
-Allocation
-
-
-mutable arrays, allocation
-arrays, allocation
-allocation, of mutable arrays
-
-
-
-Mutable arrays can be allocated. Only pointer-arrays are initialised;
-arrays of non-pointers are filled in by “user code” rather than by
-the array-allocation primitive. Reason: only the pointer case has to
-worry about GC striking with a partly-initialised array.
-
-
-
-
-
-newArray# :: Int# -> elt -> State# s -> (# State# s, MutableArray# s elt #)
-
-newCharArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
-newIntArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
-newAddrArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
-newFloatArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
-newDoubleArray# :: Int# -> State# s -> (# State# s, MutableByteArray# s elt #)
-
-
-newArray#
-newCharArray#
-newIntArray#
-newAddrArray#
-newFloatArray#
-newDoubleArray#
-
-
-
-The size of a ByteArray# is given in bytes.
-
-
-
-
-
-Reading and writing
-
-
-arrays, reading and writing
-
-
-
-
-
-readArray# :: MutableArray# s elt -> Int# -> State# s -> (# State# s, elt #)
-readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
-readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
-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# #)
-
-writeArray# :: MutableArray# s elt -> Int# -> elt -> State# s -> State# s
-writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
-writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> 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
-
-
-readArray#
-readCharArray#
-readIntArray#
-readAddrArray#
-readFloatArray#
-readDoubleArray#
-writeArray#
-writeCharArray#
-writeIntArray#
-writeAddrArray#
-writeFloatArray#
-writeDoubleArray#
-
-
-
-
-
-Equality
-
-
-arrays, testing for equality
-
-
-
-One can take “equality” of mutable arrays. What is compared is the
-name or reference to the mutable array, not its contents.
-
-
-
-
-
-sameMutableArray# :: MutableArray# s elt -> MutableArray# s elt -> Bool
-sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Bool
-
-
-sameMutableArray#
-sameMutableByteArray#
-
-
-
-
-
-Freezing mutable arrays
-
-
-arrays, freezing mutable
-freezing mutable arrays
-mutable arrays, freezing
-
-
-
-Only unsafe-freeze has a primitive. (Safe freeze is done directly in Haskell
-by copying the array and then using unsafeFreeze.)
-
-
-
-
-
-unsafeFreezeArray# :: MutableArray# s elt -> State# s -> (# State# s, Array# s elt #)
-unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
-
-
-unsafeFreezeArray#
-unsafeFreezeByteArray#
-
-
-
-
-
-
-
-Synchronizing variables (M-vars)
-
-
-synchronising variables (M-vars)
-M-Vars
-
-
-
-Synchronising variables are the primitive type used to implement
-Concurrent Haskell's MVars (see the Concurrent Haskell paper for
-the operational behaviour of these operations).
-
-
-
-
-
-type MVar# s elt -- primitive
-
-newMVar# :: State# s -> (# State# s, MVar# s elt #)
-takeMVar# :: SynchVar# s elt -> State# s -> (# State# s, elt #)
-putMVar# :: SynchVar# s elt -> State# s -> State# s
-
-
-SynchVar#
-newSynchVar#
-takeMVar
-putMVar
-
-
-
-
-
-
-
rmfile ./ghc/docs/users_guide/libraries.sgml
hunk ./ghc/docs/users_guide/profiling.sgml 843
-using the -F2s RTS option runtime option when the
-program has been compiled for generational garbage collection (the
-default).
+using the -G RTS
+option runtime option when the program has been
+compiled for generational garbage collection (the default).
hunk ./ghc/docs/users_guide/users_guide.sgml 16
-
hunk ./ghc/docs/users_guide/users_guide.sgml 37
-&libraries
hunk ./ghc/docs/users_guide/using.sgml 838
-POSIX library), just use a option (for example). The
-right interface files should then be available. lists the
-libraries available by this mechanism.
+POSIX library), just use a option (for
+example). The right interface files should then be available. The
+accompanying HsLibs document lists the libraries available by this
+mechanism.
}