clarify that unsafeCoerce# :: Float# -> Int# is not safe (see #2209)
[ghc-hetmet.git] / compiler / prelude / primops.txt.pp
index f5a98c3..471cba1 100644 (file)
@@ -1,7 +1,7 @@
 -----------------------------------------------------------------------
 -- $Id: primops.txt.pp,v 1.37 2005/11/25 09:46:19 simonmar Exp $
 --
--- Primitive Operations
+-- Primitive Operations and Types
 --
 -----------------------------------------------------------------------
 
@@ -48,7 +48,7 @@
 -- text between curly brackets.  This is a kludge to enable 
 -- processors of this file to easily get hold of simple info
 -- (eg, out_of_line), whilst avoiding parsing complex expressions
--- needed for strictness and usage info.
+-- needed for strictness info.
 
 defaults
    has_side_effects = False
@@ -57,7 +57,6 @@ defaults
    needs_wrapper    = False
    can_fail         = False
    strictness       = { \ arity -> mkStrictSig (mkTopDmdType (replicate arity lazyDmd) TopRes) }
-   usage            = { nomangle other }
 
 -- Currently, documentation is produced using latex, so contents of
 -- description fields should be legal latex. Descriptions can contain
@@ -150,6 +149,7 @@ section "Char#"
        {Operations on 31-bit characters.}
 ------------------------------------------------------------------------
 
+primtype Char#
 
 primop   CharGtOp  "gtChar#"   Compare   Char# -> Char# -> Bool
 primop   CharGeOp  "geChar#"   Compare   Char# -> Char# -> Bool
@@ -172,6 +172,8 @@ section "Int#"
        {Operations on native-size integers (30+ bits).}
 ------------------------------------------------------------------------
 
+primtype Int#
+
 primop   IntAddOp    "+#"    Dyadic
    Int# -> Int# -> Int#
    with commutable = True
@@ -203,7 +205,7 @@ primop   IntMulMayOfloOp  "mulIntMayOflo#"
 
     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.
+    \texttt{(*) :: Integer -> Integer -> Integer} will be poor.
    }
    with commutable = True
 
@@ -267,6 +269,8 @@ section "Word#"
        {Operations on native-sized unsigned words (30+ bits).}
 ------------------------------------------------------------------------
 
+primtype Word#
+
 primop   WordAddOp   "plusWord#"   Dyadic   Word# -> Word# -> Word#
    with commutable = True
 
@@ -328,11 +332,13 @@ primop   Narrow32WordOp    "narrow32Word#"    Monadic   Word# -> Word#
 #if WORD_SIZE_IN_BITS < 32
 ------------------------------------------------------------------------
 section "Int32#"
