if   pk == DoubleRep || pk == FloatRep
                      then GLD size src dst
                      else case size of
-                             L -> MOV L    (OpAddr src) (OpReg dst)
-                             B -> MOVZxL B (OpAddr src) (OpReg dst)
+                             L  -> MOV L     (OpAddr src) (OpReg dst)
+                             BU -> MOVZxL BU (OpAddr src) (OpReg dst)
     in
        returnNat (Any pk code__2)
 
        c_dst = registerCode reg_dst tmp  -- should be empty
        r_dst = registerName reg_dst tmp
        szs   = primRepToSize pks
-        opc   = case szs of L -> MOV L ; B -> MOVZxL B
+        opc   = case szs of L -> MOV L ; BU -> MOVZxL BU
 
        code  | isNilOL c_dst
               = c_addr `snocOL`
 
 
 sizeOf pr = case (primRepToSize pr) of
   IF_ARCH_alpha({B -> 1; BU -> 1; {-W -> 2; WU -> 2;-} L -> 4; {-SF -> 4;-} _ -> 8},)
-  IF_ARCH_sparc({B -> 1; BU -> 1; {-HW -> 2; HWU -> 2;-} W -> 4; {-D -> 8;-} F -> 4; DF -> 8},)
-  IF_ARCH_i386( {B -> 1; {-S -> 2;-} L -> 4; F -> 4; DF -> 8 },)
+  IF_ARCH_sparc({B -> 1; BU -> 1; W -> 4; F -> 4; DF -> 8},)
+  IF_ARCH_i386( {B -> 1; BU -> 1; L -> 4; F -> 4; DF -> 8 },)
 \end{code}
 
 % - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     | TF    -- IEEE double-precision floating pt
 #endif
 #if i386_TARGET_ARCH
-    = B            -- byte (lower)
---  | HB    -- higher byte **UNUSED**
---  | S            -- : UNUSED
-    | L
+    = B            -- byte (signed, JRS:??lower??)
+    | BU    -- byte, unsigned
+    | L     -- word32
     | F            -- IEEE single-precision floating pt
     | DF    -- IEEE single-precision floating pt
     | F80   -- Intel 80-bit internal FP format; only used for spilling
 #if sparc_TARGET_ARCH
     = B     -- byte (signed)
     | BU    -- byte (unsigned)
---  | HW    -- halfword, 2 bytes (signed): UNUSED
---  | HWU   -- halfword, 2 bytes (unsigned): UNUSED
     | W            -- word, 4 bytes