-       {Operations on 32-bit integers (Int32\#).  This type is only used
-         if plain Int\# has less than 32 bits.  In any case, the operations
+       {Operations on 32-bit integers ({\tt Int32\#}).  This type is only used
+         if plain {\tt Int\#} has less than 32 bits.  In any case, the operations
         are not primops; they are implemented (if needed) as ccalls instead.}
 ------------------------------------------------------------------------
 
+primtype Int32#
+
 primop   Int32ToIntegerOp   "int32ToInteger#" GenPrimOp 
    Int32# -> (# Int#, ByteArr# #)
    with out_of_line = True
@@ -341,10 +347,12 @@ primop   Int32ToIntegerOp   "int32ToInteger#" GenPrimOp
 ------------------------------------------------------------------------
 section "Word32#"
        {Operations on 32-bit unsigned words. This type is only used 
-        if plain Word\# has less than 32 bits. In any case, the operations
+        if plain {\tt Word\#} has less than 32 bits. In any case, the operations
         are not primops; they are implemented (if needed) as ccalls instead.}
 ------------------------------------------------------------------------
 
+primtype Word32#
+
 primop   Word32ToIntegerOp   "word32ToInteger#" GenPrimOp
    Word32# -> (# Int#, ByteArr# #)
    with out_of_line = True
@@ -357,10 +365,12 @@ primop   Word32ToIntegerOp   "word32ToInteger#" GenPrimOp
 ------------------------------------------------------------------------
 section "Int64#"
        {Operations on 64-bit unsigned words. This type is only used 
-        if plain Int\# has less than 64 bits. In any case, the operations
+        if plain {\tt Int\#} has less than 64 bits. In any case, the operations
         are not primops; they are implemented (if needed) as ccalls instead.}
 ------------------------------------------------------------------------
 
+primtype Int64#
+
 primop   Int64ToIntegerOp   "int64ToInteger#" GenPrimOp 
    Int64# -> (# Int#, ByteArr# #)
    with out_of_line = True
@@ -368,10 +378,12 @@ primop   Int64ToIntegerOp   "int64ToInteger#" GenPrimOp
 ------------------------------------------------------------------------
 section "Word64#"
        {Operations on 64-bit unsigned words. This type is only used 
-        if plain Word\# has less than 64 bits. In any case, the operations
+        if plain {\tt Word\#} has less than 64 bits. In any case, the operations
         are not primops; they are implemented (if needed) as ccalls instead.}
 ------------------------------------------------------------------------
 
+primtype Word64#
+
 primop   Word64ToIntegerOp   "word64ToInteger#" GenPrimOp
    Word64# -> (# Int#, ByteArr# #)
    with out_of_line = True
@@ -382,8 +394,8 @@ primop   Word64ToIntegerOp   "word64ToInteger#" GenPrimOp
 section "Integer#"
        {Operations on arbitrary-precision integers. These operations are 
 implemented via the GMP package. An integer is represented as a pair
-consisting of an Int\# representing the number of 'limbs' in use and
-the sign, and a ByteArr\# containing the 'limbs' themselves.  Such pairs
+consisting of an {\tt Int\#} representing the number of 'limbs' in use and
+the sign, and a {\tt ByteArr\#} containing the 'limbs' themselves.  Such pairs
 are returned as unboxed pairs, but must be passed as separate
 components.
 
@@ -415,7 +427,7 @@ primop   IntegerGcdOp   "gcdInteger#" GenPrimOp
 
 primop   IntegerIntGcdOp   "gcdIntegerInt#" GenPrimOp
    Int# -> ByteArr# -> Int# -> Int#
-   {Greatest common divisor, where second argument is an ordinary Int\#.}
+   {Greatest common divisor, where second argument is an ordinary {\tt Int\#}.}
    with out_of_line = True
 
 primop   IntegerDivExactOp   "divExactInteger#" GenPrimOp
@@ -500,6 +512,8 @@ section "Double#"
        {Operations on double-precision (64 bit) floating-point numbers.}
 ------------------------------------------------------------------------
 
+primtype Double#
+
 primop   DoubleGtOp ">##"   Compare   Double# -> Double# -> Bool
 primop   DoubleGeOp ">=##"   Compare   Double# -> Double# -> Bool
 
@@ -531,6 +545,10 @@ primop   DoubleDivOp   "/##"   Dyadic
 primop   DoubleNegOp   "negateDouble#"  Monadic   Double# -> Double#
 
 primop   Double2IntOp   "double2Int#"          GenPrimOp  Double# -> Int#
+   {Truncates a {\tt Double#} value to the nearest {\tt Int#}.
+    Results are undefined if the truncation if truncation yields
+    a value outside the range of {\tt Int#}.}
+
 primop   Double2FloatOp   "double2Float#" GenPrimOp Double# -> Float#
 
 primop   DoubleExpOp   "expDouble#"      Monadic
@@ -596,8 +614,15 @@ primop   DoublePowerOp   "**##" Dyadic
 primop   DoubleDecodeOp   "decodeDouble#" GenPrimOp    
    Double# -> (# Int#, Int#, ByteArr# #)
    {Convert to arbitrary-precision integer.
-    First Int\# in result is the exponent; second Int\# and ByteArr\# represent an Integer\# 
-    holding the mantissa.}
+    First {\tt Int\#} in result is the exponent; second {\tt Int\#} and {\tt ByteArr\#}
+    represent an {\tt Integer\#} holding the mantissa.}
+   with out_of_line = True
+
+primop   DoubleDecode_2IntOp   "decodeDouble_2Int#" GenPrimOp    
+   Double# -> (# Int#, Int#, Int# #)
+   {Convert to arbitrary-precision integer.
+    First {\tt Int\#} in result is the high 32 bits of the mantissa, and the
+    second is the low 32. The third is the exponent.}
    with out_of_line = True
 
 ------------------------------------------------------------------------
@@ -605,6 +630,8 @@ section "Float#"
        {Operations on single-precision (32-bit) floating-point numbers.}
 ------------------------------------------------------------------------
 
+primtype Float#
+
 primop   FloatGtOp  "gtFloat#"   Compare   Float# -> Float# -> Bool
 primop   FloatGeOp  "geFloat#"   Compare   Float# -> Float# -> Bool
 
@@ -636,6 +663,9 @@ primop   FloatDivOp   "divideFloat#"      Dyadic
 primop   FloatNegOp   "negateFloat#"      Monadic    Float# -> Float#
 
 primop   Float2IntOp   "float2Int#"      GenPrimOp  Float# -> Int#
+   {Truncates a {\tt Float#} value to the nearest {\tt Int#}.
+    Results are undefined if the truncation if truncation yields
+    a value outside the range of {\tt Int#}.}
 
 primop   FloatExpOp   "expFloat#"      Monadic          
    Float# -> Float#
@@ -697,66 +727,66 @@ primop   Float2DoubleOp   "float2Double#" GenPrimOp  Float# -> Double#
 primop   FloatDecodeOp   "decodeFloat#" GenPrimOp
    Float# -> (# Int#, Int#, ByteArr# #)
    {Convert to arbitrary-precision integer.
-    First Int\# in result is the exponent; second Int\# and ByteArr\# represent an Integer\# 
-    holding the mantissa.}
+    First {\tt Int\#} in result is the exponent; second {\tt Int\#} and {\tt ByteArr\#}
+    represent an {\tt Integer\#} holding the mantissa.}
+   with out_of_line = True
+
+primop   FloatDecode_IntOp   "decodeFloat_Int#" GenPrimOp
+   Float# -> (# Int#, Int# #)
+   {Convert to arbitrary-precision integer.
+    First {\tt Int\#} in result is the mantissa; second is the exponent.}
    with out_of_line = True
 
 ------------------------------------------------------------------------
 section "Arrays"
-       {Operations on Array\#.}
+       {Operations on {\tt Array\#}.}
 ------------------------------------------------------------------------
 
+primtype Array# a
+
+primtype MutArr# s a
+
 primop  NewArrayOp "newArray#" GenPrimOp
    Int# -> a -> State# s -> (# State# s, MutArr# s a #)
    {Create a new mutable array of specified size (in bytes),
     in the specified state thread,
     with each element containing the specified initial value.}
    with
-   usage       = { mangle NewArrayOp [mkP, mkM, mkP] mkM }
    out_of_line = True
 
 primop  SameMutableArrayOp "sameMutableArray#" GenPrimOp
    MutArr# s a -> MutArr# s a -> Bool
-   with
-   usage = { mangle SameMutableArrayOp [mkP, mkP] mkM }
 
 primop  ReadArrayOp "readArray#" GenPrimOp
    MutArr# s a -> Int# -> State# s -> (# State# s, a #)
    {Read from specified index of mutable array. Result is not yet evaluated.}
-   with
-   usage = { mangle ReadArrayOp [mkM, mkP, mkP] mkM }
 
 primop  WriteArrayOp "writeArray#" GenPrimOp
    MutArr# s a -> Int# -> a -> State# s -> State# s
    {Write to specified index of mutable array.}
    with
-   usage            = { mangle WriteArrayOp [mkM, mkP, mkM, mkP] mkR }
    has_side_effects = True
 
 primop  IndexArrayOp "indexArray#" GenPrimOp
    Array# a -> Int# -> (# a #)
    {Read from specified index of immutable array. Result is packaged into
     an unboxed singleton; the result itself is not yet evaluated.}
-   with
-   usage = { mangle  IndexArrayOp [mkM, mkP] mkM }
 
 primop  UnsafeFreezeArrayOp "unsafeFreezeArray#" GenPrimOp
    MutArr# s a -> State# s -> (# State# s, Array# a #)
    {Make a mutable array immutable, without copying.}
    with
-   usage            = { mangle UnsafeFreezeArrayOp [mkM, mkP] mkM }
    has_side_effects = True
 
 primop  UnsafeThawArrayOp  "unsafeThawArray#" GenPrimOp
    Array# a -> State# s -> (# State# s, MutArr# s a #)
    {Make an immutable array mutable, without copying.}
    with
-   usage       = { mangle UnsafeThawArrayOp [mkM, mkP] mkM }
    out_of_line = True
 
 ------------------------------------------------------------------------
 section "Byte Arrays"
-       {Operations on ByteArray\#. A ByteArray\# is a just a region of
+       {Operations on {\tt ByteArray\#}. A {\tt 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:
@@ -768,6 +798,10 @@ section "Byte Arrays"
 
 ------------------------------------------------------------------------
 
+primtype ByteArr#
+
+primtype MutByteArr# s
+
 primop  NewByteArrayOp_Char "newByteArray#" GenPrimOp
    Int# -> State# s -> (# State# s, MutByteArr# s #)
    {Create a new mutable byte array of specified size (in bytes), in
@@ -967,20 +1001,22 @@ primop  WriteByteArrayOp_Word64 "writeWord64Array#" GenPrimOp
 
 ------------------------------------------------------------------------
 section "Addr#"
-       {Addr\# is an arbitrary machine address assumed to point outside
-        the garbage-collected heap.  
-
-        NB: {\tt nullAddr\#::Addr\#} is not a primop, but is defined in MkId.lhs.
-        It is the null address.}
 ------------------------------------------------------------------------
 
+primtype Addr#
+       { An arbitrary machine address assumed to point outside
+        the garbage-collected heap. }
+
+pseudoop "nullAddr#" Addr#
+       { The null address. }
+
 primop  AddrAddOp "plusAddr#" GenPrimOp Addr# -> Int# -> Addr#
 primop  AddrSubOp "minusAddr#" GenPrimOp Addr# -> Addr# -> Int#
-        {Result is meaningless if two Addr\#s are so far apart that their
-        difference doesn't fit in an Int\#.}
+        {Result is meaningless if two {\tt Addr\#}s are so far apart that their
+        difference doesn't fit in an {\tt Int\#}.}
 primop  AddrRemOp "remAddr#" GenPrimOp Addr# -> Int# -> Int#
-        {Return the remainder when the Addr\# arg, treated like an Int\#,
-         is divided by the Int\# arg.}
+        {Return the remainder when the {\tt Addr\#} arg, treated like an {\tt Int\#},
+         is divided by the {\tt Int\#} arg.}
 #if (WORD_SIZE_IN_BITS == 32 || WORD_SIZE_IN_BITS == 64)
 primop   Addr2IntOp  "addr2Int#"     GenPrimOp   Addr# -> Int#
        {Coerce directly from address to int. Strongly deprecated.}
@@ -1162,33 +1198,30 @@ primop  WriteOffAddrOp_Word64 "writeWord64OffAddr#" GenPrimOp
 
 ------------------------------------------------------------------------
 section "Mutable variables"
-       {Operations on MutVar\#s, which behave like single-element mutable arrays.}
+       {Operations on MutVar\#s.}
 ------------------------------------------------------------------------
 
+primtype MutVar# s a
+       {A {\tt MutVar\#} behaves like a single-element mutable array.}
+
 primop  NewMutVarOp "newMutVar#" GenPrimOp
    a -> State# s -> (# State# s, MutVar# s a #)
-   {Create MutVar\# with specified initial value in specified state thread.}
+   {Create {\tt MutVar\#} with specified initial value in specified state thread.}
    with
-   usage       = { mangle NewMutVarOp [mkM, mkP] mkM }
    out_of_line = True
 
 primop  ReadMutVarOp "readMutVar#" GenPrimOp
    MutVar# s a -> State# s -> (# State# s, a #)
-   {Read contents of MutVar\#. Result is not yet evaluated.}
-   with
-   usage = { mangle ReadMutVarOp [mkM, mkP] mkM }
+   {Read contents of {\tt MutVar\#}. Result is not yet evaluated.}
 
 primop  WriteMutVarOp "writeMutVar#"  GenPrimOp
    MutVar# s a -> a -> State# s -> State# s
-   {Write contents of MutVar\#.}
+   {Write contents of {\tt MutVar\#}.}
    with
-   usage            = { mangle WriteMutVarOp [mkM, mkM, mkP] mkR }
    has_side_effects = True
 
 primop  SameMutVarOp "sameMutVar#" GenPrimOp
    MutVar# s a -> MutVar# s a -> Bool
-   with
-   usage = { mangle SameMutVarOp [mkP, mkP] mkM }
 
 -- not really the right type, but we don't know about pairs here.  The
 -- correct type is
@@ -1198,7 +1231,6 @@ primop  SameMutVarOp "sameMutVar#" GenPrimOp
 primop  AtomicModifyMutVarOp "atomicModifyMutVar#" GenPrimOp
    MutVar# s a -> (a -> b) -> State# s -> (# State# s, c #)
    with
-   usage = { mangle AtomicModifyMutVarOp [mkP, mkM, mkP] mkM }
    has_side_effects = True
    out_of_line = True
 
@@ -1215,17 +1247,14 @@ primop  CatchOp "catch#" GenPrimOp
        -- Catch is actually strict in its first argument
        -- but we don't want to tell the strictness
        -- analyser about that!
-   usage = { mangle CatchOp [mkM, mkM . (inFun CatchOp mkM mkM), mkP] mkM }
-        --     [mkO, mkO . (inFun mkM mkO)] mkO
         -- might use caught action multiply
    out_of_line = True
 
 primop  RaiseOp "raise#" GenPrimOp
    a -> b
    with
-   strictness  = { \ arity -> mkStrictSig (mkTopDmdType [lazyDmd] BotRes) }
+   strictness  = { \ _arity -> mkStrictSig (mkTopDmdType [lazyDmd] BotRes) }
       -- NB: result is bottom
-   usage       = { mangle RaiseOp [mkM] mkM }
    out_of_line = True
 
 -- raiseIO# needs to be a primop, because exceptions in the IO monad
@@ -1253,6 +1282,8 @@ primop  UnblockAsyncExceptionsOp "unblockAsyncExceptions#" GenPrimOp
 section "STM-accessible Mutable Variables"
 ------------------------------------------------------------------------
 
+primtype TVar# s a
+
 primop AtomicallyOp "atomically#" GenPrimOp
       (State# RealWorld -> (# State# RealWorld, a #) )
    -> State# RealWorld -> (# State# RealWorld, a #)
@@ -1292,14 +1323,14 @@ primop  Check "check#" GenPrimOp
 primop NewTVarOp "newTVar#" GenPrimOp
        a
     -> State# s -> (# State# s, TVar# s a #)
-   {Create a new Tar\# holding a specified initial value.}
+   {Create a new {\tt TVar\#} holding a specified initial value.}
    with
    out_of_line  = True
 
 primop ReadTVarOp "readTVar#" GenPrimOp
        TVar# s a
     -> State# s -> (# State# s, a #)
-   {Read contents of TVar\#.  Result is not yet evaluated.}
+   {Read contents of {\tt TVar\#}.  Result is not yet evaluated.}
    with
    out_of_line = True
 
@@ -1307,7 +1338,7 @@ primop    WriteTVarOp "writeTVar#" GenPrimOp
        TVar# s a
     -> a
     -> State# s -> State# s
-   {Write contents of TVar\#.}
+   {Write contents of {\tt TVar\#}.}
    with
    out_of_line     = True
    has_side_effects = True
@@ -1318,65 +1349,59 @@ primop  SameTVarOp "sameTVar#" GenPrimOp
 
 ------------------------------------------------------------------------
 section "Synchronized Mutable Variables"
-       {Operations on MVar\#s, which are shared mutable variables
-       ({\it not} the same as MutVar\#s!). (Note: in a non-concurrent implementation,
-       (MVar\# a) can be represented by (MutVar\# (Maybe a)).)}
+       {Operations on {\tt MVar\#}s. }
 ------------------------------------------------------------------------
 
+primtype MVar# s a
+       { A shared mutable variable ({\it not} the same as a {\tt MutVar\#}!).
+       (Note: in a non-concurrent implementation, {\tt (MVar\# a)} can be
+       represented by {\tt (MutVar\# (Maybe a))}.) }
 
 primop  NewMVarOp "newMVar#"  GenPrimOp
    State# s -> (# State# s, MVar# s a #)
-   {Create new mvar; initially empty.}
+   {Create new {\tt MVar\#}; initially empty.}
    with
-   usage       = { mangle NewMVarOp [mkP] mkR }
    out_of_line = True
 
 primop  TakeMVarOp "takeMVar#" GenPrimOp
    MVar# s a -> State# s -> (# State# s, a #)
-   {If mvar is empty, block until it becomes full.
+   {If {\tt MVar\#} is empty, block until it becomes full.
    Then remove and return its contents, and set it empty.}
    with
-   usage            = { mangle TakeMVarOp [mkM, mkP] mkM }
    has_side_effects = True
    out_of_line      = True
 
 primop  TryTakeMVarOp "tryTakeMVar#" GenPrimOp
    MVar# s a -> State# s -> (# State# s, Int#, a #)
-   {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.}
+   {If {\tt MVar\#} is empty, immediately return with integer 0 and value undefined.
+   Otherwise, return with integer 1 and contents of {\tt MVar\#}, and set {\tt MVar\#} empty.}
    with
-   usage            = { mangle TryTakeMVarOp [mkM, mkP] mkM }
    has_side_effects = True
    out_of_line      = True
 
 primop  PutMVarOp "putMVar#" GenPrimOp
    MVar# s a -> a -> State# s -> State# s
-   {If mvar is full, block until it becomes empty.
+   {If {\tt MVar\#} is full, block until it becomes empty.
    Then store value arg as its new contents.}
    with
-   usage            = { mangle PutMVarOp [mkM, mkM, mkP] mkR }
    has_side_effects = True
    out_of_line      = True
 
 primop  TryPutMVarOp "tryPutMVar#" GenPrimOp
    MVar# s a -> a -> State# s -> (# State# s, Int# #)
-   {If mvar is full, immediately return with integer 0.
-    Otherwise, store value arg as mvar's new contents, and return with integer 1.}
+   {If {\tt MVar\#} is full, immediately return with integer 0.
+    Otherwise, store value arg as {\tt MVar\#}'s new contents, and return with integer 1.}
    with
-   usage            = { mangle TryPutMVarOp [mkM, mkM, mkP] mkR }
    has_side_effects = True
    out_of_line      = True
 
 primop  SameMVarOp "sameMVar#" GenPrimOp
    MVar# s a -> MVar# s a -> Bool
-   with
-   usage = { mangle SameMVarOp [mkP, mkP] mkM }
 
 primop  IsEmptyMVarOp "isEmptyMVar#" GenPrimOp
    MVar# s a -> State# s -> (# State# s, Int# #)
-   {Return 1 if mvar is empty; 0 otherwise.}
+   {Return 1 if {\tt MVar\#} is empty; 0 otherwise.}
    with
-   usage = { mangle IsEmptyMVarOp [mkP, mkP] mkM }
    out_of_line = True
 
 ------------------------------------------------------------------------
@@ -1436,29 +1461,40 @@ primop  AsyncDoProcOp "asyncDoProc#" GenPrimOp
 
 ------------------------------------------------------------------------
 section "Concurrency primitives"
-       {(In a non-concurrent implementation, ThreadId\# can be as singleton
-       type, whose (unique) value is returned by myThreadId\#.  The 
-       other operations can be omitted.)}
 ------------------------------------------------------------------------
 
+primtype State# s
+       { {\tt State\#} is the primitive, unlifted type of states.  It has
+       one type parameter, thus {\tt State\# RealWorld}, or {\tt 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. }
+
+primtype RealWorld
+       { {\tt RealWorld} is deeply magical.  It is {\it primitive}, but it is not
+       {\it unlifted} (hence {\tt ptrArg}).  We never manipulate values of type
+       {\tt RealWorld}; it's only used in the type system, to parameterise {\tt State\#}. }
+
+primtype ThreadId#
+       {(In a non-concurrent implementation, this can be a singleton
+       type, whose (unique) value is returned by {\tt myThreadId\#}.  The 
+       other operations can be omitted.)}
+
 primop  ForkOp "fork#" GenPrimOp
    a -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
    with
-   usage            = { mangle ForkOp [mkO, mkP] mkR }
    has_side_effects = True
    out_of_line      = True
 
 primop  ForkOnOp "forkOn#" GenPrimOp
    Int# -> a -> State# RealWorld -> (# State# RealWorld, ThreadId# #)
    with
-   usage            = { mangle ForkOnOp [mkO, mkP] mkR }
    has_side_effects = True
    out_of_line      = True
 
 primop  KillThreadOp "killThread#"  GenPrimOp
    ThreadId# -> a -> State# RealWorld -> State# RealWorld
    with
-   usage            = { mangle KillThreadOp [mkP, mkM, mkP] mkR }
    has_side_effects = True
    out_of_line      = True
 
@@ -1484,23 +1520,28 @@ primop  IsCurrentThreadBoundOp "isCurrentThreadBound#" GenPrimOp
    with
    out_of_line = True
 
+primop  NoDuplicateOp "noDuplicate#" GenPrimOp
+   State# RealWorld -> State# RealWorld
+   with
+   out_of_line = True
+
 ------------------------------------------------------------------------
 section "Weak pointers"
 ------------------------------------------------------------------------
 
+primtype Weak# b
+
 -- note that tyvar "o" denotes openAlphaTyVar
 
 primop  MkWeakOp "mkWeak#" GenPrimOp
    o -> b -> c -> State# RealWorld -> (# State# RealWorld, Weak# b #)
    with
-   usage            = { mangle MkWeakOp [mkZ, mkM, mkM, mkP] mkM }
    has_side_effects = True
    out_of_line      = True
 
 primop  DeRefWeakOp "deRefWeak#" GenPrimOp
    Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, a #)
    with
-   usage            = { mangle DeRefWeakOp [mkM, mkP] mkM }
    has_side_effects = True
    out_of_line      = True
 
@@ -1508,9 +1549,6 @@ primop  FinalizeWeakOp "finalizeWeak#" GenPrimOp
    Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, 
               (State# RealWorld -> (# State# RealWorld, () #)) #)
    with
-   usage            = { mangle FinalizeWeakOp [mkM, mkP] 
-                               (mkR . (inUB FinalizeWeakOp 
-                                            [id,id,inFun FinalizeWeakOp mkR mkM])) }
    has_side_effects = True
    out_of_line      = True
 
@@ -1523,17 +1561,19 @@ primop TouchOp "touch#" GenPrimOp
 section "Stable pointers and names"
 ------------------------------------------------------------------------
 
+primtype StablePtr# a
+
+primtype StableName# a
+
 primop  MakeStablePtrOp "makeStablePtr#" GenPrimOp
    a -> State# RealWorld -> (# State# RealWorld, StablePtr# a #)
    with
-   usage            = { mangle MakeStablePtrOp [mkM, mkP] mkM }
    has_side_effects = True
    out_of_line      = True
 
 primop  DeRefStablePtrOp "deRefStablePtr#" GenPrimOp
    StablePtr# a -> State# RealWorld -> (# State# RealWorld, a #)
    with
-   usage            = { mangle DeRefStablePtrOp [mkM, mkP] mkM }
    needs_wrapper    = True
    has_side_effects = True
    out_of_line      = True
@@ -1541,26 +1581,20 @@ primop  DeRefStablePtrOp "deRefStablePtr#" GenPrimOp
 primop  EqStablePtrOp "eqStablePtr#" GenPrimOp
    StablePtr# a -> StablePtr# a -> Int#
    with
-   usage            = { mangle EqStablePtrOp [mkP, mkP] mkR }
    has_side_effects = True
 
 primop  MakeStableNameOp "makeStableName#" GenPrimOp
    a -> State# RealWorld -> (# State# RealWorld, StableName# a #)
    with
-   usage            = { mangle MakeStableNameOp [mkZ, mkP] mkR }
    needs_wrapper    = True
    has_side_effects = True
    out_of_line      = True
 
 primop  EqStableNameOp "eqStableName#" GenPrimOp
    StableName# a -> StableName# a -> Int#
-   with
-   usage = { mangle EqStableNameOp [mkP, mkP] mkR }
 
 primop  StableNameToIntOp "stableNameToInt#" GenPrimOp
    StableName# a -> Int#
-   with
-   usage = { mangle StableNameToIntOp [mkP] mkR }
 
 ------------------------------------------------------------------------
 section "Unsafe pointer equality"
@@ -1569,8 +1603,6 @@ section "Unsafe pointer equality"
 
 primop  ReallyUnsafePtrEqualityOp "reallyUnsafePtrEquality#" GenPrimOp
    a -> a -> Int#
-   with
-   usage = { mangle ReallyUnsafePtrEqualityOp [mkZ, mkZ] mkR }
 
 ------------------------------------------------------------------------
 section "Parallelism"
@@ -1579,7 +1611,6 @@ section "Parallelism"
 primop  ParOp "par#" GenPrimOp
    a -> Int#
    with
-   usage            = { mangle ParOp [mkO] mkR }
       -- Note that Par is lazy to avoid that the sparked thing
       -- gets evaluted strictly, which it should *not* be
    has_side_effects = True
@@ -1593,37 +1624,31 @@ primop  ParOp "par#" GenPrimOp
 primop  ParGlobalOp  "parGlobal#"  GenPrimOp
    a -> Int# -> Int# -> Int# -> Int# -> b -> Int#
    with
-   usage            = { mangle ParGlobalOp [mkO, mkP, mkP, mkP, mkP, mkM] mkM }
    has_side_effects = True
 
 primop  ParLocalOp  "parLocal#"  GenPrimOp
    a -> Int# -> Int# -> Int# -> Int# -> b -> Int#
    with
-   usage            = { mangle ParLocalOp [mkO, mkP, mkP, mkP, mkP, mkM] mkM }
    has_side_effects = True
 
 primop  ParAtOp  "parAt#"  GenPrimOp
    b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int#
    with
-   usage            = { mangle ParAtOp [mkO, mkZ, mkP, mkP, mkP, mkP, mkM] mkM }
    has_side_effects = True
 
 primop  ParAtAbsOp  "parAtAbs#"  GenPrimOp
    a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int#
    with
-   usage            = { mangle ParAtAbsOp [mkO, mkP, mkP, mkP, mkP, mkM] mkM }
    has_side_effects = True
 
 primop  ParAtRelOp  "parAtRel#" GenPrimOp
    a -> Int# -> Int# -> Int# -> Int# -> Int# -> b -> Int#
    with
-   usage            = { mangle ParAtRelOp [mkO, mkP, mkP, mkP, mkP, mkM] mkM }
    has_side_effects = True
 
 primop  ParAtForNowOp  "parAtForNow#" GenPrimOp
    b -> a -> Int# -> Int# -> Int# -> Int# -> c -> Int#
    with
-   usage            = { mangle ParAtForNowOp [mkO, mkZ, mkP, mkP, mkP, mkP, mkM] mkM }
    has_side_effects = True
 
 -- copyable# and noFollow# are yet to be implemented (for GpH)
@@ -1631,13 +1656,11 @@ primop  ParAtForNowOp  "parAtForNow#" GenPrimOp
 --primop  CopyableOp  "copyable#" GenPrimOp
 --   a -> Int#
 --   with
---   usage            = { mangle CopyableOp [mkZ] mkR }
 --   has_side_effects = True
 --
 --primop  NoFollowOp "noFollow#" GenPrimOp
 --   a -> Int#
 --   with
---   usage            = { mangle NoFollowOp [mkZ] mkR }
 --   has_side_effects = True
 
 
@@ -1650,7 +1673,7 @@ section "Tag to enum stuff"
 primop  DataToTagOp "dataToTag#" GenPrimOp
    a -> Int#
    with
-   strictness  = { \ arity -> mkStrictSig (mkTopDmdType [seqDmd] TopRes) }
+   strictness  = { \ _arity -> mkStrictSig (mkTopDmdType [seqDmd] TopRes) }
        -- dataToTag# must have an evaluated argument
 
 primop  TagToEnumOp "tagToEnum#" GenPrimOp     
@@ -1661,10 +1684,12 @@ section "Bytecode operations"
        {Support for the bytecode interpreter and linker.}
 ------------------------------------------------------------------------
 
+primtype BCO#
+   {Primitive bytecode type.}
 
 primop   AddrToHValueOp "addrToHValue#" GenPrimOp
    Addr# -> (# a #)
-   {Convert an Addr\# to a followable type.}
+   {Convert an {\tt Addr\#} to a followable type.}
 
 primop   MkApUpd0_Op "mkApUpd0#" GenPrimOp
    BCO# -> (# a #)
@@ -1672,27 +1697,135 @@ primop   MkApUpd0_Op "mkApUpd0#" GenPrimOp
    out_of_line = True
 
 primop  NewBCOOp "newBCO#" GenPrimOp
-   ByteArr# -> ByteArr# -> Array# a -> ByteArr# -> Int# -> ByteArr# -> State# s -> (# State# s, BCO# #)
+   ByteArr# -> ByteArr# -> Array# a -> Int# -> ByteArr# -> State# s -> (# State# s, BCO# #)
    with
    has_side_effects = True
    out_of_line      = True
 
-primop  InfoPtrOp "infoPtr#" GenPrimOp
-   a -> Addr#
+primop  UnpackClosureOp "unpackClosure#" GenPrimOp
+   a -> (# Addr#, Array# b, ByteArr# #)
    with
    out_of_line = True
 
-primop  ClosurePayloadOp "closurePayload#" GenPrimOp
-   a -> (# Array# b, ByteArr# #)
+primop  GetApStackValOp "getApStackVal#" GenPrimOp
+   a -> Int# -> (# Int#, b #)
    with
    out_of_line = True
 
 ------------------------------------------------------------------------
-section "Coercion" 
-       {{\tt unsafeCoerce\# :: a -> b} is not a primop, but is defined in MkId.lhs.}
-
+section "Etc" 
+       {Miscellaneous built-ins}
 ------------------------------------------------------------------------
 
+pseudoop   "seq"
+   a -> b -> b
+   { Evaluates its first argument to head normal form, and then returns its second
+       argument as the result. }
+
+pseudoop   "inline"
+   a -> a
+   { The call {\tt (inline f)} arranges that f is inlined, regardless of its size.
+       More precisely, the call {\tt (inline f)} rewrites to the right-hand side of
+       {\tt 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.
+       {\tt 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
+       {\tt f}'s definition; it is unconditional. The main caveat is that {\tt f}'s
+       definition must be visible to the compiler. That is, {\tt f} must be
+       {\tt let}-bound in the current scope. If no inlining takes place, the
+       {\tt inline} function expands to the identity function in Phase zero; so its
+       use imposes no overhead.
+
+       If the function is defined in another module, GHC only exposes its inlining
+       in the interface file if the function is sufficiently small that it might be
+       inlined by the automatic mechanism. There is currently no way to tell GHC to
+       expose arbitrarily-large functions in the interface file. (This shortcoming
+       is something that could be fixed, with some kind of pragma.) }
+
+pseudoop   "lazy"
+   a -> a
+   { The {\tt lazy} function restrains strictness analysis a little. The call
+       {\tt (lazy e)} means the same as {\tt e}, but {\tt 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 {\tt lazy} are inlined to be the identity function.
+
+       This behaviour is occasionally useful when controlling evaluation order.
+       Notably, {\tt lazy} is used in the library definition of {\tt Control.Parallel.par}:
+
+       {\tt par :: a -> b -> b}
+
+       {\tt par x y = case (par\# x) of \_ -> lazy y}
+
+       If {\tt lazy} were not lazy, {\tt par} would look strict in {\tt y} which
+       would defeat the whole purpose of {\tt par}.
+
+       Like {\tt seq}, the argument of {\tt lazy} can have an unboxed type. }
+
+primtype Any a
+       { The type constructor {\tt 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 {\it data} type, and that's important for
+           the code generator, because the code gen may {\it 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
+
+       {\tt length Any []}
+
+       Annoyingly, we sometimes need {\tt Any}s of other kinds, such as {\tt (* -> *)} 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. }
+
+pseudoop   "unsafeCoerce#"
+   a -> b
+   { The function {\tt 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 {\tt unsafeCoerce\#} are supposed to work (i.e. not lead to
+        spurious compile-time or run-time crashes):
+
+         * Casting any lifted type to {\tt Any}
+
+         * Casting {\tt 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
+           {\tt Ptr Int} to {\tt Ptr Float}, or {\tt [Int]} to {\tt [Float]} when the list is 
+           known to be empty.  Also, a {\tt newtype} of a type {\tt T} has the same representation
+           at runtime as {\tt T}.
+
+        Other uses of {\tt unsafeCoerce\#} are undefined.  In particular, you should not use
+       {\tt unsafeCoerce\#} to cast a T to an algebraic data type D, unless T is also
+       an algebraic data type.  For example, do not cast {\tt Int->Int} to {\tt Bool}, even if
+        you later cast that {\tt Bool} back to {\tt 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 {\tt Any}, which is not an algebraic data type.
+       
+        }
+
+-- NB. It is tempting to think that casting a value to a type that it doesn't have is safe
+-- as long as you don't "do anything" with the value in its cast form, such as seq on it.  This
+-- isn't the case: the compiler can insert seqs itself, and if these happen at the wrong type,
+-- Bad Things Might Happen.  See bug #1616: in this case we cast a function of type (a,b) -> (a,b)
+-- to () -> () and back again.  The strictness analyser saw that the function was strict, but
+-- the wrapper had type () -> (), and hence the wrapper de-constructed the (), the worker re-constructed
+-- a new (), with the result that the code ended up with "case () of (a,b) -> ...".
 
 ------------------------------------------------------------------------
 ---                                                                  ---