---  | D            -- doubleword, 8 bytes: UNUSED
     | F            -- IEEE single-precision floating pt
     | DF    -- IEEE single-precision floating pt
 #endif
 primRepToSize RetRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
 primRepToSize CostCentreRep = IF_ARCH_alpha( Q,         IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
 primRepToSize CharRep      = IF_ARCH_alpha( L,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
+
 primRepToSize Int8Rep      = IF_ARCH_alpha( B,  IF_ARCH_i386( B, IF_ARCH_sparc( B ,)))
+primRepToSize Word8Rep     = IF_ARCH_alpha( B,  IF_ARCH_i386( B, IF_ARCH_sparc( BU,)))
+
 primRepToSize IntRep       = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
 primRepToSize WordRep      = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
 primRepToSize AddrRep      = IF_ARCH_alpha( Q,  IF_ARCH_i386( L, IF_ARCH_sparc( W ,)))
 
         TF -> SLIT("t")
 #endif
 #if i386_TARGET_ARCH
-       B   -> SLIT("b")
---     HB  -> SLIT("b") UNUSED
---     S   -> SLIT("w") UNUSED
+       BU  -> SLIT("b")
        L   -> SLIT("l")
        F   -> SLIT("s")
        DF  -> SLIT("l")
 #if sparc_TARGET_ARCH
        B   -> SLIT("sb")
        BU  -> SLIT("ub")
---     HW  -> SLIT("hw") UNUSED
---     HWU -> SLIT("uhw") UNUSED
        W   -> SLIT("")
        F   -> SLIT("")
---     D   -> SLIT("d") UNUSED
        DF  -> SLIT("d")
     )
 pprStSize :: Size -> SDoc
 pprStSize x = ptext (case x of
        B   -> SLIT("b")
        BU  -> SLIT("b")
---     HW  -> SLIT("hw") UNUSED
---     HWU -> SLIT("uhw") UNUSED
        W   -> SLIT("")
        F   -> SLIT("")
---     D   -> SLIT("d") UNUSED
        DF  -> SLIT("d")
 #endif
     )
 
     returnUs (\xs -> assign : xs)
 
 -- NB: indexing in "pk" units, *not* in bytes (WDP 95/09)
-primCode ls IndexByteArrayOp_Char      rs = primCode_ReadByteArrayOp Int8Rep      ls rs
+primCode ls IndexByteArrayOp_Char      rs = primCode_ReadByteArrayOp Word8Rep     ls rs
 primCode ls IndexByteArrayOp_Int       rs = primCode_ReadByteArrayOp IntRep       ls rs
 primCode ls IndexByteArrayOp_Word      rs = primCode_ReadByteArrayOp WordRep      ls rs
 primCode ls IndexByteArrayOp_Addr      rs = primCode_ReadByteArrayOp AddrRep      ls rs
 primCode ls IndexByteArrayOp_Int64     rs = primCode_ReadByteArrayOp Int64Rep     ls rs
 primCode ls IndexByteArrayOp_Word64    rs = primCode_ReadByteArrayOp Word64Rep    ls rs
 
-primCode ls ReadByteArrayOp_Char      rs = primCode_ReadByteArrayOp Int8Rep      ls rs
+primCode ls ReadByteArrayOp_Char      rs = primCode_ReadByteArrayOp Word8Rep     ls rs
 primCode ls ReadByteArrayOp_Int       rs = primCode_ReadByteArrayOp IntRep       ls rs
 primCode ls ReadByteArrayOp_Word      rs = primCode_ReadByteArrayOp WordRep      ls rs
 primCode ls ReadByteArrayOp_Addr      rs = primCode_ReadByteArrayOp AddrRep      ls rs
 primCode ls ReadByteArrayOp_Int64     rs = primCode_ReadByteArrayOp Int64Rep     ls rs
 primCode ls ReadByteArrayOp_Word64    rs = primCode_ReadByteArrayOp Word64Rep    ls rs
 
-primCode ls ReadOffAddrOp_Char      rs = primCode_IndexOffAddrOp Int8Rep      ls rs
+primCode ls ReadOffAddrOp_Char      rs = primCode_IndexOffAddrOp Word8Rep     ls rs
 primCode ls ReadOffAddrOp_Int       rs = primCode_IndexOffAddrOp IntRep       ls rs
 primCode ls ReadOffAddrOp_Word      rs = primCode_IndexOffAddrOp WordRep      ls rs
 primCode ls ReadOffAddrOp_Addr      rs = primCode_IndexOffAddrOp AddrRep      ls rs
 primCode ls ReadOffAddrOp_Int64     rs = primCode_IndexOffAddrOp Int64Rep     ls rs
 primCode ls ReadOffAddrOp_Word64    rs = primCode_IndexOffAddrOp Word64Rep    ls rs
 
-primCode ls IndexOffAddrOp_Char      rs = primCode_IndexOffAddrOp Int8Rep      ls rs
+primCode ls IndexOffAddrOp_Char      rs = primCode_IndexOffAddrOp Word8Rep     ls rs
 primCode ls IndexOffAddrOp_Int       rs = primCode_IndexOffAddrOp IntRep       ls rs
 primCode ls IndexOffAddrOp_Word      rs = primCode_IndexOffAddrOp WordRep      ls rs
 primCode ls IndexOffAddrOp_Addr      rs = primCode_IndexOffAddrOp AddrRep      ls rs
 primCode ls IndexOffAddrOp_Int64     rs = primCode_IndexOffAddrOp Int64Rep     ls rs
 primCode ls IndexOffAddrOp_Word64    rs = primCode_IndexOffAddrOp Word64Rep    ls rs
 
-primCode ls IndexOffForeignObjOp_Char      rs = primCode_IndexOffForeignObjOp Int8Rep      ls rs
+primCode ls IndexOffForeignObjOp_Char      rs = primCode_IndexOffForeignObjOp Word8Rep     ls rs
 primCode ls IndexOffForeignObjOp_Int       rs = primCode_IndexOffForeignObjOp IntRep       ls rs
 primCode ls IndexOffForeignObjOp_Word      rs = primCode_IndexOffForeignObjOp WordRep      ls rs
 primCode ls IndexOffForeignObjOp_Addr      rs = primCode_IndexOffForeignObjOp AddrRep      ls rs
 primCode ls IndexOffForeignObjOp_Int64     rs = primCode_IndexOffForeignObjOp Int64Rep     ls rs
 primCode ls IndexOffForeignObjOp_Word64    rs = primCode_IndexOffForeignObjOp Word64Rep    ls rs
 
-primCode ls WriteOffAddrOp_Char      rs = primCode_WriteOffAddrOp Int8Rep      ls rs
+primCode ls WriteOffAddrOp_Char      rs = primCode_WriteOffAddrOp Word8Rep     ls rs
 primCode ls WriteOffAddrOp_Int       rs = primCode_WriteOffAddrOp IntRep       ls rs
 primCode ls WriteOffAddrOp_Word      rs = primCode_WriteOffAddrOp WordRep      ls rs
 primCode ls WriteOffAddrOp_Addr      rs = primCode_WriteOffAddrOp AddrRep      ls rs
 primCode ls WriteOffAddrOp_Int64     rs = primCode_WriteOffAddrOp Int64Rep     ls rs
 primCode ls WriteOffAddrOp_Word64    rs = primCode_WriteOffAddrOp Word64Rep    ls rs
 
-primCode ls WriteByteArrayOp_Char      rs = primCode_WriteByteArrayOp Int8Rep      ls rs
+primCode ls WriteByteArrayOp_Char      rs = primCode_WriteByteArrayOp Word8Rep     ls rs
 primCode ls WriteByteArrayOp_Int       rs = primCode_WriteByteArrayOp IntRep       ls rs
 primCode ls WriteByteArrayOp_Word      rs = primCode_WriteByteArrayOp WordRep      ls rs
 primCode ls WriteByteArrayOp_Addr      rs = primCode_WriteByteArrayOp AddrRep      ls rs
  -- For CharLike and IntLike, we attempt some trivial constant-folding here.
 
 amodeToStix (CCharLike (CLit (MachChar c)))
-  = StIndex Int8Rep cHARLIKE_closure (StInt (toInteger off))
+  = StIndex Word8Rep cHARLIKE_closure (StInt (toInteger off))
   where
     off = charLikeSize * (c - mIN_CHARLIKE)
 
   = panic "CCharLike"
 
 amodeToStix (CIntLike (CLit (MachInt i)))
-  = StIndex Int8Rep iNTLIKE_closure (StInt (toInteger off))
+  = StIndex Word8Rep iNTLIKE_closure (StInt (toInteger off))
   where
     off = intLikeSize * (fromInteger (i - mIN_INTLIKE))
 
 
   | CostCentreRep      -- Pointer to a cost centre
 
   | CharRep            -- Machine characters
-  | Int8Rep             --         8 bit integers
   | IntRep             --         integers (same size as ptr on this arch)
   | WordRep            --         ditto (but *unsigned*)
   | AddrRep            --         addresses ("C pointers")
   | DoubleRep          --         doubles
   | Word64Rep          --    guaranteed to be 64 bits (no more, no less.)
   | Int64Rep           --    guaranteed to be 64 bits (no more, no less.)
+
+    -- These are not expected to appear in the front end.  They are
+    -- only here to help the native code generator, and should appear
+    -- nowhere else.
+  | Int8Rep             --         8  bit signed   integers
+  | Word8Rep            --         8  bit unsigned integers
+  | Int16Rep            --         16 bit signed   integers
+  | Word16Rep           --         16 bit unsigned integers
+  | Int32Rep            --         32 bit signed   integers
+  | Word32Rep           --         32 bit unsigned integers
   
   -- Perhaps all sized integers and words should be primitive types.
   
-  -- Int8Rep is currently used to simulate some old CharRep usages
+  -- Word8Rep is currently used to simulate some old CharRep usages
   -- when Char changed size from 8 to 31 bits. It does not correspond
-  -- to a Haskell unboxed type, in particular it's not used by Int8.
+  -- to a Haskell unboxed type, in particular it's not used by Word8.
   
   | WeakPtrRep
   | ForeignObjRep      
 getPrimRepSizeInBytes :: PrimRep -> Int
 getPrimRepSizeInBytes pr =
  case pr of
-    CharRep        ->    4
     Int8Rep        ->    1
+    Word8Rep       ->    1
+    Int16Rep       ->    2
+    Word16Rep      ->    2
+    Int32Rep       ->    4
+    Word32Rep      ->    4
+
+    CharRep        ->    4
     IntRep         ->    wORD_SIZE
     AddrRep        ->    wORD_SIZE
     FloatRep       ->    wORD_SIZE
 showPrimRep CostCentreRep  = "CostCentre"
 showPrimRep CharRep       = "C_"
 showPrimRep Int8Rep       = "StgInt8"
+showPrimRep Int16Rep      = "StgInt16"
+showPrimRep Int32Rep      = "StgInt32"
+showPrimRep Word8Rep      = "StgWord8"
+showPrimRep Word16Rep     = "StgWord16"
+showPrimRep Word32Rep     = "StgWord32"
 showPrimRep IntRep        = "I_"       -- short for StgInt
 showPrimRep WordRep       = "W_"       -- short for StgWord
 showPrimRep Int64Rep       = "LI_"       -- short for StgLongInt