[m-rev.] 8, 16 and 32 bit types

Julien Fischer jfischer at opturion.com
Sat Jul 15 01:15:23 AEST 2017


Hi Zoltan,

On Mon, 3 Jul 2017, Zoltan Somogyi wrote:

>
> Attached is a partial review of the change that introduces {int,uint}{8,16,32}.
> (My web based email client doesn't handle 7000 line messages well.)
>
> Before I finish the review, I think it is important we agree on
> how we should handle two issues that my partial review has found.
>
> The first is whether the cons_ids representing the new types and the
> operations on them should look like this
>
>    ;   int8_eq
>    ;   int16_eq
>    ;   ...
>
> or like this:
>
>    ;    int_eq(signedness, int_size)
>
> While we had one int type, there was no duplication, while we had two,
> having two copies of everything dealing with it was often easier than
> worrying about parameterization. But since we now have eight and will soon
> have ten, I think parameterization is preferable. True, it results in slightly larger
> representations, but I am pretty sure the effect will be unmeasurable
> on most if not all programs.
>
> The second is that I believe the values of uint{8,16,32} constants should be
> represented by a uint, not an int, due to the 32 and 64 bit equivalents of
> "an 8 bit signed int can't represent 255".
>
> Julien, can you tell us your reasons for choosing the representations
> in the diff, as opposed to the alternatives above? Maybe there is an issue
> I haven't considered.

My reponse to your partial review is below; it also covers both the
above issues.

> > This change does not introduce the two 64-bit types, 'int64' and 'uint64'.
> > Their implementation is more complicated and is best left to a separate change.
> 
> On 64 bit systems, int64/uint64 should be easy to support, but I suppose
> we will need a way to compile an eventual library/int64.m on 32 bit systems
> as well.

We'll need to handle them similarly to the way we handle floats (doubles).

...

> It would be easier to read this if the binops were grouped by operation,
> not by type (both here and later in e.g. c_util.m). However, the answer
> to my next question may make this point moot.
> 
> Have you thought about parameterizing the integer builtin ops on
> signedness and size, something like this:
> 
> :- type signedness
>     --->    signed
>     ;       unsigned.
> 
> :- type int_size
>     --->    size_8_bit
>     ;       size_16_bit
>     ;       size_32_bit
>     ;       size_word.
> 
> :- type binary_op
>     --->    ...
>
>     ;       int_eq(signedness, int_size).
>     ...
> 
> I think it should make some of the code that operates on unops/binops shorter
> and simpler. And it should make adding size_64_bit much easier.

Parameterizing them by signedness and int_size separately is not all
that useful -- I tried it, but simply adding an enumeration of all the
integer types and parameterizing the binops by that is cleaner.  (The
latter is what the attached diff does.)

> > @@ -186,6 +312,12 @@
> >      --->    leaf(T)
> >      ;       int_const(int)
> >      ;       uint_const(uint)
> > +    ;       int8_const(int)     % XXX FIXED SIZE INTS
> > +    ;       uint8_const(int)    % XXX FIXED SIZE INTS
> > +    ;       int16_const(int)    % XXX FIXED SIZE INTS
> > +    ;       uint16_const(int)   % XXX FIXED SIZE INTS
> > +    ;       int32_const(int)    % XXX FIXED SIZE INTS
> > +    ;       uint32_const(int)   % XXX FIXED SIZE INTS
> 
> As in prog_data.m, I think that the argument of the uintN_consts should
> be a uint, not an int.

The argument in all the cases corresponding to the new integer types
will eventually be the new integer type itself not, int or uint.
They're currently just set to 'int' until after this change bootstraps.
Ditto for the similar types in prog_data.m, hlds_data.m, elds.m, llds.m,
mlds.m (in fact anywhere that actually needs to deal with values of the
new types).  The reason they should be the new types themselves is that
the compiler has optimizations that may wish to manipulate the constant
values in various ways and using the actual types is less error prone
than emulating them using some other type.

...

> > diff --git a/compiler/dupproc.m b/compiler/dupproc.m
> > index 483e27a72..db059f175 100644
> > --- a/compiler/dupproc.m
> > +++ b/compiler/dupproc.m
> > @@ -439,6 +439,24 @@ standardize_rval_const(Const, StdConst, DupProcMap) :-
> >          Const = llconst_uint(_),
> >          StdConst = Const
> >      ;
> > +        Const = llconst_int8(_),
> > +        StdConst = Const
> > +    ;
> > +        Const = llconst_uint8(_),
> > +        StdConst = Const
> > +    ;
> > +        Const = llconst_int16(_),
> > +        StdConst = Const
> > +    ;
> > +        Const = llconst_uint16(_),
> > +        StdConst = Const
> > +    ;
> > +        Const = llconst_int32(_),
> > +        StdConst = Const
> > +    ;
> > +        Const = llconst_uint32(_),
> > +        StdConst = Const
> > +    ;
> >          Const = llconst_foreign(_, _),
> >          StdConst = Const
> 
> Not your fault, but this code should really use multi-arm switches
> for the cases in which the switch arm's code is just "StdConst = Const".
> This code seems to predate the implementation of multi-arm switches.

I've changes this to a multi-arm switch; and a couple of other ones
in this module as well

...

> > diff --git a/compiler/inst_check.m b/compiler/inst_check.m
> > index 5dcf448ed..e3f6b990f 100644
> > --- a/compiler/inst_check.m
> > +++ b/compiler/inst_check.m
> > @@ -258,6 +258,60 @@ check_inst_defn_has_matching_type(TypeTable, FunctorsToTypesMap, InstId,
> >                      ForTypeCtor = uint_type_ctor,
> >                      MaybeForTypeKind = yes(ftk_uint)
> >                  else if
> > +                    ( ForTypeCtorName = unqualified("int8")
> > +                    ; ForTypeCtorName = qualified(unqualified(""), "int8")
> > +                    ; ForTypeCtorName = qualified(unqualified("int8"), "int8")
> > +                    ),
> > +                    ForTypeCtorArity = 0
> > +                then
> > +                    ForTypeCtor = int8_type_ctor,
> > +                    MaybeForTypeKind = yes(ftk_int8)
> > +                else if
> > +                    ( ForTypeCtorName = unqualified("uint8")
> > +                    ; ForTypeCtorName = qualified(unqualified(""), "uint8")
> > +                    ; ForTypeCtorName = qualified(unqualified("uint8"), "uint8")
> > +                    ),
> 
> If this threefold test is repeated this many times, it deserves to be put
> in a predicate of its own, both to make the code easier to read and to make
> future maintenance easier.

Done.

...

> > diff --git a/compiler/prog_rep_tables.m b/compiler/prog_rep_tables.m
> > index 306c9daee..a15370b3f 100644
> > --- a/compiler/prog_rep_tables.m
> > +++ b/compiler/prog_rep_tables.m
> > @@ -333,19 +333,37 @@ add_type_to_table(Type, TypeCode, !StringTable, !TypeTable) :-
> >              BuiltinType = builtin_type_uint,
> >              Selector = 6
> >          ;
> > -            BuiltinType = builtin_type_float,
> > +            BuiltinType = builtin_type_int8,
> >              Selector = 7
> 
> Changing the mapping from types to their bytecodes will make a deep_profiler
> built after this change misread any Deep.procrep files created by an executable
> compiled with a compiler that doesn't have this change. This would need
> to be reflected in the deep profiler's own version of the binary compatibility
> version number, and the parser adjusted to read the new(er) version of the
> file format as well as the old (and the existing "new").
> 
> However, the simplest solution is to map all the new types to previously
> unused Selector values, with an XXX on old/new_proc_rep_id_string in
> deep_profiler/program_representation.m to ask people tidy up the Selectors
> the next time the format of the program representation file is changed
> for some unavoidable reason.

Done.

> In a similar vein, I would add the new TYPE_CTORs to the end of the encoding
> in the runtime. This should make bumping the binary compatibility number
> unnecessary right now, since it would allow an updated runtime to properly
> handle the output of an old compiler, and the only situation in which
> you could get incompatibilities would be when the new types start being used,
> which can be only after Part 2 of this change.

Done.

> > diff --git a/compiler/prog_type.m b/compiler/prog_type.m
> > index 1333510be..6d2097b27 100644
> > --- a/compiler/prog_type.m
> > +++ b/compiler/prog_type.m
> > @@ -283,6 +283,12 @@
> >  :- type type_ctor_cat_builtin
> >      --->    cat_builtin_int
> >      ;       cat_builtin_uint
> > +    ;       cat_builtin_int8
> > +    ;       cat_builtin_uint8
> > +    ;       cat_builtin_int16
> > +    ;       cat_builtin_uint16
> > +    ;       cat_builtin_int32
> > +    ;       cat_builtin_uint32
> >      ;       cat_builtin_float
> >      ;       cat_builtin_char
> 
> These could be parameterized as well. You would have to flatten them out
> when writing them out as C, since in C these have to be enum values,
> but that need not dictate their representation in Mercury.

Done.

There are an updated log message and diff attached.

Julien.
-------------- next part --------------
Add builtin  8, 16 and 32 bit integer types -- Part 1.

Add the new builtin types: int8, uint8, int16, uint16, int32 and uint32.
Support for these new types will need to be bootstrapped over several changes.
This is the first such change and does the following:

- Extends the compiler to recognise 'int8', 'uint8', 'int16', 'uint16', 'int32'
  and 'uint32' as builtin types.
- Extends the set of builtin arithmetic, bitwise and relational operators to
  cover the new types.
- Extends all of the code generators to handle new types.  There currently lots
  of limitations and placeholders marked by 'XXX FIXED SIZE INT'.  These will
  be lifted in later changes.
- Extends the runtimes to support the new types.
- Adds new modules to the standard library intended to hold the basic
  operations on the new types.  (These are currently empty and not documented.)

This change does not introduce the two 64-bit types, 'int64' and 'uint64'.
Their implementation is more complicated and is best left to a separate change.

compiler/prog_type.m:
compiler/prog_data.m:
compiler/builtin_lib_types.m:
    Recognise int8, uint8, int16, uint16, int32 and uint32 as builtin types.

    Add new type, int_type/0,that enumerates all the possible integer types.
  
    Extend the cons_id/0 type to cover the new types.
    
compiler/builtin_ops.m:
    Parameterize the integer operations in the unary_op/0 and binary_op/0
    types by the new int_type/0 type.

    Add builtin operations for all the new types.
    
compiler/hlds_data.m:
    Add new tag types for the new types.

compiler/hlds_pred.m:
    Parameterize integers in the table_trie_step/0 type.
    
compiler/ctgc.selector.m:
compiler/dead_proc_elim.m:
compiler/export.m:
compiler/foreign.m:
compiler/goal_util.m:
compiler/higher_order.m:
compiler/hlds_code_util.m:
compiler/hlds_dependency_graph.m:
compiler/hlds_out_pred.m:
compiler/hlds_out_util.m:
compiler/implementation_defined_literals.m:
compiler/inst_check.m:
compiler/mercury_to_mercury.m:
compiler/mode_util.m:
compiler/module_qual.qualify_items.m:
compiler/opt_debug.m:
compiler/opt_util.m:
compiler/parse_tree_out_info.m:
compiler/parse_tree_to_term.m:
compiler/parse_type_name.m:
compiler/polymorphism.m:
compiler/prog_out.m:
compiler/prog_rep.m:
compiler/prog_rep_tables.m:
compiler/prog_util.m:
compiler/rbmm.exection_path.m:
compiler/rtti.m:
compiler/rtti_to_mlds.m:
compiler/switch_util.m:
compiler/table_gen.m:
compiler/type_constraints.m:
compiler/type_ctor_info.m:
compiler/type_util.m:
compiler/typecheck.m:
compiler/unify_gen.m:
compiler/unify_proc.m:
compiler/unused_imports.m:
compiler/xml_documentation.m:
    Conform to the above changes to the parse tree and HLDS.

compiler/c_util.m:
    Support generating the builtin operations for the new types.

doc/reference_manual.texi:
    Add the new types to the list of reserved type names.

    Add the mapping from the new types to their target language types.
    These are commented out for now.
    
compiler/llds.m:
    Replace the lt_integer/0 and lt_unsigned functors of the llds_type/0,
    with a single lt_int/1 functor that is parameterized by the int_type/0
    type. 

    Add a representations for constants of the new types to the LLDS.
  
compiler/call_gen.m:
compiler/dupproc.m:
compiler/exprn_aux.m:
compiler/global_data.m:
compiler/jumpopt.m:
compiler/llds_out_data.m:
compiler/llds_out_global.m:
compiler/llds_out_instr.m:
compiler/lookup_switch.m:
compiler/middle_rec.m:
compiler/peephole.m:
compiler/pragma_c_gen.m:
compiler/stack_layout.m:
compiler/string_switch.m:
compiler/switch_gen.m:
compiler/tag_switch.m:
compiler/trace_gen.m:
compiler/transform_llds.m:
    Support the new types in the LLDS code generator.
    
compiler/mlds.m:
    Support constants of the new types in the MLDS.
    
compiler/ml_accurate_gc.m:
compiler/ml_call_gen.m:
compiler/ml_code_util.m:
compiler/ml_disj_gen.m:
compiler/ml_foreign_proc_gen.m:
compiler/ml_global_data.m:
compiler/ml_lookup_switch.m:
compiler/ml_simplify_switch.m:
compiler/ml_string_switch.m:
compiler/ml_switch_gen.m:
compiler/ml_tailcall.m:
compiler/ml_type_gen.m:
compiler/ml_unify_gen.m:
compiler/ml_util.m:
compiler/mlds_to_target_util.m:
    Conform to the above changes to the MLDS.
    
compiler/mlds_to_c.m:
compiler/mlds_to_cs.m:
compiler/mlds_to_java.m:
    Generate the appropriate target code for constants of the new
    types and operations involving them.
    
compiler/bytecode.m:
compiler/bytecode_gen.m:
    Handle the new types in the bytecode generator; we just abort if we
    encounter them for now.
    
compiler/elds.m:
compiler/elds_to_erlang.m:
compiler/erl_call_gen.m:
compiler/erl_code_util.m:
compiler/erl_rtti.m:
compiler/erl_unify_gen.m:
    Handle the new types in the Erlang code generator.
    
library/private_builtin.m:
    Add placeholders for the builtin unify and compare operations for
    the new types.  Since the bootstrapping compiler will not recognise
    the new types we give the polymorphic arguments.  These can be
    replaced after this change has bootstrapped.
    
    Update the Java list of TypeCtorRep constants.
    
library/int8.m:
library/int16.m:
library/int32.m:
library/uint8.m:
library/uint16.m:
library/uint32.m:
    New modules that will eventually contain builtin operations
    on the new types.
    
library/library.m:
library/MODULES_UNDOC:
    Do not include the above modules in the library documentation
    for now.
    
library/construct.m:
library/erlang_rtti_implementation.m:
library/rtti_implementation.m:
deep_profiler/program_representation_utils.m:
mdbcomp/program_representation.m:
    Handle the new types.
    
runtime/mercury_dotnet.cs.in:
java/runtime/TypeCtorRep.java:
runtime/mercury_type_info.h:
    Update the list of TypeCtorReps.
    
configure.ac:
runtime/mercury_conf.h.in:
    Check for the header stdint.h.
    
runtime/mercury_std.h:
    Include stdint.h; abort if that header is no present.
    
runtime/mercury_builtin_types.[ch]:
runtime/mercury_builtin_types_proc_layouts.h:
runtime/mercury_construct.c:
runtime/mercury_deconstruct.c:
runtime/mercury_deep_copy_body.h:
runtime/mercury_ml_expand_body.h
runtime/mercury_table_type_body.h:
runtime/mercury_tabling_macros.h:
runtime/mercury_tabling_preds.h:
runtime/mercury_term_size.c:
runtime/mercury_unify_compare_body.h:
    Add the new builtin types and handle them throughout the runtime.
-------------- next part --------------
diff --git a/compiler/builtin_lib_types.m b/compiler/builtin_lib_types.m
index 44ab70241..7f33a3b01 100644
--- a/compiler/builtin_lib_types.m
+++ b/compiler/builtin_lib_types.m
@@ -26,6 +26,12 @@
 
 :- func int_type = mer_type.
 :- func uint_type = mer_type.
+:- func int8_type = mer_type.
+:- func uint8_type = mer_type.
+:- func int16_type = mer_type.
+:- func uint16_type = mer_type.
+:- func int32_type = mer_type.
+:- func uint32_type = mer_type.
 :- func float_type = mer_type.
 :- func string_type = mer_type.
 :- func char_type = mer_type.
@@ -60,6 +66,12 @@
 
 :- func int_type_ctor = type_ctor.
 :- func uint_type_ctor = type_ctor.
+:- func int8_type_ctor = type_ctor.
+:- func uint8_type_ctor = type_ctor.
+:- func int16_type_ctor = type_ctor.
+:- func uint16_type_ctor = type_ctor.
+:- func int32_type_ctor = type_ctor.
+:- func uint32_type_ctor = type_ctor.
 :- func float_type_ctor = type_ctor.
 :- func char_type_ctor = type_ctor.
 :- func string_type_ctor = type_ctor.
@@ -112,9 +124,21 @@
 
 %-----------------------------------------------------------------------------%
 
-int_type = builtin_type(builtin_type_int).
+int_type = builtin_type(builtin_type_int(int_type_int)).
 
-uint_type = builtin_type(builtin_type_uint).
+uint_type = builtin_type(builtin_type_int(int_type_uint)).
+
+int8_type = builtin_type(builtin_type_int(int_type_int8)).
+
+uint8_type = builtin_type(builtin_type_int(int_type_uint8)).
+
+int16_type = builtin_type(builtin_type_int(int_type_int16)).
+
+uint16_type = builtin_type(builtin_type_int(int_type_uint16)).
+
+int32_type = builtin_type(builtin_type_int(int_type_int32)).
+
+uint32_type = builtin_type(builtin_type_int(int_type_uint32)).
 
 float_type = builtin_type(builtin_type_float).
 
@@ -218,6 +242,18 @@ int_type_ctor = type_ctor(Name, 0) :-
     Name = unqualified("int").
 uint_type_ctor = type_ctor(Name, 0) :-
     Name = unqualified("uint").
+int8_type_ctor = type_ctor(Name, 0) :-
+    Name = unqualified("int8").
+uint8_type_ctor = type_ctor(Name, 0) :-
+    Name = unqualified("uint8").
+int16_type_ctor = type_ctor(Name, 0) :-
+    Name = unqualified("int16").
+uint16_type_ctor = type_ctor(Name, 0) :-
+    Name = unqualified("uint16").
+int32_type_ctor = type_ctor(Name, 0) :-
+    Name = unqualified("int32").
+uint32_type_ctor = type_ctor(Name, 0) :-
+    Name = unqualified("uint32").
 float_type_ctor = type_ctor(Name, 0) :-
     Name = unqualified("float").
 char_type_ctor = type_ctor(Name, 0) :-
diff --git a/compiler/builtin_ops.m b/compiler/builtin_ops.m
index 6b1f40fcf..605f70e8c 100644
--- a/compiler/builtin_ops.m
+++ b/compiler/builtin_ops.m
@@ -23,6 +23,8 @@
 :- import_module hlds.hlds_pred.
 :- import_module mdbcomp.
 :- import_module mdbcomp.sym_name.
+:- import_module parse_tree.
+:- import_module parse_tree.prog_data.
 
 :- import_module list.
 
@@ -35,9 +37,8 @@
     ;       strip_tag
     ;       mkbody
     ;       unmkbody
-    ;       bitwise_complement
+    ;       bitwise_complement(int_type)
     ;       logical_not
-    ;       uint_bitwise_complement
     ;       hash_string
     ;       hash_string2
     ;       hash_string3
@@ -46,21 +47,25 @@
     ;       hash_string6.
 
 :- type binary_op
-    --->    int_add
-    ;       int_sub
-    ;       int_mul
-    ;       int_div % assumed to truncate toward zero
-    ;       int_mod % remainder (w.r.t. truncating integer division)
-                    % XXX `mod' should be renamed `rem'
-    ;       unchecked_left_shift
-    ;       unchecked_right_shift
-    ;       bitwise_and
-    ;       bitwise_or
-    ;       bitwise_xor
+    --->    int_add(int_type)
+    ;       int_sub(int_type)
+    ;       int_mul(int_type)
+    ;       int_div(int_type) % Assumed to truncate toward zero.
+    ;       int_mod(int_type) % Remainder (w.r.t. truncating integer division).
+                              % XXX `mod' should be renamed `rem'
+    ;       unchecked_left_shift(int_type)
+    ;       unchecked_right_shift(int_type)
+    ;       bitwise_and(int_type)
+    ;       bitwise_or(int_type)
+    ;       bitwise_xor(int_type)
     ;       logical_and
     ;       logical_or
-    ;       eq      % ==
-    ;       ne      % !=
+            % The following type are primarily used with integers, but also
+            % with characters and enumerations.
+            % XXX the latter two uses are not covered by int_type, for now we
+            % use the convention that they should use `int_type_int'.
+    ;       eq(int_type)      % ==
+    ;       ne(int_type)      % !=
     ;       body
     ;       array_index(array_elem_type)
     ;       string_unsafe_index_code_unit
@@ -82,10 +87,10 @@
             % or equivalent code on backends which support this, and code
             % equivalent to "strcmp(SA, SB) == 0" on backends which don't.
 
-    ;       int_lt  % signed integer comparisons
-    ;       int_gt
-    ;       int_le
-    ;       int_ge
+    ;       int_lt(int_type)  % signed integer comparisons
+    ;       int_gt(int_type)
+    ;       int_le(int_type)
+    ;       int_ge(int_type)
 
     ;       unsigned_le % unsigned integer comparison (for signed values)
             % Note that the arguments to `unsigned_le' are just ordinary
@@ -94,26 +99,6 @@
             % binary(unsigned_le, int_const(1), int_const(-1)) returns true,
             % since (MR_Unsigned) 1 <= (MR_Unsigned) -1.
 
-    ;       uint_eq
-    ;       uint_ne
-    ;       uint_lt
-    ;       uint_gt
-    ;       uint_le
-    ;       uint_ge
-
-    ;       uint_add
-    ;       uint_sub
-    ;       uint_mul
-    ;       uint_div
-    ;       uint_mod
-
-    ;       uint_bitwise_and
-    ;       uint_bitwise_or
-    ;       uint_bitwise_xor
-
-    ;       uint_unchecked_left_shift
-    ;       uint_unchecked_right_shift
-
     ;       float_plus      %  XXX the integer versions use different names.
     ;       float_minus     %  E.g add instead of plus etc.
     ;       float_times
@@ -186,6 +171,12 @@
     --->    leaf(T)
     ;       int_const(int)
     ;       uint_const(uint)
+    ;       int8_const(int)     % XXX FIXED SIZE INTS
+    ;       uint8_const(int)    % XXX FIXED SIZE INTS
+    ;       int16_const(int)    % XXX FIXED SIZE INTS
+    ;       uint16_const(int)   % XXX FIXED SIZE INTS
+    ;       int32_const(int)    % XXX FIXED SIZE INTS
+    ;       uint32_const(int)   % XXX FIXED SIZE INTS
     ;       float_const(float)
     ;       unary(unary_op, simple_expr(T))
     ;       binary(binary_op, simple_expr(T), simple_expr(T)).
@@ -288,8 +279,8 @@ builtin_translation(ModuleName, PredName, ProcNum, Args, Code) :-
             % builtin_translation.
             Code = assign(Y, leaf(X))
         ;
-            ( PredName = "builtin_int_gt", CompareOp = int_gt
-            ; PredName = "builtin_int_lt", CompareOp = int_lt
+            ( PredName = "builtin_int_gt", CompareOp = int_gt(int_type_int)
+            ; PredName = "builtin_int_lt", CompareOp = int_lt(int_type_int)
             ),
             ProcNum = 0, Args = [X, Y],
             Code = test(binary(CompareOp, leaf(X), leaf(Y)))
@@ -312,22 +303,30 @@ builtin_translation(ModuleName, PredName, ProcNum, Args, Code) :-
     ;
         ModuleName = "term_size_prof_builtin",
         PredName = "term_size_plus", ProcNum = 0, Args = [X, Y, Z],
-        Code = assign(Z, binary(int_add, leaf(X), leaf(Y)))
+        Code = assign(Z, binary(int_add(int_type_int), leaf(X), leaf(Y)))
     ;
-        ModuleName = "int",
+        ( ModuleName = "int", IntType = int_type_int
+        ; ModuleName = "uint", IntType = int_type_uint
+        ; ModuleName = "int8", IntType = int_type_int8
+        ; ModuleName = "uint8", IntType = int_type_uint8
+        ; ModuleName = "int16", IntType = int_type_int16
+        ; ModuleName = "uint16", IntType = int_type_uint16
+        ; ModuleName = "int32", IntType = int_type_int32
+        ; ModuleName = "uint32", IntType = int_type_uint32
+        ),
         (
             PredName = "+",
             (
                 Args = [X, Y, Z],
                 (
                     ProcNum = 0,
-                    Code = assign(Z, binary(int_add, leaf(X), leaf(Y)))
+                    Code = assign(Z, binary(int_add(IntType), leaf(X), leaf(Y)))
                 ;
                     ProcNum = 1,
-                    Code = assign(X, binary(int_sub, leaf(Z), leaf(Y)))
+                    Code = assign(X, binary(int_sub(IntType), leaf(Z), leaf(Y)))
                 ;
                     ProcNum = 2,
-                    Code = assign(Y, binary(int_sub, leaf(Z), leaf(X)))
+                    Code = assign(Y, binary(int_sub(IntType), leaf(Z), leaf(X)))
                 )
             ;
                 Args = [X, Y],
@@ -340,124 +339,57 @@ builtin_translation(ModuleName, PredName, ProcNum, Args, Code) :-
                 Args = [X, Y, Z],
                 (
                     ProcNum = 0,
-                    Code = assign(Z, binary(int_sub, leaf(X), leaf(Y)))
+                    Code = assign(Z, binary(int_sub(IntType), leaf(X), leaf(Y)))
                 ;
                     ProcNum = 1,
-                    Code = assign(X, binary(int_add, leaf(Y), leaf(Z)))
+                    Code = assign(X, binary(int_add(IntType), leaf(Y), leaf(Z)))
                 ;
                     ProcNum = 2,
-                    Code = assign(Y, binary(int_sub, leaf(X), leaf(Z)))
+                    Code = assign(Y, binary(int_sub(IntType), leaf(X), leaf(Z)))
                 )
             ;
                 Args = [X, Y],
                 ProcNum = 0,
-                Code = assign(Y, binary(int_sub, int_const(0), leaf(X)))
+                Code = assign(Y, binary(int_sub(IntType), int_const(0), leaf(X)))
             )
         ;
             PredName = "xor", Args = [X, Y, Z],
             (
                 ProcNum = 0,
-                Code = assign(Z, binary(bitwise_xor, leaf(X), leaf(Y)))
+                Code = assign(Z, binary(bitwise_xor(IntType), leaf(X), leaf(Y)))
             ;
                 ProcNum = 1,
-                Code = assign(Y, binary(bitwise_xor, leaf(X), leaf(Z)))
+                Code = assign(Y, binary(bitwise_xor(IntType), leaf(X), leaf(Z)))
             ;
                 ProcNum = 2,
-                Code = assign(X, binary(bitwise_xor, leaf(Y), leaf(Z)))
+                Code = assign(X, binary(bitwise_xor(IntType), leaf(Y), leaf(Z)))
             )
         ;
-            ( PredName = "plus", ArithOp = int_add
-            ; PredName = "minus", ArithOp = int_sub
-            ; PredName = "*", ArithOp = int_mul
-            ; PredName = "times", ArithOp = int_mul
-            ; PredName = "unchecked_quotient", ArithOp = int_div
-            ; PredName = "unchecked_rem", ArithOp = int_mod
+            % XXX should we provide plus/2, minus/2 and times/2 for types other
+            % than 'int'?
+            ( PredName = "plus", ModuleName = "int", ArithOp = int_add(int_type_int)
+            ; PredName = "minus", ModuleName = "int", ArithOp = int_sub(int_type_int)
+            ; PredName = "*", ArithOp = int_mul(IntType)
+            ; PredName = "times", ModuleName = "int", ArithOp = int_mul(int_type_int)
+            ; PredName = "unchecked_quotient", ArithOp = int_div(IntType)
+            ; PredName = "unchecked_rem", ArithOp = int_mod(IntType)
             ; PredName = "unchecked_left_shift",
-                ArithOp = unchecked_left_shift
+                ArithOp = unchecked_left_shift(IntType)
             ; PredName = "unchecked_right_shift",
-                ArithOp = unchecked_right_shift
-            ; PredName = "/\\", ArithOp = bitwise_and
-            ; PredName = "\\/", ArithOp = bitwise_or
+                ArithOp = unchecked_right_shift(IntType)
+            ; PredName = "/\\", ArithOp = bitwise_and(IntType)
+            ; PredName = "\\/", ArithOp = bitwise_or(IntType)
             ),
             ProcNum = 0, Args = [X, Y, Z],
             Code = assign(Z, binary(ArithOp, leaf(X), leaf(Y)))
         ;
             PredName = "\\", ProcNum = 0, Args = [X, Y],
-            Code = assign(Y, unary(bitwise_complement, leaf(X)))
-        ;
-            ( PredName = ">", CompareOp = int_gt
-            ; PredName = "<", CompareOp = int_lt
-            ; PredName = ">=", CompareOp = int_ge
-            ; PredName = "=<", CompareOp = int_le
-            ),
-            ProcNum = 0, Args = [X, Y],
-            Code = test(binary(CompareOp, leaf(X), leaf(Y)))
-        )
-    ;
-        ModuleName = "uint",
-        (
-            PredName = "\\",
-            ProcNum = 0,
-            Args = [X, Y],
-            Code = assign(Y, unary(uint_bitwise_complement, leaf(X)))
-        ;
-            PredName = "+",
-            Args = [X, Y, Z],
-            (
-                ProcNum = 0,
-                Code = assign(Z, binary(uint_add, leaf(X), leaf(Y)))
-            ;
-                ProcNum = 1,
-                Code = assign(X, binary(uint_sub, leaf(Z), leaf(Y)))
-            ;
-                ProcNum = 2,
-                Code = assign(Y, binary(uint_sub, leaf(Z), leaf(X)))
-            )
-        ;
-            PredName = "-",
-            Args = [X, Y, Z],
-            (
-                ProcNum = 0,
-                Code = assign(Z, binary(int_sub, leaf(X), leaf(Y)))
-            ;
-                ProcNum = 1,
-                Code = assign(X, binary(uint_add, leaf(Y), leaf(Z)))
-            ;
-                ProcNum = 2,
-                Code = assign(Y, binary(uint_sub, leaf(X), leaf(Z)))
-            )
-        ;
-            ( PredName = "*", ArithOp = uint_mul
-            ; PredName = "unchecked_quotient", ArithOp = uint_div
-            ; PredName = "unchecked_rem", ArithOp = uint_mod
-            ; PredName = "/\\", ArithOp = uint_bitwise_and
-            ; PredName = "\\/", ArithOp = uint_bitwise_or
-            ; PredName = "unchecked_left_shift",
-                ArithOp = uint_unchecked_left_shift
-            ; PredName = "unchecked_right_shift",
-                ArithOp = uint_unchecked_right_shift
-            ),
-            ProcNum = 0,
-            Args = [X, Y, Z],
-            Code = assign(Z, binary(ArithOp, leaf(X), leaf(Y)))
-        ;
-            PredName = "xor",
-            Args = [X, Y, Z],
-            (
-                ProcNum = 0,
-                Code = assign(Z, binary(uint_bitwise_xor, leaf(X), leaf(Y)))
-            ;
-                ProcNum = 1,
-                Code = assign(Y, binary(uint_bitwise_xor, leaf(X), leaf(Z)))
-            ;
-                ProcNum = 2,
-                Code = assign(X, binary(uint_bitwise_xor, leaf(Y), leaf(Z)))
-            )
+            Code = assign(Y, unary(bitwise_complement(IntType), leaf(X)))
         ;
-            ( PredName = ">", CompareOp = uint_gt
-            ; PredName = "<", CompareOp = uint_lt
-            ; PredName = ">=", CompareOp = uint_ge
-            ; PredName = "=<", CompareOp = uint_le
+            ( PredName = ">", CompareOp = int_gt(IntType)
+            ; PredName = "<", CompareOp = int_lt(IntType)
+            ; PredName = ">=", CompareOp = int_ge(IntType)
+            ; PredName = "=<", CompareOp = int_le(IntType)
             ),
             ProcNum = 0, Args = [X, Y],
             Code = test(binary(CompareOp, leaf(X), leaf(Y)))
diff --git a/compiler/bytecode.m b/compiler/bytecode.m
index 5dc8d79b2..3281b9ee3 100644
--- a/compiler/bytecode.m
+++ b/compiler/bytecode.m
@@ -1031,20 +1031,20 @@ determinism_debug(detism_failure,      "failure").
 
 :- pred binop_code(binary_op::in, int::out) is det.
 
-binop_code(int_add,                  0).
-binop_code(int_sub,                  1).
-binop_code(int_mul,                  2).
-binop_code(int_div,                  3).
-binop_code(int_mod,                  4).
-binop_code(unchecked_left_shift,     5).
-binop_code(unchecked_right_shift,    6).
-binop_code(bitwise_and,              7).
-binop_code(bitwise_or,               8).
-binop_code(bitwise_xor,              9).
+binop_code(int_add(int_type_int),    0).
+binop_code(int_sub(int_type_int),    1).
+binop_code(int_mul(int_type_int),    2).
+binop_code(int_div(int_type_int),    3).
+binop_code(int_mod(int_type_int),    4).
+binop_code(unchecked_left_shift(int_type_int),  5).
+binop_code(unchecked_right_shift(int_type_int), 6).
+binop_code(bitwise_and(int_type_int), 7).
+binop_code(bitwise_or(int_type_int),  8).
+binop_code(bitwise_xor(int_type_int), 9).
 binop_code(logical_and,             10).
 binop_code(logical_or,              11).
-binop_code(eq,                      12).
-binop_code(ne,                      13).
+binop_code(eq(int_type_int),        12).
+binop_code(ne(int_type_int),        13).
 binop_code(array_index(_Type),      14).
 binop_code(str_eq,                  15).
 binop_code(str_ne,                  16).
@@ -1052,10 +1052,10 @@ binop_code(str_lt,                  17).
 binop_code(str_gt,                  18).
 binop_code(str_le,                  19).
 binop_code(str_ge,                  20).
-binop_code(int_lt,                  21).
-binop_code(int_gt,                  22).
-binop_code(int_le,                  23).
-binop_code(int_ge,                  24).
+binop_code(int_lt(int_type_int),    21).
+binop_code(int_gt(int_type_int),    22).
+binop_code(int_le(int_type_int),    23).
+binop_code(int_ge(int_type_int),    24).
 binop_code(float_plus,              25).
 binop_code(float_minus,             26).
 binop_code(float_times,             27).
@@ -1076,39 +1076,135 @@ binop_code(float_from_dword,        41).
 binop_code(pointer_equal_conservative, 42).
 binop_code(offset_str_eq(_),        43).
 binop_code(string_unsafe_index_code_unit, 44).
-binop_code(uint_eq,                 45).
-binop_code(uint_ne,                 46).
-binop_code(uint_lt,                 47).
-binop_code(uint_gt,                 48).
-binop_code(uint_le,                 49).
-binop_code(uint_ge,                 50).
-binop_code(uint_add,                51).
-binop_code(uint_sub,                52).
-binop_code(uint_mul,                53).
-binop_code(uint_div,                54).
-binop_code(uint_mod,                55).
-binop_code(uint_bitwise_and,        56).
-binop_code(uint_bitwise_or,         57).
-binop_code(uint_bitwise_xor,        58).
-binop_code(uint_unchecked_left_shift, 59).
-binop_code(uint_unchecked_right_shift, 60).
+binop_code(eq(int_type_uint),       45).
+binop_code(ne(int_type_uint),       46).
+binop_code(int_lt(int_type_uint),   47).
+binop_code(int_gt(int_type_uint),   48).
+binop_code(int_le(int_type_uint),   49).
+binop_code(int_ge(int_type_uint),   50).
+binop_code(int_add(int_type_uint),  51).
+binop_code(int_sub(int_type_uint),  52).
+binop_code(int_mul(int_type_uint),  53).
+binop_code(int_div(int_type_uint),                54).
+binop_code(int_mod(int_type_uint),                55).
+binop_code(bitwise_and(int_type_uint),  56).
+binop_code(bitwise_or(int_type_uint), 57).
+binop_code(bitwise_xor(int_type_uint), 58).
+binop_code(unchecked_left_shift(int_type_uint), 59).
+binop_code(unchecked_right_shift(int_type_uint), 60).
+binop_code(eq(int_type_int8),       61).
+binop_code(ne(int_type_int8),       62).
+binop_code(int_lt(int_type_int8),   63).
+binop_code(int_gt(int_type_int8),   64).
+binop_code(int_le(int_type_int8),   65).
+binop_code(int_ge(int_type_int8),   66).
+binop_code(int_add(int_type_int8),  67).
+binop_code(int_sub(int_type_int8),  68).
+binop_code(int_mul(int_type_int8),  69).
+binop_code(int_div(int_type_int8),  70).
+binop_code(int_mod(int_type_int8),  71).
+binop_code(bitwise_and(int_type_int8), 72).
+binop_code(bitwise_or(int_type_int8), 73).
+binop_code(bitwise_xor(int_type_int8), 74).
+binop_code(unchecked_left_shift(int_type_int8), 75).
+binop_code(unchecked_right_shift(int_type_int8), 76).
+binop_code(eq(int_type_uint8),       77).
+binop_code(ne(int_type_uint8),       78).
+binop_code(int_lt(int_type_uint8),   79).
+binop_code(int_gt(int_type_uint8),   80).
+binop_code(int_le(int_type_uint8),   81).
+binop_code(int_ge(int_type_uint8),   82).
+binop_code(int_add(int_type_uint8),  83).
+binop_code(int_sub(int_type_uint8),  84).
+binop_code(int_mul(int_type_uint8),  85).
+binop_code(int_div(int_type_uint8),  86).
+binop_code(int_mod(int_type_uint8),  87).
+binop_code(bitwise_and(int_type_uint8), 88).
+binop_code(bitwise_or(int_type_uint8),  89).
+binop_code(bitwise_xor(int_type_uint8), 90).
+binop_code(unchecked_left_shift(int_type_uint8), 91).
+binop_code(unchecked_right_shift(int_type_uint8), 92).
+binop_code(eq(int_type_int16),       93).
+binop_code(ne(int_type_int16),       94).
+binop_code(int_lt(int_type_int16),   95).
+binop_code(int_gt(int_type_int16),   96).
+binop_code(int_le(int_type_int16),   97).
+binop_code(int_ge(int_type_int16),   98).
+binop_code(int_add(int_type_int16),  99).
+binop_code(int_sub(int_type_int16), 100).
+binop_code(int_mul(int_type_int16), 101).
+binop_code(int_div(int_type_int16), 102).
+binop_code(int_mod(int_type_int16), 103).
+binop_code(bitwise_and(int_type_int16), 104).
+binop_code(bitwise_or(int_type_int16),  105).
+binop_code(bitwise_xor(int_type_int16), 106).
+binop_code(unchecked_left_shift(int_type_int16),  107).
+binop_code(unchecked_right_shift(int_type_int16), 108).
+binop_code(eq(int_type_uint16),       109).
+binop_code(ne(int_type_uint16),       110).
+binop_code(int_lt(int_type_uint16),   111).
+binop_code(int_gt(int_type_uint16),   112).
+binop_code(int_le(int_type_uint16),   113).
+binop_code(int_ge(int_type_uint16),   114).
+binop_code(int_add(int_type_uint16),  115).
+binop_code(int_sub(int_type_uint16),  116).
+binop_code(int_mul(int_type_uint16),  117).
+binop_code(int_div(int_type_uint16),  118).
+binop_code(int_mod(int_type_uint16),  119).
+binop_code(bitwise_and(int_type_uint16), 120).
+binop_code(bitwise_or(int_type_uint16),  121).
+binop_code(bitwise_xor(int_type_uint16), 122).
+binop_code(unchecked_left_shift(int_type_uint16), 123).
+binop_code(unchecked_right_shift(int_type_uint16), 124).
+binop_code(eq(int_type_int32),       125).
+binop_code(ne(int_type_int32),       126).
+binop_code(int_lt(int_type_int32),   127).
+binop_code(int_gt(int_type_int32),   128).
+binop_code(int_le(int_type_int32),   129).
+binop_code(int_ge(int_type_int32),   130).
+binop_code(int_add(int_type_int32),  131).
+binop_code(int_sub(int_type_int32),  132).
+binop_code(int_mul(int_type_int32),  133).
+binop_code(int_div(int_type_int32),  134).
+binop_code(int_mod(int_type_int32),                135).
+binop_code(bitwise_and(int_type_int32), 136).
+binop_code(bitwise_or(int_type_int32),  137).
+binop_code(bitwise_xor(int_type_int32), 138).
+binop_code(unchecked_left_shift(int_type_int32), 139).
+binop_code(unchecked_right_shift(int_type_int32), 140).
+binop_code(eq(int_type_uint32),       141).
+binop_code(ne(int_type_uint32),       142).
+binop_code(int_lt(int_type_uint32),   143).
+binop_code(int_gt(int_type_uint32),   144).
+binop_code(int_le(int_type_uint32),   145).
+binop_code(int_ge(int_type_uint32),   146).
+binop_code(int_add(int_type_uint32),  147).
+binop_code(int_sub(int_type_uint32),  148).
+binop_code(int_mul(int_type_uint32),  149).
+binop_code(int_div(int_type_uint32),  150).
+binop_code(int_mod(int_type_uint32),  151).
+binop_code(bitwise_and(int_type_uint32), 152).
+binop_code(bitwise_or(int_type_uint32),  153).
+binop_code(bitwise_xor(int_type_uint32), 154).
+binop_code(unchecked_left_shift(int_type_uint32),  155).
+binop_code(unchecked_right_shift(int_type_uint32), 156).
 
 :- pred binop_debug(binary_op::in, string::out) is det.
 
-binop_debug(int_add,                "+").
-binop_debug(int_sub,                "-").
-binop_debug(int_mul,                "*").
-binop_debug(int_div,                "/").
-binop_debug(int_mod,                "mod").
-binop_debug(unchecked_left_shift,   "<<").
-binop_debug(unchecked_right_shift,  ">>").
-binop_debug(bitwise_and,            "&").
-binop_debug(bitwise_or,             "|").
-binop_debug(bitwise_xor,            "^").
+binop_debug(int_add(int_type_int),  "+").
+binop_debug(int_sub(int_type_int),  "-").
+binop_debug(int_mul(int_type_int),  "*").
+binop_debug(int_div(int_type_int),  "/").
+binop_debug(int_mod(int_type_int),  "mod").
+binop_debug(unchecked_left_shift(int_type_int),   "<<").
+binop_debug(unchecked_right_shift(int_type_int),  ">>").
+binop_debug(bitwise_and(int_type_int), "&").
+binop_debug(bitwise_or(int_type_int), "|").
+binop_debug(bitwise_xor(int_type_int), "^").
 binop_debug(logical_and,            "and").
 binop_debug(logical_or,             "or").
-binop_debug(eq,                     "eq").
-binop_debug(ne,                     "ne").
+binop_debug(eq(int_type_int),       "eq").
+binop_debug(ne(int_type_int),       "ne").
 binop_debug(array_index(_Type),     "array_index").
 binop_debug(str_eq,                 "str_eq").
 binop_debug(str_ne,                 "str_ne").
@@ -1116,10 +1212,10 @@ binop_debug(str_lt,                 "str_lt").
 binop_debug(str_gt,                 "str_gt").
 binop_debug(str_le,                 "str_le").
 binop_debug(str_ge,                 "str_ge").
-binop_debug(int_lt,                 "<").
-binop_debug(int_gt,                 ">").
-binop_debug(int_le,                 "<=").
-binop_debug(int_ge,                 ">=").
+binop_debug(int_lt(int_type_int),   "<").
+binop_debug(int_gt(int_type_int),   ">").
+binop_debug(int_le(int_type_int),   "<=").
+binop_debug(int_ge(int_type_int),   ">=").
 binop_debug(float_plus,             "float_plus").
 binop_debug(float_minus,            "float_minus").
 binop_debug(float_times,            "float_times").
@@ -1140,22 +1236,118 @@ binop_debug(float_from_dword,       "float_from_dword").
 binop_debug(pointer_equal_conservative, "pointer_equal_conservative").
 binop_debug(offset_str_eq(_),       "offset_str_eq").
 binop_debug(string_unsafe_index_code_unit, "string_unsafe_index_code_unit").
-binop_debug(uint_eq,                "uint_eq").
-binop_debug(uint_ne,                "uint_ne").
-binop_debug(uint_lt,                "uint_lt").
-binop_debug(uint_gt,                "uint_gt").
-binop_debug(uint_le,                "uint_le").
-binop_debug(uint_ge,                "uint_ge").
-binop_debug(uint_add,               "uint_add").
-binop_debug(uint_sub,               "uint_sub").
-binop_debug(uint_mul,               "uint_mul").
-binop_debug(uint_div,               "uint_div").
-binop_debug(uint_mod,               "uint_mod").
-binop_debug(uint_bitwise_and,       "uint_bitwise_and").
-binop_debug(uint_bitwise_or,        "uint_bitwise_or").
-binop_debug(uint_bitwise_xor,       "uint_bitwise_xor").
-binop_debug(uint_unchecked_left_shift, "uint_unchecked_left_shift").
-binop_debug(uint_unchecked_right_shift, "uint_unchecked_right_shift").
+binop_debug(eq(int_type_uint),      "==(uint)").
+binop_debug(ne(int_type_uint),      "!=(uint)").
+binop_debug(int_lt(int_type_uint),  "<(uint)").
+binop_debug(int_gt(int_type_uint),  ">(uint)").
+binop_debug(int_le(int_type_uint),  "<=(uint)").
+binop_debug(int_ge(int_type_uint),  ">=(uint)").
+binop_debug(int_add(int_type_uint), "+(uint)").
+binop_debug(int_sub(int_type_uint), "-(uint)").
+binop_debug(int_mul(int_type_uint), "*(uint)").
+binop_debug(int_div(int_type_uint), "/(uint)").
+binop_debug(int_mod(int_type_uint), "mod(uint)").
+binop_debug(bitwise_and(int_type_uint), "&(uint)").
+binop_debug(bitwise_or(int_type_uint), "|(uint)").
+binop_debug(bitwise_xor(int_type_uint), "^(uint)").
+binop_debug(unchecked_left_shift(int_type_uint), "<<(uint)").
+binop_debug(unchecked_right_shift(int_type_uint), ">>(uint)").
+binop_debug(eq(int_type_int8),      "==(int8)").
+binop_debug(ne(int_type_int8),      "!=(int8)").
+binop_debug(int_lt(int_type_int8),  "<(int8)").
+binop_debug(int_gt(int_type_int8),  ">(int8)").
+binop_debug(int_le(int_type_int8),  "<=(int8)").
+binop_debug(int_ge(int_type_int8),  ">=(int8)").
+binop_debug(int_add(int_type_int8), "+(int8)").
+binop_debug(int_sub(int_type_int8), "-(int8)").
+binop_debug(int_mul(int_type_int8), "*(int8)").
+binop_debug(int_div(int_type_int8), "/(int8)").
+binop_debug(int_mod(int_type_int8), "mod(int8)").
+binop_debug(bitwise_and(int_type_int8), "&(int8)").
+binop_debug(bitwise_or(int_type_int8), "|(int8)").
+binop_debug(bitwise_xor(int_type_int8), "^(int8)").
+binop_debug(unchecked_left_shift(int_type_int8), "<<(int8)").
+binop_debug(unchecked_right_shift(int_type_int8), ">>(int8)").
+binop_debug(eq(int_type_uint8),      "==(uint8)").
+binop_debug(ne(int_type_uint8),      "!=(uint8)").
+binop_debug(int_lt(int_type_uint8),  "<(uint8)").
+binop_debug(int_gt(int_type_uint8),  ">(uint8)").
+binop_debug(int_le(int_type_uint8),  "<=(uint8)").
+binop_debug(int_ge(int_type_uint8),  ">=(uint8)").
+binop_debug(int_add(int_type_uint8), "+(uint8)").
+binop_debug(int_sub(int_type_uint8), "-(uint8)").
+binop_debug(int_mul(int_type_uint8), "*(uint8)").
+binop_debug(int_div(int_type_uint8), "/(uint8)").
+binop_debug(int_mod(int_type_uint8), "mod(uint8)").
+binop_debug(bitwise_and(int_type_uint8), "&(uint8)").
+binop_debug(bitwise_or(int_type_uint8), "|(uint8)").
+binop_debug(bitwise_xor(int_type_uint8), "^(uint8)").
+binop_debug(unchecked_left_shift(int_type_uint8), "<<(uint8)").
+binop_debug(unchecked_right_shift(int_type_uint8), ">>(uint8)").
+binop_debug(eq(int_type_int16),      "==(int6)").
+binop_debug(ne(int_type_int16),      "!=(int16)").
+binop_debug(int_lt(int_type_int16),  "<(int16)").
+binop_debug(int_gt(int_type_int16),  ">(int16)").
+binop_debug(int_le(int_type_int16),  "<=(int16)").
+binop_debug(int_ge(int_type_int16),  ">=(int16)").
+binop_debug(int_add(int_type_int16), "+(int16)").
+binop_debug(int_sub(int_type_int16), "-(int16)").
+binop_debug(int_mul(int_type_int16), "*(int16)").
+binop_debug(int_div(int_type_int16), "/(int16)").
+binop_debug(int_mod(int_type_int16), "mod(int16)").
+binop_debug(bitwise_and(int_type_int16), "&(int16)").
+binop_debug(bitwise_or(int_type_int16), "|(int16)").
+binop_debug(bitwise_xor(int_type_int16), "^(int16)").
+binop_debug(unchecked_left_shift(int_type_int16), "<<(int16)").
+binop_debug(unchecked_right_shift(int_type_int16), ">>(int16)").
+binop_debug(eq(int_type_uint16),      "==(uint16)").
+binop_debug(ne(int_type_uint16),      "!=(uint16)").
+binop_debug(int_lt(int_type_uint16),  "<(uint16)").
+binop_debug(int_gt(int_type_uint16),  ">(uint16)").
+binop_debug(int_le(int_type_uint16),  "<=(uint16)").
+binop_debug(int_ge(int_type_uint16),  ">=(uint16)").
+binop_debug(int_add(int_type_uint16), "+(uint16)").
+binop_debug(int_sub(int_type_uint16), "-(uint16)").
+binop_debug(int_mul(int_type_uint16), "*(uint16)").
+binop_debug(int_div(int_type_uint16), "/(uint16)").
+binop_debug(int_mod(int_type_uint16), "mod(uint16)").
+binop_debug(bitwise_and(int_type_uint16), "&(uint16)").
+binop_debug(bitwise_or(int_type_uint16), "|(uint16)").
+binop_debug(bitwise_xor(int_type_uint16), "^(uint16)").
+binop_debug(unchecked_left_shift(int_type_uint16), "<<(uint16)").
+binop_debug(unchecked_right_shift(int_type_uint16), ">>(uint16)").
+binop_debug(eq(int_type_int32),      "==(int32)").
+binop_debug(ne(int_type_int32),      "!=(int32)").
+binop_debug(int_lt(int_type_int32),  "<(int32)").
+binop_debug(int_gt(int_type_int32),  ">(int32)").
+binop_debug(int_le(int_type_int32),  "<=(int32)").
+binop_debug(int_ge(int_type_int32),  ">=(int32)").
+binop_debug(int_add(int_type_int32), "+(int32)").
+binop_debug(int_sub(int_type_int32), "-(int32)").
+binop_debug(int_mul(int_type_int32), "*(int32)").
+binop_debug(int_div(int_type_int32), "/(int32)").
+binop_debug(int_mod(int_type_int32), "mod(int32)").
+binop_debug(bitwise_and(int_type_int32), "&(int32)").
+binop_debug(bitwise_or(int_type_int32), "|(int32)").
+binop_debug(bitwise_xor(int_type_int32), "^(int32)").
+binop_debug(unchecked_left_shift(int_type_int32), "<<(int32)").
+binop_debug(unchecked_right_shift(int_type_int32), ">>(int32)").
+binop_debug(eq(int_type_uint32),      "==(uint32)").
+binop_debug(ne(int_type_uint32),      "!=(uint32)").
+binop_debug(int_lt(int_type_uint32),  "<(uint32)").
+binop_debug(int_gt(int_type_uint32),  ">(uint32)").
+binop_debug(int_le(int_type_uint32),  "<=(uint32)").
+binop_debug(int_ge(int_type_uint32),  ">=(uint32)").
+binop_debug(int_add(int_type_uint32), "+(uint32)").
+binop_debug(int_sub(int_type_uint32), "-(uint32)").
+binop_debug(int_mul(int_type_uint32), "*(uint32)").
+binop_debug(int_div(int_type_uint32), "/(uint32)").
+binop_debug(int_mod(int_type_uint32), "mod(uint32").
+binop_debug(bitwise_and(int_type_uint32), "&(uint32)").
+binop_debug(bitwise_or(int_type_uint32),  "|(uint32)").
+binop_debug(bitwise_xor(int_type_uint32), "^(uint32)").
+binop_debug(unchecked_left_shift(int_type_uint32), "<<(uint32)").
+binop_debug(unchecked_right_shift(int_type_uint32), ">>(uint32)").
 
 :- pred unop_code(unary_op::in, int::out) is det.
 
@@ -1165,7 +1357,7 @@ unop_code(unmktag,              2).
 unop_code(mkbody,               3).
 unop_code(unmkbody,             4).
 unop_code(strip_tag,            5).
-unop_code(bitwise_complement,   6).
+unop_code(bitwise_complement(int_type_int), 6).
 unop_code(logical_not,          7).
 unop_code(hash_string,          8).
 unop_code(hash_string2,         9).
@@ -1173,7 +1365,13 @@ unop_code(hash_string3,        10).
 unop_code(hash_string4,        11).
 unop_code(hash_string5,        12).
 unop_code(hash_string6,        13).
-unop_code(uint_bitwise_complement, 14).
+unop_code(bitwise_complement(int_type_uint), 14).
+unop_code(bitwise_complement(int_type_int8), 15).
+unop_code(bitwise_complement(int_type_uint8), 16).
+unop_code(bitwise_complement(int_type_int16), 17).
+unop_code(bitwise_complement(int_type_uint16), 18).
+unop_code(bitwise_complement(int_type_int32), 19).
+unop_code(bitwise_complement(int_type_uint32), 20).
 
 :- pred unop_debug(unary_op::in, string::out) is det.
 
@@ -1183,7 +1381,7 @@ unop_debug(unmktag,             "unmktag").
 unop_debug(mkbody,              "mkbody").
 unop_debug(unmkbody,            "unmkbody").
 unop_debug(strip_tag,           "strip_tag").
-unop_debug(bitwise_complement,  "bitwise_complement").
+unop_debug(bitwise_complement(int_type_int),  "bitwise_complement(int)").
 unop_debug(logical_not,         "not").
 unop_debug(hash_string,         "hash_string").
 unop_debug(hash_string2,        "hash_string2").
@@ -1191,7 +1389,13 @@ unop_debug(hash_string3,        "hash_string3").
 unop_debug(hash_string4,        "hash_string4").
 unop_debug(hash_string5,        "hash_string5").
 unop_debug(hash_string6,        "hash_string6").
-unop_debug(uint_bitwise_complement, "uint_bitwise_complement").
+unop_debug(bitwise_complement(int_type_uint), "bitwise_complement(uint)").
+unop_debug(bitwise_complement(int_type_int8), "bitwise_complement(int8)").
+unop_debug(bitwise_complement(int_type_uint8), "bitwise_complement(uint8)").
+unop_debug(bitwise_complement(int_type_int16), "bitwise_complement(int16)").
+unop_debug(bitwise_complement(int_type_uint16), "bitwise_complement(uint16)").
+unop_debug(bitwise_complement(int_type_int32), "bitwise_complement(int32)").
+unop_debug(bitwise_complement(int_type_uint32), "bitwise_complement(uint32)").
 
 %---------------------------------------------------------------------------%
 
diff --git a/compiler/bytecode_gen.m b/compiler/bytecode_gen.m
index 9174830a4..1a172370f 100644
--- a/compiler/bytecode_gen.m
+++ b/compiler/bytecode_gen.m
@@ -575,12 +575,30 @@ gen_unify(Unification, ByteInfo, Code) :-
         ByteInfo = byte_info(_, _, ModuleInfo, _, _),
         TypeCategory = classify_type_ctor(ModuleInfo, TypeCtor),
         (
-            TypeCategory = ctor_cat_builtin(cat_builtin_int),
+            TypeCategory = ctor_cat_builtin(cat_builtin_int(int_type_int)),
             TestId = int_test
         ;
-            TypeCategory = ctor_cat_builtin(cat_builtin_uint),
+            TypeCategory = ctor_cat_builtin(cat_builtin_int(int_type_uint)),
             sorry($module, $pred, "uint")
         ;
+            TypeCategory = ctor_cat_builtin(cat_builtin_int(int_type_int8)),
+            sorry($module, $pred, "int8")
+        ;
+            TypeCategory = ctor_cat_builtin(cat_builtin_int(int_type_uint8)),
+            sorry($module, $pred, "uint8")
+        ;
+            TypeCategory = ctor_cat_builtin(cat_builtin_int(int_type_int16)),
+            sorry($module, $pred, "int16")
+        ;
+            TypeCategory = ctor_cat_builtin(cat_builtin_int(int_type_uint16)),
+            sorry($module, $pred, "uint16")
+        ;
+            TypeCategory = ctor_cat_builtin(cat_builtin_int(int_type_int32)),
+            sorry($module, $pred, "int32")
+        ;
+            TypeCategory = ctor_cat_builtin(cat_builtin_int(int_type_uint32)),
+            sorry($module, $pred, "uint32")
+        ;
             TypeCategory = ctor_cat_builtin(cat_builtin_char),
             TestId = char_test
         ;
@@ -769,6 +787,24 @@ map_cons_id(ByteInfo, ConsId, ByteConsId) :-
         ConsId = uint_const(_),
         unexpected($file, $pred, "uint")
     ;
+        ConsId = int8_const(_),
+        unexpected($file, $pred, "int8")
+    ;
+        ConsId = uint8_const(_),
+        unexpected($file, $pred, "uint8")
+    ;
+        ConsId = int16_const(_),
+        unexpected($file, $pred, "int16")
+    ;
+        ConsId = uint16_const(_),
+        unexpected($file, $pred, "uint16")
+    ;
+        ConsId = int32_const(_),
+        unexpected($file, $pred, "int32")
+    ;
+        ConsId = uint32_const(_),
+        unexpected($file, $pred, "uint32")
+    ;
         ConsId = float_const(FloatVal),
         ByteConsId = byte_float_const(FloatVal)
     ;
@@ -833,6 +869,18 @@ map_cons_tag(string_tag(_), _) :-
 map_cons_tag(int_tag(IntVal), byte_enum_tag(IntVal)).
 map_cons_tag(uint_tag(_), _) :-
     sorry($module, $pred, "bytecode with uints").
+map_cons_tag(int8_tag(_), _) :-
+    sorry($module, $pred, "bytecode with int8s").
+map_cons_tag(uint8_tag(_), _) :-
+    sorry($module, $pred, "bytecode with uint8s").
+map_cons_tag(int16_tag(_), _) :-
+    sorry($module, $pred, "bytecode with int16s").
+map_cons_tag(uint16_tag(_), _) :-
+    sorry($module, $pred, "bytecode with uint16s").
+map_cons_tag(int32_tag(_), _) :-
+    sorry($module, $pred, "bytecode with int32s").
+map_cons_tag(uint32_tag(_), _) :-
+    sorry($module, $pred, "bytecode with uint32s").
 map_cons_tag(foreign_tag(_, _), _) :-
     sorry($module, $pred, "bytecode with foreign tags").
 map_cons_tag(float_tag(_), _) :-
diff --git a/compiler/c_util.m b/compiler/c_util.m
index 4f25295ba..48ea69617 100644
--- a/compiler/c_util.m
+++ b/compiler/c_util.m
@@ -214,6 +214,9 @@
     %
 :- pred unary_prefix_op(unary_op::in, string::out) is det.
 
+    % XXX is this type really necessary?  binop_category_string/3's only caller
+    % only cares about if the operation is a 'float_arith_binop' or not.
+    %
 :- type binop_category
     --->    array_index_binop
     ;       string_index_binop
@@ -223,8 +226,6 @@
     ;       general_string_compare_binop
     ;       string_compare_binop
     ;       unsigned_compare_binop
-    ;       uint_compare_binop
-    ;       uint_binary_infix_binop
     ;       float_compare_binop
     ;       float_arith_binop
     ;       int_or_bool_binary_infix_binop
@@ -809,9 +810,8 @@ unary_prefix_op(unmktag,            "MR_unmktag").
 unary_prefix_op(strip_tag,          "MR_strip_tag").
 unary_prefix_op(mkbody,             "MR_mkbody").
 unary_prefix_op(unmkbody,           "MR_unmkbody").
-unary_prefix_op(bitwise_complement, "~").
+unary_prefix_op(bitwise_complement(_), "~").
 unary_prefix_op(logical_not,        "!").
-unary_prefix_op(uint_bitwise_complement, "~").
 unary_prefix_op(hash_string,        "MR_hash_string").
 unary_prefix_op(hash_string2,       "MR_hash_string2").
 unary_prefix_op(hash_string3,       "MR_hash_string3").
@@ -840,24 +840,6 @@ binop_category_string(str_gt, string_compare_binop, ">").
 
 binop_category_string(unsigned_le, unsigned_compare_binop, "<=").
 
-binop_category_string(uint_eq, uint_compare_binop, "==").
-binop_category_string(uint_ne, uint_compare_binop, "!=").
-binop_category_string(uint_le, uint_compare_binop, "<=").
-binop_category_string(uint_ge, uint_compare_binop, ">=").
-binop_category_string(uint_lt, uint_compare_binop, "<").
-binop_category_string(uint_gt, uint_compare_binop, ">").
-
-binop_category_string(uint_add, uint_binary_infix_binop, "+").
-binop_category_string(uint_sub, uint_binary_infix_binop, "-").
-binop_category_string(uint_mul, uint_binary_infix_binop, "*").
-binop_category_string(uint_div, uint_binary_infix_binop, "/").
-binop_category_string(uint_mod, uint_binary_infix_binop, "%").
-binop_category_string(uint_bitwise_and, uint_binary_infix_binop, "&").
-binop_category_string(uint_bitwise_or, uint_binary_infix_binop, "|").
-binop_category_string(uint_bitwise_xor, uint_binary_infix_binop, "^").
-binop_category_string(uint_unchecked_left_shift, uint_binary_infix_binop, "<<").
-binop_category_string(uint_unchecked_right_shift, uint_binary_infix_binop, ">>").
-
 binop_category_string(float_plus, float_arith_binop, "+").
 binop_category_string(float_minus, float_arith_binop, "-").
 binop_category_string(float_times, float_arith_binop, "*").
@@ -870,26 +852,26 @@ binop_category_string(float_ge, float_compare_binop, ">=").
 binop_category_string(float_lt, float_compare_binop, "<").
 binop_category_string(float_gt, float_compare_binop, ">").
 
-binop_category_string(int_add, int_or_bool_binary_infix_binop, "+").
-binop_category_string(int_sub, int_or_bool_binary_infix_binop, "-").
-binop_category_string(int_mul, int_or_bool_binary_infix_binop, "*").
-binop_category_string(int_div, int_or_bool_binary_infix_binop, "/").
-binop_category_string(unchecked_left_shift,  int_or_bool_binary_infix_binop,
+binop_category_string(int_add(_), int_or_bool_binary_infix_binop, "+").
+binop_category_string(int_sub(_), int_or_bool_binary_infix_binop, "-").
+binop_category_string(int_mul(_), int_or_bool_binary_infix_binop, "*").
+binop_category_string(int_div(_), int_or_bool_binary_infix_binop, "/").
+binop_category_string(unchecked_left_shift(_),  int_or_bool_binary_infix_binop,
     "<<").
-binop_category_string(unchecked_right_shift, int_or_bool_binary_infix_binop,
+binop_category_string(unchecked_right_shift(_), int_or_bool_binary_infix_binop,
     ">>").
-binop_category_string(bitwise_and, int_or_bool_binary_infix_binop, "&").
-binop_category_string(bitwise_or, int_or_bool_binary_infix_binop, "|").
-binop_category_string(bitwise_xor, int_or_bool_binary_infix_binop, "^").
-binop_category_string(int_mod, int_or_bool_binary_infix_binop, "%").
-binop_category_string(eq, int_or_bool_binary_infix_binop, "==").
-binop_category_string(ne, int_or_bool_binary_infix_binop, "!=").
+binop_category_string(bitwise_and(_), int_or_bool_binary_infix_binop, "&").
+binop_category_string(bitwise_or(_), int_or_bool_binary_infix_binop, "|").
+binop_category_string(bitwise_xor(_), int_or_bool_binary_infix_binop, "^").
+binop_category_string(int_mod(_), int_or_bool_binary_infix_binop, "%").
+binop_category_string(eq(_), int_or_bool_binary_infix_binop, "==").
+binop_category_string(ne(_), int_or_bool_binary_infix_binop, "!=").
 binop_category_string(logical_and, int_or_bool_binary_infix_binop, "&&").
 binop_category_string(logical_or, int_or_bool_binary_infix_binop, "||").
-binop_category_string(int_lt, int_or_bool_binary_infix_binop, "<").
-binop_category_string(int_gt, int_or_bool_binary_infix_binop, ">").
-binop_category_string(int_le, int_or_bool_binary_infix_binop, "<=").
-binop_category_string(int_ge, int_or_bool_binary_infix_binop, ">=").
+binop_category_string(int_lt(_), int_or_bool_binary_infix_binop, "<").
+binop_category_string(int_gt(_), int_or_bool_binary_infix_binop, ">").
+binop_category_string(int_le(_), int_or_bool_binary_infix_binop, "<=").
+binop_category_string(int_ge(_), int_or_bool_binary_infix_binop, ">=").
 
 binop_category_string(str_cmp, general_string_compare_binop, "MR_strcmp").
 binop_category_string(offset_str_eq(N), offset_string_compare_binop(N),
diff --git a/compiler/call_gen.m b/compiler/call_gen.m
index f43bdcd78..11ad7f0ea 100644
--- a/compiler/call_gen.m
+++ b/compiler/call_gen.m
@@ -747,6 +747,12 @@ generate_assign_builtin(Var, AssignExpr, Code, !CLD) :-
 convert_simple_expr(leaf(Var)) = var(Var).
 convert_simple_expr(int_const(Int)) = const(llconst_int(Int)).
 convert_simple_expr(uint_const(UInt)) = const(llconst_uint(UInt)).
+convert_simple_expr(int8_const(Int8)) = const(llconst_int8(Int8)).
+convert_simple_expr(uint8_const(UInt8)) = const(llconst_uint8(UInt8)).
+convert_simple_expr(int16_const(Int16)) = const(llconst_int16(Int16)).
+convert_simple_expr(uint16_const(UInt16)) = const(llconst_uint16(UInt16)).
+convert_simple_expr(int32_const(Int32)) = const(llconst_int32(Int32)).
+convert_simple_expr(uint32_const(UInt32)) = const(llconst_uint32(UInt32)).
 convert_simple_expr(float_const(Float)) = const(llconst_float(Float)).
 convert_simple_expr(unary(UnOp, Expr)) =
     unop(UnOp, convert_simple_expr(Expr)).
diff --git a/compiler/code_util.m b/compiler/code_util.m
index b194f7414..dc73ca7a7 100644
--- a/compiler/code_util.m
+++ b/compiler/code_util.m
@@ -354,12 +354,12 @@ natural_neg_rval(binop(Op, X, Y), binop(NegOp, X, Y)) :-
 
 :- pred neg_op(binary_op::in, binary_op::out) is semidet.
 
-neg_op(eq, ne).
-neg_op(ne, eq).
-neg_op(int_lt, int_ge).
-neg_op(int_le, int_gt).
-neg_op(int_gt, int_le).
-neg_op(int_ge, int_lt).
+neg_op(eq(T), ne(T)).
+neg_op(ne(T), eq(T)).
+neg_op(int_lt(T), int_ge(T)).
+neg_op(int_le(T), int_gt(T)).
+neg_op(int_gt(T), int_le(T)).
+neg_op(int_ge(T), int_lt(T)).
 neg_op(str_eq, str_ne).
 neg_op(str_ne, str_eq).
 neg_op(str_lt, str_ge).
diff --git a/compiler/ctgc.selector.m b/compiler/ctgc.selector.m
index 7f1465e9a..928cf65f9 100644
--- a/compiler/ctgc.selector.m
+++ b/compiler/ctgc.selector.m
@@ -117,6 +117,12 @@ selector_init(ConsId, Index) = [TermSel] :-
         ( ConsId = closure_cons(_, _)
         ; ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
diff --git a/compiler/dead_proc_elim.m b/compiler/dead_proc_elim.m
index b36fdd8d2..76ba08506 100644
--- a/compiler/dead_proc_elim.m
+++ b/compiler/dead_proc_elim.m
@@ -819,6 +819,12 @@ dead_proc_examine_goal(Goal, CurrProc, !Queue, !Needed) :-
                 ; ConsId = tuple_cons(_)
                 ; ConsId = int_const(_)
                 ; ConsId = uint_const(_)
+                ; ConsId = int8_const(_)
+                ; ConsId = uint8_const(_)
+                ; ConsId = int16_const(_)
+                ; ConsId = uint16_const(_)
+                ; ConsId = int32_const(_)
+                ; ConsId = uint32_const(_)
                 ; ConsId = float_const(_)
                 ; ConsId = char_const(_)
                 ; ConsId = string_const(_)
diff --git a/compiler/dense_switch.m b/compiler/dense_switch.m
index d552bfe0a..4dd2a7d95 100644
--- a/compiler/dense_switch.m
+++ b/compiler/dense_switch.m
@@ -128,7 +128,8 @@ generate_dense_switch(TaggedCases, VarRval, VarName, CodeModel, SwitchGoalInfo,
     ( if FirstVal = 0 then
         IndexRval = VarRval
     else
-        IndexRval = binop(int_sub, VarRval, const(llconst_int(FirstVal)))
+        IndexRval = binop(int_sub(int_type_int), VarRval,
+            const(llconst_int(FirstVal)))
     ),
     % If the switch is not locally deterministic, we need to check that
     % the value of the variable lies within the appropriate range.
diff --git a/compiler/dep_par_conj.m b/compiler/dep_par_conj.m
index 0be54b798..6fcb69525 100644
--- a/compiler/dep_par_conj.m
+++ b/compiler/dep_par_conj.m
@@ -3151,7 +3151,7 @@ allocate_future(ModuleInfo, SharedVar, Goals, !VarSet, !VarTypes,
         ForeignAttrs = par_builtin_foreign_proc_attributes(purity_pure, no),
         ArgName = foreign_arg(FutureNameVar,
             yes(foreign_arg_name_mode("Name", in_mode)),
-            builtin_type(builtin_type_int), bp_native_if_possible),
+            builtin_type(builtin_type_int(int_type_int)), bp_native_if_possible),
         ArgFuture = foreign_arg(FutureVar,
             yes(foreign_arg_name_mode("Future", out_mode)),
             FutureVarType, bp_native_if_possible),
@@ -3185,7 +3185,7 @@ make_future_var(SharedVarName, SharedVarType, FutureVar, FutureVarType,
 make_future_name_var_and_goal(Name, FutureNameVar, Goal, !VarSet, !VarTypes,
         !TSStringTable) :-
     varset.new_named_var("FutureName" ++ Name, FutureNameVar, !VarSet),
-    IntType = builtin_type(builtin_type_int),
+    IntType = builtin_type(builtin_type_int(int_type_int)),
     add_var_type(FutureNameVar, IntType, !VarTypes),
     allocate_ts_string(Name, NameId, !TSStringTable),
     RHS = rhs_functor(int_const(NameId), is_not_exist_constr, []),
diff --git a/compiler/disj_gen.m b/compiler/disj_gen.m
index 55a01cbbb..64ae4554e 100644
--- a/compiler/disj_gen.m
+++ b/compiler/disj_gen.m
@@ -278,12 +278,13 @@ generate_lookup_disj(ResumeVars, LookupDisjInfo, Code, !CI, !CLD) :-
     TestMoreSolnsCode = from_list([
         llds_instr(assign(LaterBaseReg, lval(CurSlot)),
             "Init later base register"),
-        llds_instr(if_val(binop(int_ge, lval(LaterBaseReg),
+        llds_instr(if_val(binop(int_ge(int_type_int), lval(LaterBaseReg),
             const(llconst_int(MaxSlot))),
             code_label(UndoLabel)),
             "Jump to undo hijack code if there are no more solutions"),
         llds_instr(assign(CurSlot,
-            binop(int_add, lval(CurSlot), const(llconst_int(NumOutVars)))),
+            binop(int_add(int_type_int), lval(CurSlot),
+            const(llconst_int(NumOutVars)))),
             "Update current slot"),
         llds_instr(goto(code_label(AfterUndoLabel)),
             "Jump around undo hijack code"),
diff --git a/compiler/dupproc.m b/compiler/dupproc.m
index 483e27a72..57db91391 100644
--- a/compiler/dupproc.m
+++ b/compiler/dupproc.m
@@ -341,31 +341,16 @@ standardize_code_addr(CodeAddr, StdCodeAddr, DupProcMap) :-
         standardize_proc_label(ProcLabel, StdProcLabel, DupProcMap),
         StdCodeAddr = code_imported_proc(StdProcLabel)
     ;
-        CodeAddr = code_succip,
-        StdCodeAddr = CodeAddr
-    ;
-        CodeAddr = do_succeed(_),
-        StdCodeAddr = CodeAddr
-    ;
-        CodeAddr = do_redo,
-        StdCodeAddr = CodeAddr
-    ;
-        CodeAddr = do_fail,
-        StdCodeAddr = CodeAddr
-    ;
-        CodeAddr = do_trace_redo_fail_shallow,
-        StdCodeAddr = CodeAddr
-    ;
-        CodeAddr = do_trace_redo_fail_deep,
-        StdCodeAddr = CodeAddr
-    ;
-        CodeAddr = do_call_closure(_),
-        StdCodeAddr = CodeAddr
-    ;
-        CodeAddr = do_call_class_method(_),
-        StdCodeAddr = CodeAddr
-    ;
-        CodeAddr = do_not_reached,
+        ( CodeAddr = code_succip
+        ; CodeAddr = do_succeed(_)
+        ; CodeAddr = do_redo
+        ; CodeAddr = do_fail
+        ; CodeAddr = do_trace_redo_fail_shallow
+        ; CodeAddr = do_trace_redo_fail_deep
+        ; CodeAddr = do_call_closure(_)
+        ; CodeAddr = do_call_class_method(_)
+        ; CodeAddr = do_not_reached
+        ),
         StdCodeAddr = CodeAddr
     ).
 
@@ -391,18 +376,16 @@ standardize_maybe_code_addr(MaybeCodeAddr, MaybeStdCodeAddr, DupProcMap) :-
 
 standardize_rval(Rval, StdRval, DupProcMap) :-
     (
-        Rval = lval(_),
+        ( Rval = lval(_)
+        ; Rval = mkword(_, _)
+        ; Rval = mkword_hole(_)
+        ; Rval = mem_addr(_)
+        ),
         StdRval = Rval
     ;
         Rval = var(_),
         unexpected($module, $pred, "var")
     ;
-        Rval = mkword(_, _),
-        StdRval = Rval
-    ;
-        Rval = mkword_hole(_),
-        StdRval = Rval
-    ;
         Rval = const(Const),
         standardize_rval_const(Const, StdConst, DupProcMap),
         StdRval = const(StdConst)
@@ -415,9 +398,6 @@ standardize_rval(Rval, StdRval, DupProcMap) :-
         standardize_rval(RvalL, StdRvalL, DupProcMap),
         standardize_rval(RvalR, StdRvalR, DupProcMap),
         StdRval = binop(Binop, StdRvalL, StdRvalR)
-    ;
-        Rval = mem_addr(_),
-        StdRval = Rval
     ).
 
     % Compute the standard form of an rval constant.
@@ -427,36 +407,27 @@ standardize_rval(Rval, StdRval, DupProcMap) :-
 
 standardize_rval_const(Const, StdConst, DupProcMap) :-
     (
-        Const = llconst_true,
-        StdConst = Const
-    ;
-        Const = llconst_false,
-        StdConst = Const
-    ;
-        Const = llconst_int(_),
-        StdConst = Const
-    ;
-        Const = llconst_uint(_),
-        StdConst = Const
-    ;
-        Const = llconst_foreign(_, _),
-        StdConst = Const
-    ;
-        Const = llconst_float(_),
-        StdConst = Const
-    ;
-        Const = llconst_string(_),
-        StdConst = Const
-    ;
-        Const = llconst_multi_string(_),
+        ( Const = llconst_true
+        ; Const = llconst_false
+        ; Const = llconst_int(_)
+        ; Const = llconst_uint(_)
+        ; Const = llconst_int8(_)
+        ; Const = llconst_uint8(_)
+        ; Const = llconst_int16(_)
+        ; Const = llconst_uint16(_)
+        ; Const = llconst_int32(_)
+        ; Const = llconst_uint32(_)
+        ; Const = llconst_foreign(_, _)
+        ; Const = llconst_float(_)
+        ; Const = llconst_string(_)
+        ; Const = llconst_multi_string(_)
+        ; Const = llconst_data_addr(_, _)
+        ),
         StdConst = Const
     ;
         Const = llconst_code_addr(CodeAddr),
         standardize_code_addr(CodeAddr, StdCodeAddr, DupProcMap),
         StdConst = llconst_code_addr(StdCodeAddr)
-    ;
-        Const = llconst_data_addr(_, _),
-        StdConst = Const
     ).
 
 %-----------------------------------------------------------------------------%
diff --git a/compiler/elds.m b/compiler/elds.m
index 4c84090bb..5248bd6d4 100644
--- a/compiler/elds.m
+++ b/compiler/elds.m
@@ -215,6 +215,12 @@
     --->    elds_char(char)
     ;       elds_int(int)
     ;       elds_uint(uint)
+    ;       elds_int8(int)    % XXX FIXED SIZE INT
+    ;       elds_uint8(int)
+    ;       elds_int16(int)
+    ;       elds_uint16(int)
+    ;       elds_int32(int)
+    ;       elds_uint32(int)
     ;       elds_float(float)
 
     ;       elds_binary(string)
diff --git a/compiler/elds_to_erlang.m b/compiler/elds_to_erlang.m
index d9abd1dd6..aea5e3552 100644
--- a/compiler/elds_to_erlang.m
+++ b/compiler/elds_to_erlang.m
@@ -782,6 +782,31 @@ output_term(ModuleInfo, VarSet, Indent, Term, !IO) :-
         io.write_uint(UInt, !IO),
         space(!IO)
     ;
+        % XXX FIXED SIZE INT
+        Term = elds_int8(Int8),
+        io.write_int(Int8, !IO),
+        space(!IO)
+    ;
+        Term = elds_uint8(UInt8),
+        io.write_int(UInt8, !IO),
+        space(!IO)
+    ;
+        Term = elds_int16(Int16),
+        io.write_int(Int16, !IO),
+        space(!IO)
+    ;
+        Term = elds_uint16(UInt16),
+        io.write_int(UInt16, !IO),
+        space(!IO)
+    ;
+        Term = elds_int32(Int32),
+        io.write_int(Int32, !IO),
+        space(!IO)
+    ;
+        Term = elds_uint32(UInt32),
+        io.write_int(UInt32, !IO),
+        space(!IO)
+    ;
         Term = elds_float(Float),
         output_float(Float, !IO),
         space(!IO)
diff --git a/compiler/erl_call_gen.m b/compiler/erl_call_gen.m
index 2efea9539..30e79a89d 100644
--- a/compiler/erl_call_gen.m
+++ b/compiler/erl_call_gen.m
@@ -447,6 +447,24 @@ erl_gen_simple_expr(ModuleInfo, VarTypes, SimpleExpr) = Expr :-
         SimpleExpr = uint_const(UInt),
         Expr = elds_term(elds_uint(UInt))
     ;
+        SimpleExpr = int8_const(Int8),
+        Expr = elds_term(elds_int8(Int8))
+    ;
+        SimpleExpr = uint8_const(UInt8),
+        Expr = elds_term(elds_uint8(UInt8))
+    ;
+        SimpleExpr = int16_const(Int16),
+        Expr = elds_term(elds_int16(Int16))
+    ;
+        SimpleExpr = uint16_const(UInt16),
+        Expr = elds_term(elds_uint16(UInt16))
+    ;
+        SimpleExpr = int32_const(Int32),
+        Expr = elds_term(elds_int32(Int32))
+    ;
+        SimpleExpr = uint32_const(UInt32),
+        Expr = elds_term(elds_uint32(UInt32))
+    ;
         SimpleExpr = float_const(Float),
         Expr = elds_term(elds_float(Float))
     ;
@@ -493,9 +511,8 @@ std_unop_to_elds(StdUnOp, EldsUnOp) :-
         ),
         fail
     ;
-        ( StdUnOp = bitwise_complement,      EldsUnOp = elds.bnot
-        ; StdUnOp = uint_bitwise_complement, EldsUnOp = elds.bnot
-        ; StdUnOp = logical_not,             EldsUnOp = elds.logical_not
+        ( StdUnOp = bitwise_complement(_), EldsUnOp = elds.bnot
+        ; StdUnOp = logical_not,           EldsUnOp = elds.logical_not
         )
     ).
 
@@ -515,20 +532,20 @@ std_binop_to_elds(StdBinOp, EldsBinOp) :-
         ),
         fail
     ;
-        ( StdBinOp = int_add,               EldsBinOp = elds.add
-        ; StdBinOp = int_sub,               EldsBinOp = elds.sub
-        ; StdBinOp = int_mul,               EldsBinOp = elds.mul
-        ; StdBinOp = int_div,               EldsBinOp = elds.int_div
-        ; StdBinOp = int_mod,               EldsBinOp = elds.(rem)
-        ; StdBinOp = unchecked_left_shift,  EldsBinOp = elds.bsl
-        ; StdBinOp = unchecked_right_shift, EldsBinOp = elds.bsr
-        ; StdBinOp = bitwise_and,           EldsBinOp = elds.band
-        ; StdBinOp = bitwise_or,            EldsBinOp = elds.bor
-        ; StdBinOp = bitwise_xor,           EldsBinOp = elds.bxor
+        ( StdBinOp = int_add(_),            EldsBinOp = elds.add
+        ; StdBinOp = int_sub(_),            EldsBinOp = elds.sub
+        ; StdBinOp = int_mul(_),            EldsBinOp = elds.mul
+        ; StdBinOp = int_div(_),            EldsBinOp = elds.int_div
+        ; StdBinOp = int_mod(_),            EldsBinOp = elds.(rem)
+        ; StdBinOp = unchecked_left_shift(_),  EldsBinOp = elds.bsl
+        ; StdBinOp = unchecked_right_shift(_), EldsBinOp = elds.bsr
+        ; StdBinOp = bitwise_and(_),        EldsBinOp = elds.band
+        ; StdBinOp = bitwise_or(_),         EldsBinOp = elds.bor
+        ; StdBinOp = bitwise_xor(_),        EldsBinOp = elds.bxor
         ; StdBinOp = logical_and,           EldsBinOp = elds.andalso
         ; StdBinOp = logical_or,            EldsBinOp = elds.orelse
-        ; StdBinOp = eq,                    EldsBinOp = elds.(=:=)
-        ; StdBinOp = ne,                    EldsBinOp = elds.(=/=)
+        ; StdBinOp = eq(_),                 EldsBinOp = elds.(=:=)
+        ; StdBinOp = ne(_),                 EldsBinOp = elds.(=/=)
         ; StdBinOp = offset_str_eq(_),      EldsBinOp = elds.(=:=)
         ; StdBinOp = str_eq,                EldsBinOp = elds.(=:=)
         ; StdBinOp = str_ne,                EldsBinOp = elds.(=/=)
@@ -536,10 +553,10 @@ std_binop_to_elds(StdBinOp, EldsBinOp) :-
         ; StdBinOp = str_gt,                EldsBinOp = elds.(>)
         ; StdBinOp = str_le,                EldsBinOp = elds.(=<)
         ; StdBinOp = str_ge,                EldsBinOp = elds.(>=)
-        ; StdBinOp = int_lt,                EldsBinOp = elds.(<)
-        ; StdBinOp = int_gt,                EldsBinOp = elds.(>)
-        ; StdBinOp = int_le,                EldsBinOp = elds.(=<)
-        ; StdBinOp = int_ge,                EldsBinOp = elds.(>=)
+        ; StdBinOp = int_lt(_),             EldsBinOp = elds.(<)
+        ; StdBinOp = int_gt(_),             EldsBinOp = elds.(>)
+        ; StdBinOp = int_le(_),             EldsBinOp = elds.(=<)
+        ; StdBinOp = int_ge(_),             EldsBinOp = elds.(>=)
         ; StdBinOp = float_plus,            EldsBinOp = elds.add
         ; StdBinOp = float_minus,           EldsBinOp = elds.sub
         ; StdBinOp = float_times,           EldsBinOp = elds.mul
@@ -552,22 +569,6 @@ std_binop_to_elds(StdBinOp, EldsBinOp) :-
         ; StdBinOp = float_ge,              EldsBinOp = elds.(>=)
         ; StdBinOp = compound_eq,           EldsBinOp = elds.(=:=)
         ; StdBinOp = compound_lt,           EldsBinOp = elds.(<)
-        ; StdBinOp = uint_eq,               EldsBinOp = elds.(=:=)
-        ; StdBinOp = uint_ne,               EldsBinOp = elds.(=/=)
-        ; StdBinOp = uint_lt,               EldsBinOp = elds.(<)
-        ; StdBinOp = uint_gt,               EldsBinOp = elds.(>)
-        ; StdBinOp = uint_le,               EldsBinOp = elds.(=<)
-        ; StdBinOp = uint_ge,               EldsBinOp = elds.(>=)
-        ; StdBinOp = uint_add,              EldsBinOp = elds.add
-        ; StdBinOp = uint_sub,              EldsBinOp = elds.sub
-        ; StdBinOp = uint_mul,              EldsBinOp = elds.mul
-        ; StdBinOp = uint_div,              EldsBinOp = elds.int_div
-        ; StdBinOp = uint_mod,              EldsBinOp = elds.(rem)
-        ; StdBinOp = uint_bitwise_and,      EldsBinOp = elds.band
-        ; StdBinOp = uint_bitwise_or,       EldsBinOp = elds.bor
-        ; StdBinOp = uint_bitwise_xor,      EldsBinOp = elds.bxor
-        ; StdBinOp = uint_unchecked_left_shift, EldsBinOp = elds.bsl
-        ; StdBinOp = uint_unchecked_right_shift, EldsBinOp = elds.bsr
         )
     ).
 
diff --git a/compiler/erl_code_util.m b/compiler/erl_code_util.m
index d26b5027c..fe896cfb8 100644
--- a/compiler/erl_code_util.m
+++ b/compiler/erl_code_util.m
@@ -514,6 +514,12 @@ non_variable_term(Term) :-
         ( Term = elds_char(_)
         ; Term = elds_int(_)
         ; Term = elds_uint(_)
+        ; Term = elds_int8(_)
+        ; Term = elds_uint8(_)
+        ; Term = elds_int16(_)
+        ; Term = elds_uint16(_)
+        ; Term = elds_int32(_)
+        ; Term = elds_uint32(_)
         ; Term = elds_float(_)
         ; Term = elds_binary(_)
         ; Term = elds_list_of_ints(_)
@@ -662,6 +668,12 @@ erl_rename_vars_in_term(Subn, Term0, Term) :-
     (
         ( Term0 = elds_int(_)
         ; Term0 = elds_uint(_)
+        ; Term0 = elds_int8(_)
+        ; Term0 = elds_uint8(_)
+        ; Term0 = elds_int16(_)
+        ; Term0 = elds_uint16(_)
+        ; Term0 = elds_int32(_)
+        ; Term0 = elds_uint32(_)
         ; Term0 = elds_float(_)
         ; Term0 = elds_binary(_)
         ; Term0 = elds_list_of_ints(_)
@@ -827,6 +839,12 @@ erl_vars_in_term(Term, !Set) :-
     (
         ( Term = elds_int(_)
         ; Term = elds_uint(_)
+        ; Term = elds_int8(_)
+        ; Term = elds_uint8(_)
+        ; Term = elds_int16(_)
+        ; Term = elds_uint16(_)
+        ; Term = elds_int32(_)
+        ; Term = elds_uint32(_)
         ; Term = elds_float(_)
         ; Term = elds_binary(_)
         ; Term = elds_list_of_ints(_)
@@ -966,6 +984,12 @@ erl_term_size(Term) = Size :-
     (
         ( Term = elds_int(_)
         ; Term = elds_uint(_)
+        ; Term = elds_int8(_)
+        ; Term = elds_uint8(_)
+        ; Term = elds_int16(_)
+        ; Term = elds_uint16(_)
+        ; Term = elds_int32(_)
+        ; Term = elds_uint32(_)
         ; Term = elds_float(_)
         ; Term = elds_binary(_)
         ; Term = elds_list_of_ints(_)
diff --git a/compiler/erl_rtti.m b/compiler/erl_rtti.m
index 3dac2c80e..7c5c788e8 100644
--- a/compiler/erl_rtti.m
+++ b/compiler/erl_rtti.m
@@ -610,6 +610,18 @@ erlang_type_ctor_rep(erlang_builtin(builtin_ctor_int)) =
     elds_term(make_enum_alternative("etcr_int")).
 erlang_type_ctor_rep(erlang_builtin(builtin_ctor_uint)) =
     elds_term(make_enum_alternative("etcr_uint")).
+erlang_type_ctor_rep(erlang_builtin(builtin_ctor_int8)) =
+    elds_term(make_enum_alternative("etcr_int8")).
+erlang_type_ctor_rep(erlang_builtin(builtin_ctor_uint8)) =
+    elds_term(make_enum_alternative("etcr_uint8")).
+erlang_type_ctor_rep(erlang_builtin(builtin_ctor_int16)) =
+    elds_term(make_enum_alternative("etcr_int16")).
+erlang_type_ctor_rep(erlang_builtin(builtin_ctor_uint16)) =
+    elds_term(make_enum_alternative("etcr_uint16")).
+erlang_type_ctor_rep(erlang_builtin(builtin_ctor_int32)) =
+    elds_term(make_enum_alternative("etcr_int32")).
+erlang_type_ctor_rep(erlang_builtin(builtin_ctor_uint32)) =
+    elds_term(make_enum_alternative("etcr_uint32")).
 erlang_type_ctor_rep(erlang_builtin(builtin_ctor_float)) =
     elds_term(make_enum_alternative("etcr_float")).
 erlang_type_ctor_rep(erlang_builtin(builtin_ctor_char)) =
diff --git a/compiler/erl_unify_gen.m b/compiler/erl_unify_gen.m
index ae0cdd0c5..56fc7a0e4 100644
--- a/compiler/erl_unify_gen.m
+++ b/compiler/erl_unify_gen.m
@@ -66,6 +66,12 @@
     ;       tuple_cons(ground)
     ;       int_const(ground)
     ;       uint_const(ground)
+    ;       int8_const(ground)
+    ;       uint8_const(ground)
+    ;       int16_const(ground)
+    ;       uint16_const(ground)
+    ;       int32_const(ground)
+    ;       uint32_const(ground)
     ;       float_const(ground)
     ;       char_const(ground)
     ;       string_const(ground).
@@ -282,6 +288,24 @@ cons_id_to_term(ConsId, Args, DummyVarReplacement, Term, !Info) :-
         ConsId = uint_const(UInt),
         Term = elds_uint(UInt)
     ;
+        ConsId = int8_const(Int8),
+        Term = elds_int8(Int8)
+    ;
+        ConsId = uint8_const(UInt8),
+        Term = elds_uint8(UInt8)
+    ;
+        ConsId = int16_const(Int16),
+        Term = elds_int16(Int16)
+    ;
+        ConsId = uint16_const(UInt16),
+        Term = elds_uint16(UInt16)
+    ;
+        ConsId = int32_const(Int32),
+        Term = elds_int32(Int32)
+    ;
+        ConsId = uint32_const(UInt32),
+        Term = elds_uint32(UInt32)
+    ;
         ConsId = float_const(Float),
         Term = elds_float(Float)
     ;
@@ -298,6 +322,12 @@ cons_id_to_expr(ConsId, Args, DummyVarReplacement, Expr, !Info) :-
         ; ConsId = tuple_cons(_)
         ; ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
diff --git a/compiler/export.m b/compiler/export.m
index 57e503004..88a4f10dc 100644
--- a/compiler/export.m
+++ b/compiler/export.m
@@ -653,9 +653,7 @@ convert_type_to_mercury(Rval, Type, TargetArgLoc, ConvertedRval) :-
             % is signed.
             ConvertedRval = "(MR_UnsignedChar) " ++ Rval
         ;
-            ( BuiltinType = builtin_type_int
-            ; BuiltinType = builtin_type_uint
-            ),
+            BuiltinType = builtin_type_int(_),
             ConvertedRval = Rval
         )
     ;
@@ -685,8 +683,7 @@ convert_type_from_mercury(SourceArgLoc, Rval, Type, ConvertedRval) :-
                 ConvertedRval = Rval
             )
         ;
-            ( BuiltinType = builtin_type_int
-            ; BuiltinType = builtin_type_uint
+            ( BuiltinType = builtin_type_int(_)
             ; BuiltinType = builtin_type_char
             ),
             ConvertedRval = Rval
@@ -960,6 +957,12 @@ foreign_const_name_and_tag(TypeCtor, Mapping, TagValues, Ctor,
     ;
         ( TagVal = string_tag(_)
         ; TagVal = uint_tag(_)
+        ; TagVal = int8_tag(_)
+        ; TagVal = uint8_tag(_)
+        ; TagVal = int16_tag(_)
+        ; TagVal = uint16_tag(_)
+        ; TagVal = int32_tag(_)
+        ; TagVal = uint32_tag(_)
         ; TagVal = float_tag(_)
         ; TagVal = closure_tag(_, _, _)
         ; TagVal = type_ctor_info_tag(_, _, _)
diff --git a/compiler/exprn_aux.m b/compiler/exprn_aux.m
index f0c860d9a..aeb766733 100644
--- a/compiler/exprn_aux.m
+++ b/compiler/exprn_aux.m
@@ -111,6 +111,12 @@ const_is_constant(Const, ExprnOpts, IsConst) :-
         ; Const = llconst_false
         ; Const = llconst_int(_)
         ; Const = llconst_uint(_)
+        ; Const = llconst_int8(_)
+        ; Const = llconst_uint8(_)
+        ; Const = llconst_int16(_)
+        ; Const = llconst_uint16(_)
+        ; Const = llconst_int32(_)
+        ; Const = llconst_uint32(_)
         ; Const = llconst_foreign(_, _)
         ; Const = llconst_string(_)
         ; Const = llconst_multi_string(_)
diff --git a/compiler/fact_table.m b/compiler/fact_table.m
index 3efbdab3d..8ede1691c 100644
--- a/compiler/fact_table.m
+++ b/compiler/fact_table.m
@@ -536,10 +536,10 @@ check_fact_type_and_mode(Types0, [Term | Terms], ArgNum0, PredOrFunc,
             Functor = term.integer(_, _, Signedness, _),
             (
                 Signedness = signed,
-                RequiredType = yes(builtin_type_int)
+                RequiredType = yes(builtin_type_int(int_type_int))
             ;
                 Signedness = unsigned,
-                RequiredType = yes(builtin_type_uint)
+                RequiredType = yes(builtin_type_int(int_type_uint))
             )
         ;
             Functor = term.float(_),
@@ -734,7 +734,7 @@ create_fact_table_struct([Info | Infos], I, Context, StructContents,
             Type = builtin_type(builtin_type_string),
             TypeStr = "MR_ConstString"
         ;
-            Type = builtin_type(builtin_type_int),
+            Type = builtin_type(builtin_type_int(int_type_int)),
             TypeStr = "MR_Integer"
         ;
             Type = builtin_type(builtin_type_float),
@@ -1941,7 +1941,7 @@ get_output_args_list([Info | Infos], ArgStrings0, Args) :-
 
 convert_key_string_to_arg(ArgString, Type, Arg) :-
     % XXX UINT - handle uints here too when we support them in fact tables.
-    ( if Type = builtin_type(builtin_type_int) then
+    ( if Type = builtin_type(builtin_type_int(int_type_int)) then
         ( if string.base_string_to_int(36, ArgString, I) then
             Arg = term.integer(base_10, integer(I), signed, size_word)
         else
@@ -2671,7 +2671,7 @@ generate_hash_code([pragma_var(_, Name, Mode, _) | PragmaVars], [Type | Types],
         FactTableSize, C_Code) :-
     NextArgNum = ArgNum + 1,
     ( if mode_is_fully_input(ModuleInfo, Mode) then
-        ( if Type = builtin_type(builtin_type_int) then
+        ( if Type = builtin_type(builtin_type_int(int_type_int)) then
             generate_hash_int_code(Name, LabelName, LabelNum,
                 PredName, PragmaVars, Types, ModuleInfo,
                 NextArgNum, FactTableSize, C_Code0)
diff --git a/compiler/foreign.m b/compiler/foreign.m
index 7ae239a5c..310f1fe54 100644
--- a/compiler/foreign.m
+++ b/compiler/foreign.m
@@ -294,11 +294,32 @@ exported_type_to_string(Lang, ExportedType) = Result :-
 
 exported_builtin_type_to_c_string(BuiltinType) = CTypeName :-
     (
-        BuiltinType = builtin_type_int,
-        CTypeName = "MR_Integer"
-    ;
-        BuiltinType = builtin_type_uint,
-        CTypeName = "MR_Unsigned"
+        BuiltinType = builtin_type_int(IntType),
+        (
+            IntType = int_type_int,
+            CTypeName = "MR_Integer"
+        ;
+            IntType = int_type_uint,
+            CTypeName = "MR_Unsigned"
+        ;
+            IntType = int_type_int8,
+            CTypeName = "int8_t"
+        ;
+            IntType = int_type_uint8,
+            CTypeName = "uint8_t"
+        ;
+            IntType = int_type_int16,
+            CTypeName = "int16_t"
+        ;
+            IntType = int_type_uint16,
+            CTypeName = "uint16_t"
+        ;
+            IntType = int_type_int32,
+            CTypeName = "int32_t"
+        ;
+            IntType = int_type_uint32,
+            CTypeName = "uint32_t"
+        )
     ;
         BuiltinType = builtin_type_float,
         CTypeName = "MR_Float"
@@ -312,11 +333,32 @@ exported_builtin_type_to_c_string(BuiltinType) = CTypeName :-
 
 exported_builtin_type_to_csharp_string(BuiltinType) = CsharpTypeName :-
     (
-        BuiltinType = builtin_type_int,
-        CsharpTypeName = "int"
-    ;
-        BuiltinType = builtin_type_uint,
-        CsharpTypeName = "uint"
+        BuiltinType = builtin_type_int(IntType),
+        (
+            IntType = int_type_int,
+            CsharpTypeName = "int"
+        ;
+            IntType = int_type_uint,
+            CsharpTypeName = "uint"
+        ;
+            IntType = int_type_int8,
+            CsharpTypeName = "sbyte"
+        ;
+            IntType = int_type_uint8,
+            CsharpTypeName = "byte"
+        ;
+            IntType = int_type_int16,
+            CsharpTypeName = "short"
+        ;
+            IntType = int_type_uint16,
+            CsharpTypeName = "ushort"
+        ;
+            IntType = int_type_int32,
+            CsharpTypeName = "int"
+        ;
+            IntType = int_type_uint32,
+            CsharpTypeName = "uint"
+        )
     ;
         BuiltinType = builtin_type_float,
         CsharpTypeName = "double"
@@ -330,11 +372,32 @@ exported_builtin_type_to_csharp_string(BuiltinType) = CsharpTypeName :-
 
 exported_builtin_type_to_java_string(BuiltinType) = JavaTypeName :-
     (
-        BuiltinType = builtin_type_int,
-        JavaTypeName = "int"
-    ;
-        BuiltinType = builtin_type_uint,
-        JavaTypeName = "int"
+        BuiltinType = builtin_type_int(IntType),
+        (
+            IntType = int_type_int,
+            JavaTypeName = "int"
+        ;
+            IntType = int_type_uint,
+            JavaTypeName = "int"
+        ;
+            IntType= int_type_int8,
+            JavaTypeName = "byte"
+        ;
+            IntType = int_type_uint8,
+            JavaTypeName = "byte"
+        ;
+            IntType = int_type_int16,
+            JavaTypeName = "short"
+        ;
+            IntType = int_type_uint16,
+            JavaTypeName = "short"
+        ;
+            IntType = int_type_int32,
+            JavaTypeName = "int"
+        ;
+            IntType = int_type_uint32,
+            JavaTypeName = "int"
+        )
     ;
         BuiltinType = builtin_type_float,
         JavaTypeName = "double"
diff --git a/compiler/global_data.m b/compiler/global_data.m
index 56149e627..8daa37c7b 100644
--- a/compiler/global_data.m
+++ b/compiler/global_data.m
@@ -372,7 +372,7 @@ add_scalar_static_cell(TypedArgs0, DataId, !Info) :-
     % so that the generated C structure isn't empty.
     (
         TypedArgs0 = [],
-        TypedArgs = [typed_rval(const(llconst_int(-1)), lt_integer)]
+        TypedArgs = [typed_rval(const(llconst_int(-1)), lt_int(int_type_int))]
     ;
         TypedArgs0 = [_ | _],
         TypedArgs = TypedArgs0
@@ -512,13 +512,13 @@ find_general_llds_types_in_cell(UnboxFloat, [_Type | Types], [Rval | Rvals],
     then
         LLDSType = LLDSType0
     else if
-        NaturalType = lt_integer,
+        NaturalType = lt_int(int_type_int),
         LLDSType0 = lt_data_ptr
     then
         LLDSType = lt_data_ptr
     else if
         NaturalType = lt_data_ptr,
-        LLDSType0 = lt_integer
+        LLDSType0 = lt_int(int_type_int)
     then
         LLDSType = lt_data_ptr
     else
@@ -1346,6 +1346,12 @@ remap_rval_const(Remap, Const0, Const) :-
         ; Const0 = llconst_false
         ; Const0 = llconst_int(_)
         ; Const0 = llconst_uint(_)
+        ; Const0 = llconst_int8(_)
+        ; Const0 = llconst_uint8(_)
+        ; Const0 = llconst_int16(_)
+        ; Const0 = llconst_uint16(_)
+        ; Const0 = llconst_int32(_)
+        ; Const0 = llconst_uint32(_)
         ; Const0 = llconst_foreign(_, _)
         ; Const0 = llconst_float(_)
         ; Const0 = llconst_string(_)
diff --git a/compiler/goal_util.m b/compiler/goal_util.m
index c32bba45a..1aa3e98ca 100644
--- a/compiler/goal_util.m
+++ b/compiler/goal_util.m
@@ -1194,6 +1194,12 @@ cons_id_proc_refs_acc(ConsId, !ReferredToProcs) :-
         ; ConsId = tuple_cons(_)
         ; ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
diff --git a/compiler/higher_order.m b/compiler/higher_order.m
index 9a1e9453d..e67a570ba 100644
--- a/compiler/higher_order.m
+++ b/compiler/higher_order.m
@@ -915,6 +915,12 @@ is_interesting_cons_id(Params, ConsId) = IsInteresting :-
         ( ConsId = cons(_, _, _)
         ; ConsId = tuple_cons(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
diff --git a/compiler/hlds_code_util.m b/compiler/hlds_code_util.m
index 2513145df..501830255 100644
--- a/compiler/hlds_code_util.m
+++ b/compiler/hlds_code_util.m
@@ -93,6 +93,24 @@ cons_id_to_tag(ModuleInfo, ConsId) = Tag:-
         ConsId = uint_const(UInt),
         Tag = uint_tag(UInt)
     ;
+        ConsId = int8_const(Int8),
+        Tag = int8_tag(Int8)
+    ;
+        ConsId = uint8_const(UInt8),
+        Tag = uint8_tag(UInt8)
+    ;
+        ConsId = int16_const(Int16),
+        Tag = int16_tag(Int16)
+    ;
+        ConsId = uint16_const(UInt16),
+        Tag = uint16_tag(UInt16)
+    ;
+        ConsId = int32_const(Int32),
+        Tag = int32_tag(Int32)
+    ;
+        ConsId = uint32_const(UInt32),
+        Tag = uint32_tag(UInt32)
+    ;
         ConsId = float_const(Float),
         Tag = float_tag(Float)
     ;
diff --git a/compiler/hlds_data.m b/compiler/hlds_data.m
index 08e7cd676..c54d0dbe8 100644
--- a/compiler/hlds_data.m
+++ b/compiler/hlds_data.m
@@ -599,6 +599,14 @@ cons_table_optimize(!ConsTable) :-
             % the specified unsigned integer value. This is used for uint
             % constants.
 
+            % XXX FIXED SIZE INT
+    ;       int8_tag(int)
+    ;       uint8_tag(int)
+    ;       int16_tag(int)
+    ;       uint16_tag(int)
+    ;       int32_tag(int)
+    ;       uint32_tag(int)
+
     ;       foreign_tag(foreign_language, string)
             % This means the constant is represented by the string which is
             % embedded directly in the target language. This is used for
@@ -782,6 +790,12 @@ get_primary_tag(Tag) = MaybePrimaryTag :-
         % But it's safe to be conservative...
         ( Tag = int_tag(_)
         ; Tag = uint_tag(_)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = float_tag(_)
         ; Tag = string_tag(_)
         ; Tag = foreign_tag(_, _)
@@ -819,6 +833,12 @@ get_secondary_tag(Tag) = MaybeSecondaryTag :-
     (
         ( Tag = int_tag(_)
         ; Tag = uint_tag(_)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = float_tag(_)
         ; Tag = string_tag(_)
         ; Tag = foreign_tag(_, _)
diff --git a/compiler/hlds_dependency_graph.m b/compiler/hlds_dependency_graph.m
index 4e491902f..8a7eb3f82 100644
--- a/compiler/hlds_dependency_graph.m
+++ b/compiler/hlds_dependency_graph.m
@@ -462,6 +462,12 @@ add_dependency_arcs_in_cons(DepGraph, WhatEdges, Caller, ConsId, !DepArcs) :-
         ; ConsId = tuple_cons(_)
         ; ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
diff --git a/compiler/hlds_out_pred.m b/compiler/hlds_out_pred.m
index b500993b0..80ec7ebfa 100644
--- a/compiler/hlds_out_pred.m
+++ b/compiler/hlds_out_pred.m
@@ -1218,12 +1218,30 @@ write_space_and_table_trie_step(TVarSet, StepDesc, !IO) :-
 
 table_trie_step_desc(TVarSet, Step) = Str :-
     (
-        Step = table_trie_step_int,
+        Step = table_trie_step_int(int_type_int),
         Str = "int"
     ;
-        Step = table_trie_step_uint,
+        Step = table_trie_step_int(int_type_uint),
         Str = "uint"
     ;
+        Step = table_trie_step_int(int_type_int8),
+        Str = "int8"
+    ;
+        Step = table_trie_step_int(int_type_uint8),
+        Str = "uint8"
+    ;
+        Step = table_trie_step_int(int_type_int16),
+        Str = "int16"
+    ;
+        Step = table_trie_step_int(int_type_uint16),
+        Str = "uint16"
+    ;
+        Step = table_trie_step_int(int_type_int32),
+        Str = "int32"
+    ;
+        Step = table_trie_step_int(int_type_uint32),
+        Str = "uint32"
+    ;
         Step = table_trie_step_char,
         Str = "char"
     ;
diff --git a/compiler/hlds_out_util.m b/compiler/hlds_out_util.m
index 69acf9d8a..0f303fd64 100644
--- a/compiler/hlds_out_util.m
+++ b/compiler/hlds_out_util.m
@@ -679,6 +679,36 @@ functor_cons_id_to_string(ModuleInfo, VarSet, VarNamePrint, ConsId, ArgVars)
             term.integer(base_10, integer.from_uint(UInt), unsigned, size_word),
             ArgVars)
     ;
+        ConsId = int8_const(Int8),
+        Str = functor_to_string(VarSet, VarNamePrint,
+            term.integer(base_10, integer(Int8), signed, size_8_bit),
+            ArgVars)
+    ;
+        ConsId = uint8_const(UInt8),
+        Str = functor_to_string(VarSet, VarNamePrint,
+            term.integer(base_10, integer(UInt8), unsigned, size_8_bit),
+            ArgVars)
+    ;
+        ConsId = int16_const(Int16),
+        Str = functor_to_string(VarSet, VarNamePrint,
+            term.integer(base_10, integer(Int16), signed, size_16_bit),
+            ArgVars)
+    ;
+        ConsId = uint16_const(UInt16),
+        Str = functor_to_string(VarSet, VarNamePrint,
+            term.integer(base_10, integer(UInt16), unsigned, size_16_bit),
+            ArgVars)
+    ;
+        ConsId = int32_const(Int32),
+        Str = functor_to_string(VarSet, VarNamePrint,
+            term.integer(base_10, integer(Int32), signed, size_32_bit),
+            ArgVars)
+    ;
+        ConsId = uint32_const(UInt32),
+        Str = functor_to_string(VarSet, VarNamePrint,
+            term.integer(base_10, integer(UInt32), unsigned, size_32_bit),
+            ArgVars)
+    ;
         ConsId = float_const(Float),
         Str = functor_to_string(VarSet, VarNamePrint,
             term.float(Float), ArgVars)
@@ -836,6 +866,24 @@ cons_id_and_vars_or_arity_to_string(VarSet, Qual, ConsId, MaybeArgVars)
         ConsId = uint_const(UInt),
         String = uint_to_string(UInt) ++ "u"
     ;
+        ConsId = int8_const(Int8),
+        string.int_to_string(Int8, String)
+    ;
+        ConsId = uint8_const(UInt8),
+        string.int_to_string(UInt8, String)
+    ;
+        ConsId = int16_const(Int16),
+        string.int_to_string(Int16, String)
+    ;
+        ConsId = uint16_const(UInt16),
+        string.int_to_string(UInt16, String)
+    ;
+        ConsId = int32_const(Int32),
+        string.int_to_string(Int32, String)
+    ;
+        ConsId = uint32_const(UInt32),
+        string.int_to_string(UInt32, String)
+    ;
         ConsId = float_const(Float),
         String = float_to_string(Float)
     ;
diff --git a/compiler/hlds_pred.m b/compiler/hlds_pred.m
index bc48ce39c..92f661bb9 100644
--- a/compiler/hlds_pred.m
+++ b/compiler/hlds_pred.m
@@ -2028,8 +2028,7 @@ attribute_list_to_attributes(Attributes, AttributeSet) :-
     %
 :- type table_trie_step
     --->    table_trie_step_dummy
-    ;       table_trie_step_int
-    ;       table_trie_step_uint
+    ;       table_trie_step_int(int_type)
     ;       table_trie_step_char
     ;       table_trie_step_string
     ;       table_trie_step_float
@@ -2879,8 +2878,7 @@ structure_reuse_info_init = structure_reuse_info(no, no).
 
 table_step_stats_kind(Step) = KindStr :-
     (
-        ( Step = table_trie_step_int
-        ; Step = table_trie_step_uint
+        ( Step = table_trie_step_int(_)
         ; Step = table_trie_step_char
         ; Step = table_trie_step_string
         ; Step = table_trie_step_float
diff --git a/compiler/implementation_defined_literals.m b/compiler/implementation_defined_literals.m
index e13e7a255..3d1ffd290 100644
--- a/compiler/implementation_defined_literals.m
+++ b/compiler/implementation_defined_literals.m
@@ -104,6 +104,12 @@ subst_literals_in_goal(Info, Goal0, Goal) :-
                 ; ConsId = closure_cons(_, _)
                 ; ConsId = int_const(_)
                 ; ConsId = uint_const(_)
+                ; ConsId = int8_const(_)
+                ; ConsId = uint8_const(_)
+                ; ConsId = int16_const(_)
+                ; ConsId = uint16_const(_)
+                ; ConsId = int32_const(_)
+                ; ConsId = uint32_const(_)
                 ; ConsId = float_const(_)
                 ; ConsId = char_const(_)
                 ; ConsId = string_const(_)
diff --git a/compiler/inst_check.m b/compiler/inst_check.m
index 0f98d574c..710c54b62 100644
--- a/compiler/inst_check.m
+++ b/compiler/inst_check.m
@@ -240,29 +240,55 @@ check_inst_defn_has_matching_type(TypeTable, FunctorsToTypesMap, InstId,
                 ForTypeCtor0 = type_ctor(ForTypeCtorName, ForTypeCtorArity),
                 % We bind ForTypeCtor to a standardized form of ForTypeCtor0.
                 ( if
-                    ( ForTypeCtorName = unqualified("int")
-                    ; ForTypeCtorName = qualified(unqualified(""), "int")
-                    ; ForTypeCtorName = qualified(unqualified("int"), "int")
-                    ),
+                    sym_name_for_builtin_type(ForTypeCtorName, "int"),
                     ForTypeCtorArity = 0
                 then
                     ForTypeCtor = int_type_ctor,
-                    MaybeForTypeKind = yes(ftk_int)
+                    MaybeForTypeKind = yes(ftk_int(int_type_int))
                 else if
-                    ( ForTypeCtorName = unqualified("uint")
-                    ; ForTypeCtorName = qualified(unqualified(""), "uint")
-                    ; ForTypeCtorName = qualified(unqualified("uint"), "uint")
-                    ),
+                    sym_name_for_builtin_type(ForTypeCtorName, "uint"),
                     ForTypeCtorArity = 0
                 then
                     ForTypeCtor = uint_type_ctor,
-                    MaybeForTypeKind = yes(ftk_uint)
+                    MaybeForTypeKind = yes(ftk_int(int_type_uint))
                 else if
-                    ( ForTypeCtorName = unqualified("float")
-                    ; ForTypeCtorName = qualified(unqualified(""), "float")
-                    ; ForTypeCtorName = qualified(unqualified("float"),
-                        "float")
-                    ),
+                    sym_name_for_builtin_type(ForTypeCtorName, "int8"),
+                    ForTypeCtorArity = 0
+                then
+                    ForTypeCtor = int8_type_ctor,
+                    MaybeForTypeKind = yes(ftk_int(int_type_int8))
+                else if
+                    sym_name_for_builtin_type(ForTypeCtorName, "uint8"),
+                    ForTypeCtorArity = 0
+                then
+                    ForTypeCtor = uint8_type_ctor,
+                    MaybeForTypeKind = yes(ftk_int(int_type_uint8))
+                else if
+                    sym_name_for_builtin_type(ForTypeCtorName, "int16"),
+                    ForTypeCtorArity = 0
+                then
+                    ForTypeCtor = int16_type_ctor,
+                    MaybeForTypeKind = yes(ftk_int(int_type_int16))
+                else if
+                    sym_name_for_builtin_type(ForTypeCtorName, "uint16"),
+                    ForTypeCtorArity = 0
+                then
+                    ForTypeCtor = uint16_type_ctor,
+                    MaybeForTypeKind = yes(ftk_int(int_type_uint16))
+                else if
+                    sym_name_for_builtin_type(ForTypeCtorName, "int32"),
+                    ForTypeCtorArity = 0
+                then
+                    ForTypeCtor = int32_type_ctor,
+                    MaybeForTypeKind = yes(ftk_int(int_type_int32))
+                else if
+                    sym_name_for_builtin_type(ForTypeCtorName, "uint32"),
+                    ForTypeCtorArity = 0
+                then
+                    ForTypeCtor = uint32_type_ctor,
+                    MaybeForTypeKind = yes(ftk_int(int_type_uint32))
+                else if
+                    sym_name_for_builtin_type(ForTypeCtorName, "float"),
                     ForTypeCtorArity = 0
                 then
                     ForTypeCtor = float_type_ctor,
@@ -280,11 +306,7 @@ check_inst_defn_has_matching_type(TypeTable, FunctorsToTypesMap, InstId,
                     ForTypeCtor = char_type_ctor,
                     MaybeForTypeKind = yes(ftk_char)
                 else if
-                    ( ForTypeCtorName = unqualified("string")
-                    ; ForTypeCtorName = qualified(unqualified(""), "string")
-                    ; ForTypeCtorName = qualified(unqualified("string"),
-                        "string")
-                    ),
+                    sym_name_for_builtin_type(ForTypeCtorName, "string"),
                     ForTypeCtorArity = 0
                 then
                     ForTypeCtor = string_type_ctor,
@@ -374,6 +396,14 @@ check_inst_defn_has_matching_type(TypeTable, FunctorsToTypesMap, InstId,
         InstDefn = InstDefn0
     ).
 
+:- pred sym_name_for_builtin_type(sym_name::in, string::in) is semidet.
+
+sym_name_for_builtin_type(SymName, TypeName) :-
+    ( SymName = unqualified(TypeName)
+    ; SymName = qualified(unqualified(""), TypeName)
+    ; SymName = qualified(unqualified(TypeName), TypeName)
+    ).
+
 :- pred type_defn_or_builtin_to_type_ctor(type_defn_or_builtin::in,
     type_ctor::out) is det.
 
@@ -383,12 +413,30 @@ type_defn_or_builtin_to_type_ctor(TypeDefnOrBuiltin, TypeCtor) :-
     ;
         TypeDefnOrBuiltin = type_builtin(BuiltinType),
         (
-            BuiltinType = builtin_type_int,
+            BuiltinType = builtin_type_int(int_type_int),
             TypeCtor = type_ctor(unqualified("int"), 0)
         ;
-            BuiltinType = builtin_type_uint,
+            BuiltinType = builtin_type_int(int_type_uint),
             TypeCtor = type_ctor(unqualified("uint"), 0)
         ;
+            BuiltinType = builtin_type_int(int_type_int8),
+            TypeCtor = type_ctor(unqualified("int8"), 0)
+        ;
+            BuiltinType = builtin_type_int(int_type_uint8),
+            TypeCtor = type_ctor(unqualified("uint8"), 0)
+        ;
+            BuiltinType = builtin_type_int(int_type_int16),
+            TypeCtor = type_ctor(unqualified("int16"), 0)
+        ;
+            BuiltinType = builtin_type_int(int_type_uint16),
+            TypeCtor = type_ctor(unqualified("uint16"), 0)
+        ;
+            BuiltinType = builtin_type_int(int_type_int32),
+            TypeCtor = type_ctor(unqualified("int32"), 0)
+        ;
+            BuiltinType = builtin_type_int(int_type_uint32),
+            TypeCtor = type_ctor(unqualified("uint32"), 0)
+        ;
             BuiltinType = builtin_type_float,
             TypeCtor = type_ctor(unqualified("float"), 0)
         ;
@@ -407,8 +455,7 @@ type_defn_or_builtin_to_type_ctor(TypeDefnOrBuiltin, TypeCtor) :-
 
 :- type for_type_kind
     --->    ftk_user(type_ctor, hlds_type_defn)
-    ;       ftk_int
-    ;       ftk_uint
+    ;       ftk_int(int_type)
     ;       ftk_float
     ;       ftk_char
     ;       ftk_string.
@@ -485,8 +532,14 @@ check_for_type_bound_insts(ForTypeKind, [BoundInst | BoundInsts],
                 !:RevMismatchConsIdStrs = [ConsIdStr | !.RevMismatchConsIdStrs]
             )
         ;
-            ( ForTypeKind = ftk_int
-            ; ForTypeKind = ftk_uint
+            ( ForTypeKind = ftk_int(int_type_int)
+            ; ForTypeKind = ftk_int(int_type_uint)
+            ; ForTypeKind = ftk_int(int_type_int8)
+            ; ForTypeKind = ftk_int(int_type_uint8)
+            ; ForTypeKind = ftk_int(int_type_int16)
+            ; ForTypeKind = ftk_int(int_type_uint16)
+            ; ForTypeKind = ftk_int(int_type_int32)
+            ; ForTypeKind = ftk_int(int_type_uint32)
             ; ForTypeKind = ftk_float
             ; ForTypeKind = ftk_string
             ),
@@ -495,10 +548,16 @@ check_for_type_bound_insts(ForTypeKind, [BoundInst | BoundInsts],
     ;
         ConsId = int_const(_),
         (
-            ForTypeKind = ftk_int
+            ForTypeKind = ftk_int(int_type_int)
         ;
             ( ForTypeKind = ftk_user(_, _)
-            ; ForTypeKind = ftk_uint
+            ; ForTypeKind = ftk_int(int_type_uint)
+            ; ForTypeKind = ftk_int(int_type_int8)
+            ; ForTypeKind = ftk_int(int_type_uint8)
+            ; ForTypeKind = ftk_int(int_type_int16)
+            ; ForTypeKind = ftk_int(int_type_uint16)
+            ; ForTypeKind = ftk_int(int_type_int32)
+            ; ForTypeKind = ftk_int(int_type_uint32)
             ; ForTypeKind = ftk_float
             ; ForTypeKind = ftk_char
             ; ForTypeKind = ftk_string
@@ -508,10 +567,130 @@ check_for_type_bound_insts(ForTypeKind, [BoundInst | BoundInsts],
     ;
         ConsId = uint_const(_),
         (
-            ForTypeKind = ftk_uint
+            ForTypeKind = ftk_int(int_type_uint)
         ;
             ( ForTypeKind = ftk_user(_, _)
-            ; ForTypeKind = ftk_int
+            ; ForTypeKind = ftk_int(int_type_int)
+            ; ForTypeKind = ftk_int(int_type_int8)
+            ; ForTypeKind = ftk_int(int_type_uint8)
+            ; ForTypeKind = ftk_int(int_type_int16)
+            ; ForTypeKind = ftk_int(int_type_uint16)
+            ; ForTypeKind = ftk_int(int_type_int32)
+            ; ForTypeKind = ftk_int(int_type_uint32)
+            ; ForTypeKind = ftk_float
+            ; ForTypeKind = ftk_char
+            ; ForTypeKind = ftk_string
+            ),
+            !:RevMismatchConsIdStrs = [ConsIdStr | !.RevMismatchConsIdStrs]
+        )
+    ;
+        ConsId = int8_const(_),
+        (
+            ForTypeKind = ftk_int(int_type_int8)
+        ;
+            ( ForTypeKind = ftk_user(_, _)
+            ; ForTypeKind = ftk_int(int_type_int)
+            ; ForTypeKind = ftk_int(int_type_uint)
+            ; ForTypeKind = ftk_int(int_type_uint8)
+            ; ForTypeKind = ftk_int(int_type_int16)
+            ; ForTypeKind = ftk_int(int_type_uint16)
+            ; ForTypeKind = ftk_int(int_type_int32)
+            ; ForTypeKind = ftk_int(int_type_uint32)
+            ; ForTypeKind = ftk_float
+            ; ForTypeKind = ftk_char
+            ; ForTypeKind = ftk_string
+            ),
+            !:RevMismatchConsIdStrs = [ConsIdStr | !.RevMismatchConsIdStrs]
+        )
+    ;
+        ConsId = uint8_const(_),
+        (
+            ForTypeKind = ftk_int(int_type_uint8)
+        ;
+            ( ForTypeKind = ftk_user(_, _)
+            ; ForTypeKind = ftk_int(int_type_int)
+            ; ForTypeKind = ftk_int(int_type_uint)
+            ; ForTypeKind = ftk_int(int_type_int8)
+            ; ForTypeKind = ftk_int(int_type_int16)
+            ; ForTypeKind = ftk_int(int_type_uint16)
+            ; ForTypeKind = ftk_int(int_type_int32)
+            ; ForTypeKind = ftk_int(int_type_uint32)
+            ; ForTypeKind = ftk_float
+            ; ForTypeKind = ftk_char
+            ; ForTypeKind = ftk_string
+            ),
+            !:RevMismatchConsIdStrs = [ConsIdStr | !.RevMismatchConsIdStrs]
+        )
+    ;
+        ConsId = int16_const(_),
+        (
+            ForTypeKind = ftk_int(int_type_int16)
+        ;
+            ( ForTypeKind = ftk_user(_, _)
+            ; ForTypeKind = ftk_int(int_type_int)
+            ; ForTypeKind = ftk_int(int_type_uint)
+            ; ForTypeKind = ftk_int(int_type_int8)
+            ; ForTypeKind = ftk_int(int_type_uint8)
+            ; ForTypeKind = ftk_int(int_type_uint16)
+            ; ForTypeKind = ftk_int(int_type_int32)
+            ; ForTypeKind = ftk_int(int_type_uint32)
+            ; ForTypeKind = ftk_float
+            ; ForTypeKind = ftk_char
+            ; ForTypeKind = ftk_string
+            ),
+            !:RevMismatchConsIdStrs = [ConsIdStr | !.RevMismatchConsIdStrs]
+        )
+    ;
+        ConsId = uint16_const(_),
+        (
+            ForTypeKind = ftk_int(int_type_uint16)
+        ;
+            ( ForTypeKind = ftk_user(_, _)
+            ; ForTypeKind = ftk_int(int_type_int)
+            ; ForTypeKind = ftk_int(int_type_uint)
+            ; ForTypeKind = ftk_int(int_type_int8)
+            ; ForTypeKind = ftk_int(int_type_uint8)
+            ; ForTypeKind = ftk_int(int_type_int16)
+            ; ForTypeKind = ftk_int(int_type_int32)
+            ; ForTypeKind = ftk_int(int_type_uint32)
+            ; ForTypeKind = ftk_float
+            ; ForTypeKind = ftk_char
+            ; ForTypeKind = ftk_string
+            ),
+            !:RevMismatchConsIdStrs = [ConsIdStr | !.RevMismatchConsIdStrs]
+        )
+    ;
+        ConsId = int32_const(_),
+        (
+            ForTypeKind = ftk_int(int_type_int32)
+        ;
+            ( ForTypeKind = ftk_user(_, _)
+            ; ForTypeKind = ftk_int(int_type_int)
+            ; ForTypeKind = ftk_int(int_type_uint)
+            ; ForTypeKind = ftk_int(int_type_int8)
+            ; ForTypeKind = ftk_int(int_type_uint8)
+            ; ForTypeKind = ftk_int(int_type_int16)
+            ; ForTypeKind = ftk_int(int_type_uint16)
+            ; ForTypeKind = ftk_int(int_type_uint32)
+            ; ForTypeKind = ftk_float
+            ; ForTypeKind = ftk_char
+            ; ForTypeKind = ftk_string
+            ),
+            !:RevMismatchConsIdStrs = [ConsIdStr | !.RevMismatchConsIdStrs]
+        )
+    ;
+        ConsId = uint32_const(_),
+        (
+            ForTypeKind = ftk_int(int_type_uint32)
+        ;
+            ( ForTypeKind = ftk_user(_, _)
+            ; ForTypeKind = ftk_int(int_type_int)
+            ; ForTypeKind = ftk_int(int_type_uint)
+            ; ForTypeKind = ftk_int(int_type_int8)
+            ; ForTypeKind = ftk_int(int_type_uint8)
+            ; ForTypeKind = ftk_int(int_type_int16)
+            ; ForTypeKind = ftk_int(int_type_uint16)
+            ; ForTypeKind = ftk_int(int_type_int32)
             ; ForTypeKind = ftk_float
             ; ForTypeKind = ftk_char
             ; ForTypeKind = ftk_string
@@ -524,8 +703,7 @@ check_for_type_bound_insts(ForTypeKind, [BoundInst | BoundInsts],
             ForTypeKind = ftk_float
         ;
             ( ForTypeKind = ftk_user(_, _)
-            ; ForTypeKind = ftk_int
-            ; ForTypeKind = ftk_uint
+            ; ForTypeKind = ftk_int(_)
             ; ForTypeKind = ftk_char
             ; ForTypeKind = ftk_string
             ),
@@ -537,8 +715,7 @@ check_for_type_bound_insts(ForTypeKind, [BoundInst | BoundInsts],
             ForTypeKind = ftk_char
         ;
             ( ForTypeKind = ftk_user(_, _)
-            ; ForTypeKind = ftk_int
-            ; ForTypeKind = ftk_uint
+            ; ForTypeKind = ftk_int(_)
             ; ForTypeKind = ftk_float
             ; ForTypeKind = ftk_string
             ),
@@ -550,8 +727,7 @@ check_for_type_bound_insts(ForTypeKind, [BoundInst | BoundInsts],
             ForTypeKind = ftk_string
         ;
             ( ForTypeKind = ftk_user(_, _)
-            ; ForTypeKind = ftk_int
-            ; ForTypeKind = ftk_uint
+            ; ForTypeKind = ftk_int(_)
             ; ForTypeKind = ftk_float
             ; ForTypeKind = ftk_char
             ),
@@ -650,11 +826,32 @@ get_possible_types_for_bound_inst(FunctorsToTypesMap, BoundInst, MaybeTypes) :-
         ConsId = tuple_cons(Arity),
         MaybeTypes = yes([type_tuple(Arity)])
     ;
-        ConsId = int_const(_),
-        MaybeTypes = yes([type_builtin(builtin_type_int)])
-    ;
-        ConsId = uint_const(_),
-        MaybeTypes = yes([type_builtin(builtin_type_uint)])
+        (
+            ConsId = int_const(_),
+            IntType = int_type_int
+        ;
+            ConsId = uint_const(_),
+            IntType = int_type_uint
+        ;
+            ConsId = int8_const(_),
+            IntType = int_type_int8
+        ;
+            ConsId = uint8_const(_),
+            IntType = int_type_uint8
+        ;
+            ConsId = int16_const(_),
+            IntType = int_type_int16
+        ;
+            ConsId = uint16_const(_),
+            IntType = int_type_uint16
+        ;
+            ConsId = int32_const(_),
+            IntType = int_type_int32
+        ;
+            ConsId = uint32_const(_),
+            IntType = int_type_uint32
+        ),
+        MaybeTypes = yes([type_builtin(builtin_type_int(IntType))])
     ;
         ConsId = float_const(_),
         MaybeTypes = yes([type_builtin(builtin_type_float)])
@@ -754,12 +951,30 @@ maybe_issue_type_match_error(InstId, InstDefn, ForTypeKind, MismatchConsIdStrs,
     InstDefinedInThisModule = inst_status_defined_in_this_module(InstStatus),
     (
         (
-            ForTypeKind = ftk_int,
+            ForTypeKind = ftk_int(int_type_int),
             ForTypeCtor = int_type_ctor
         ;
-            ForTypeKind = ftk_uint,
+            ForTypeKind = ftk_int(int_type_uint),
             ForTypeCtor = uint_type_ctor
         ;
+            ForTypeKind = ftk_int(int_type_int8),
+            ForTypeCtor = int8_type_ctor
+        ;
+            ForTypeKind = ftk_int(int_type_uint8),
+            ForTypeCtor = uint8_type_ctor
+        ;
+            ForTypeKind = ftk_int(int_type_int16),
+            ForTypeCtor = int16_type_ctor
+        ;
+            ForTypeKind = ftk_int(int_type_uint16),
+            ForTypeCtor = uint16_type_ctor
+        ;
+            ForTypeKind = ftk_int(int_type_int32),
+            ForTypeCtor = int32_type_ctor
+        ;
+            ForTypeKind = ftk_int(int_type_uint32),
+            ForTypeCtor = uint32_type_ctor
+        ;
             ForTypeKind = ftk_float,
             ForTypeCtor = float_type_ctor
         ;
@@ -1052,20 +1267,62 @@ find_mismatches_from_builtin(ExpectedBuiltinType, CurNum,
         [BoundInst | BoundInsts], !NumMismatches, !PiecesCord) :-
     BoundInst = bound_functor(ConsId, _SubInsts),
     (
-        ExpectedBuiltinType = builtin_type_int,
+        ExpectedBuiltinType = builtin_type_int(int_type_int),
         ( if ConsId = int_const(_) then
             true
         else
             record_mismatch(CurNum, BoundInst, !NumMismatches, !PiecesCord)
         )
     ;
-        ExpectedBuiltinType = builtin_type_uint,
+        ExpectedBuiltinType = builtin_type_int(int_type_uint),
         ( if ConsId = uint_const(_) then
             true
         else
             record_mismatch(CurNum, BoundInst, !NumMismatches, !PiecesCord)
         )
     ;
+        ExpectedBuiltinType = builtin_type_int(int_type_int8),
+        ( if ConsId = int8_const(_) then
+            true
+        else
+            record_mismatch(CurNum, BoundInst, !NumMismatches, !PiecesCord)
+        )
+    ;
+        ExpectedBuiltinType = builtin_type_int(int_type_uint8),
+        ( if ConsId = uint8_const(_) then
+            true
+        else
+            record_mismatch(CurNum, BoundInst, !NumMismatches, !PiecesCord)
+        )
+    ;
+        ExpectedBuiltinType = builtin_type_int(int_type_int16),
+        ( if ConsId = int16_const(_) then
+            true
+        else
+            record_mismatch(CurNum, BoundInst, !NumMismatches, !PiecesCord)
+        )
+    ;
+        ExpectedBuiltinType = builtin_type_int(int_type_uint16),
+        ( if ConsId = uint16_const(_) then
+            true
+        else
+            record_mismatch(CurNum, BoundInst, !NumMismatches, !PiecesCord)
+        )
+    ;
+        ExpectedBuiltinType = builtin_type_int(int_type_int32),
+        ( if ConsId = int32_const(_) then
+            true
+        else
+            record_mismatch(CurNum, BoundInst, !NumMismatches, !PiecesCord)
+        )
+    ;
+        ExpectedBuiltinType = builtin_type_int(int_type_uint32),
+        ( if ConsId = uint32_const(_) then
+            true
+        else
+            record_mismatch(CurNum, BoundInst, !NumMismatches, !PiecesCord)
+        )
+    ;
         ExpectedBuiltinType = builtin_type_float,
         ( if ConsId = float_const(_) then
             true
@@ -1221,12 +1478,30 @@ type_defn_or_builtin_to_string(TypeDefnOrBuiltin) = Str :-
     ;
         TypeDefnOrBuiltin = type_builtin(BuiltinType),
         (
-            BuiltinType = builtin_type_int,
+            BuiltinType = builtin_type_int(int_type_int),
             Str = "int"
         ;
-            BuiltinType = builtin_type_uint,
+            BuiltinType = builtin_type_int(int_type_uint),
             Str = "uint"
         ;
+            BuiltinType = builtin_type_int(int_type_int8),
+            Str = "int8"
+        ;
+            BuiltinType = builtin_type_int(int_type_uint8),
+            Str = "uint8"
+        ;
+            BuiltinType = builtin_type_int(int_type_int16),
+            Str = "int16"
+        ;
+            BuiltinType = builtin_type_int(int_type_uint16),
+            Str = "uint16"
+        ;
+            BuiltinType = builtin_type_int(int_type_int32),
+            Str = "int32"
+        ;
+            BuiltinType = builtin_type_int(int_type_uint32),
+            Str = "uint32"
+        ;
             BuiltinType = builtin_type_float,
             Str = "float"
         ;
diff --git a/compiler/ite_gen.m b/compiler/ite_gen.m
index 84c933cd3..e85487eca 100644
--- a/compiler/ite_gen.m
+++ b/compiler/ite_gen.m
@@ -328,8 +328,10 @@ generate_negation(CodeModel, Goal0, NotGoalInfo, Code, !CI, !CLD) :-
             Op = str_eq
         else if Type = builtin_type(builtin_type_float) then
             Op = float_eq
+        else if Type = builtin_type(builtin_type_int(IntType)) then
+            Op = eq(IntType)
         else
-            Op = eq
+            Op = eq(int_type_int)
         ),
         TestCode = singleton(
             llds_instr(if_val(binop(Op, ValL, ValR), CodeAddr),
diff --git a/compiler/jumpopt.m b/compiler/jumpopt.m
index cdc64b06b..1fcc9e106 100644
--- a/compiler/jumpopt.m
+++ b/compiler/jumpopt.m
@@ -67,6 +67,7 @@
 :- import_module hlds.hlds_llds.
 :- import_module ll_backend.code_util.
 :- import_module ll_backend.opt_util.
+:- import_module parse_tree.prog_data.
 :- import_module parse_tree.prog_data_foreign.
 
 :- import_module map.
@@ -571,7 +572,8 @@ jump_opt_llcall(Uinstr0, Comment0, Instrs0, PrevInstr, JumpOptInfo,
             counter.allocate(LabelNum, LabelNumCounter0, LabelNumCounter1),
             NewLabel = internal_label(LabelNum, ProcLabel),
             NewInstrs = [
-                llds_instr(if_val(binop(ne, lval(curfr), lval(maxfr)),
+                llds_instr(if_val(binop(
+                    ne(int_type_int), lval(curfr), lval(maxfr)),
                     code_label(NewLabel)),
                     "branch around if cannot tail call"),
                 llds_instr(assign(maxfr, lval(prevfr_slot(lval(curfr)))),
@@ -1016,7 +1018,7 @@ needs_workaround(Lval, Cond) :-
         Cond = unop(logical_not, lval(Lval))
     ;
         Cond = binop(Op, Left, Right),
-        ( Op = eq ; Op = ne ),
+        ( Op = eq(_) ; Op = ne(_) ),
         (
             Right = lval(Lval),
             ( Left = const(llconst_int(0))
@@ -1157,6 +1159,12 @@ short_circuit_labels_const(InstrMap, RvalConst0, RvalConst) :-
         ; RvalConst0 = llconst_false
         ; RvalConst0 = llconst_int(_I)
         ; RvalConst0 = llconst_uint(_U)
+        ; RvalConst0 = llconst_int8(_I8)
+        ; RvalConst0 = llconst_uint8(_U8)
+        ; RvalConst0 = llconst_int16(_I16)
+        ; RvalConst0 = llconst_uint16(_U16)
+        ; RvalConst0 = llconst_int32(_I32)
+        ; RvalConst0 = llconst_uint32(_U32)
         ; RvalConst0 = llconst_foreign(_V, _T)
         ; RvalConst0 = llconst_float(_F)
         ; RvalConst0 = llconst_string(_S)
@@ -1179,7 +1187,7 @@ short_circuit_labels_const(InstrMap, RvalConst0, RvalConst) :-
 %
 % :- pred short_circuit_labels_maybe_rvals(instrmap::in, list(maybe(rval))::in,
 %     list(maybe(rval))::out) is det.
-% 
+%
 % short_circuit_labels_maybe_rvals(_, [], []).
 % short_circuit_labels_maybe_rvals(InstrMap, [MaybeRval0 | MaybeRvals0],
 %         [MaybeRval | MaybeRvals]) :-
diff --git a/compiler/ll_pseudo_type_info.m b/compiler/ll_pseudo_type_info.m
index a6bae0e50..199781a9d 100644
--- a/compiler/ll_pseudo_type_info.m
+++ b/compiler/ll_pseudo_type_info.m
@@ -89,7 +89,7 @@ convert_pseudo_type_info(Pseudo, !StaticCellInfo, Rval, LldsType) :-
     (
         Pseudo = type_var(Int),
         Rval = const(llconst_int(Int)),
-        LldsType = lt_integer
+        LldsType = lt_int(int_type_int)
     ;
         Pseudo = plain_arity_zero_pseudo_type_info(RttiTypeCtor),
         DataId = rtti_data_id(
diff --git a/compiler/llds.m b/compiler/llds.m
index 02df86c23..73a3fdec1 100644
--- a/compiler/llds.m
+++ b/compiler/llds.m
@@ -1203,6 +1203,15 @@
     ;       llconst_false
     ;       llconst_int(int)
     ;       llconst_uint(uint)
+
+            % XXX FIXED SIZE INT
+    ;       llconst_int8(int)
+    ;       llconst_uint8(int)
+    ;       llconst_int16(int)
+    ;       llconst_uint16(int)
+    ;       llconst_int32(int)
+    ;       llconst_uint32(int)
+
     ;       llconst_foreign(string, llds_type)
             % A constant in the target language.
             % It may be a #defined constant in C which is why
@@ -1368,11 +1377,10 @@
             % An unsigned version of intleast_32, represented using the C type
             % uint_least32_t.
 
-    ;       lt_integer
+    ;       lt_int(int_type)
+
             % A Mercury `int', represented in C as a value of type `MR_Integer'
             % (which is a signed integral type of the same size as a pointer).
-
-    ;       lt_unsigned
             % Something whose C type is `MR_Unsigned' (the unsigned equivalent
             % of `MR_Integer').
 
@@ -1669,8 +1677,14 @@ rval_type(mem_addr(_), lt_data_ptr).
 
 const_type(llconst_true, lt_bool).
 const_type(llconst_false, lt_bool).
-const_type(llconst_int(_), lt_integer).
-const_type(llconst_uint(_), lt_unsigned).
+const_type(llconst_int(_), lt_int(int_type_int)).
+const_type(llconst_uint(_), lt_int(int_type_uint)).
+const_type(llconst_int8(_), lt_int(int_type_int8)).
+const_type(llconst_uint8(_), lt_int(int_type_uint8)).
+const_type(llconst_int16(_), lt_int(int_type_int16)).
+const_type(llconst_uint16(_), lt_int(int_type_uint16)).
+const_type(llconst_int32(_), lt_int(int_type_int32)).
+const_type(llconst_uint32(_), lt_int(int_type_uint32)).
 const_type(llconst_foreign(_, Type), Type).
 const_type(llconst_float(_), lt_float).
 const_type(llconst_string(_), lt_string).
@@ -1684,15 +1698,14 @@ unop_return_type(unmktag, lt_word).
 unop_return_type(strip_tag, lt_word).
 unop_return_type(mkbody, lt_word).
 unop_return_type(unmkbody, lt_word).
-unop_return_type(bitwise_complement, lt_integer).
+unop_return_type(bitwise_complement(IntType), lt_int(IntType)).
 unop_return_type(logical_not, lt_bool).
-unop_return_type(hash_string, lt_integer).
-unop_return_type(hash_string2, lt_integer).
-unop_return_type(hash_string3, lt_integer).
-unop_return_type(hash_string4, lt_integer).
-unop_return_type(hash_string5, lt_integer).
-unop_return_type(hash_string6, lt_integer).
-unop_return_type(uint_bitwise_complement, lt_unsigned).
+unop_return_type(hash_string, lt_int(int_type_int)).
+unop_return_type(hash_string2, lt_int(int_type_int)).
+unop_return_type(hash_string3, lt_int(int_type_int)).
+unop_return_type(hash_string4, lt_int(int_type_int)).
+unop_return_type(hash_string5, lt_int(int_type_int)).
+unop_return_type(hash_string6, lt_int(int_type_int)).
 
 unop_arg_type(mktag, lt_word).
 unop_arg_type(tag, lt_word).
@@ -1700,7 +1713,7 @@ unop_arg_type(unmktag, lt_word).
 unop_arg_type(strip_tag, lt_word).
 unop_arg_type(mkbody, lt_word).
 unop_arg_type(unmkbody, lt_word).
-unop_arg_type(bitwise_complement, lt_integer).
+unop_arg_type(bitwise_complement(IntType), lt_int(IntType)).
 unop_arg_type(logical_not, lt_bool).
 unop_arg_type(hash_string, lt_string).
 unop_arg_type(hash_string2, lt_string).
@@ -1708,24 +1721,23 @@ unop_arg_type(hash_string3, lt_string).
 unop_arg_type(hash_string4, lt_string).
 unop_arg_type(hash_string5, lt_string).
 unop_arg_type(hash_string6, lt_string).
-unop_arg_type(uint_bitwise_complement, lt_unsigned).
-
-binop_return_type(int_add, lt_integer).
-binop_return_type(int_sub, lt_integer).
-binop_return_type(int_mul, lt_integer).
-binop_return_type(int_div, lt_integer).
-binop_return_type(int_mod, lt_integer).
-binop_return_type(unchecked_left_shift, lt_integer).
-binop_return_type(unchecked_right_shift, lt_integer).
-binop_return_type(bitwise_and, lt_integer).
-binop_return_type(bitwise_or, lt_integer).
-binop_return_type(bitwise_xor, lt_integer).
+
+binop_return_type(int_add(IntType), lt_int(IntType)).
+binop_return_type(int_sub(IntType), lt_int(IntType)).
+binop_return_type(int_mul(IntType), lt_int(IntType)).
+binop_return_type(int_div(IntType), lt_int(IntType)).
+binop_return_type(int_mod(IntType), lt_int(IntType)).
+binop_return_type(unchecked_left_shift(IntType), lt_int(IntType)).
+binop_return_type(unchecked_right_shift(IntType), lt_int(IntType)).
+binop_return_type(bitwise_and(IntType), lt_int(IntType)).
+binop_return_type(bitwise_or(IntType), lt_int(IntType)).
+binop_return_type(bitwise_xor(IntType), lt_int(IntType)).
 binop_return_type(logical_and, lt_bool).
 binop_return_type(logical_or, lt_bool).
-binop_return_type(eq, lt_bool).
-binop_return_type(ne, lt_bool).
+binop_return_type(eq(_), lt_bool).
+binop_return_type(ne(_), lt_bool).
 binop_return_type(array_index(_Type), lt_word).
-binop_return_type(string_unsafe_index_code_unit, lt_integer).
+binop_return_type(string_unsafe_index_code_unit, lt_int(int_type_int)).
 binop_return_type(offset_str_eq(_), lt_bool).
 binop_return_type(str_eq, lt_bool).
 binop_return_type(str_ne, lt_bool).
@@ -1733,11 +1745,11 @@ binop_return_type(str_lt, lt_bool).
 binop_return_type(str_gt, lt_bool).
 binop_return_type(str_le, lt_bool).
 binop_return_type(str_ge, lt_bool).
-binop_return_type(str_cmp, lt_integer).
-binop_return_type(int_lt, lt_bool).
-binop_return_type(int_gt, lt_bool).
-binop_return_type(int_le, lt_bool).
-binop_return_type(int_ge, lt_bool).
+binop_return_type(str_cmp, lt_int(int_type_int)).
+binop_return_type(int_lt(_), lt_bool).
+binop_return_type(int_gt(_), lt_bool).
+binop_return_type(int_le(_), lt_bool).
+binop_return_type(int_ge(_), lt_bool).
 binop_return_type(unsigned_le, lt_bool).
 binop_return_type(float_plus, lt_float).
 binop_return_type(float_minus, lt_float).
@@ -1755,22 +1767,6 @@ binop_return_type(body, lt_word).
 binop_return_type(compound_eq, lt_bool).
 binop_return_type(compound_lt, lt_bool).
 binop_return_type(pointer_equal_conservative, lt_bool).
-binop_return_type(uint_eq, lt_bool).
-binop_return_type(uint_ne, lt_bool).
-binop_return_type(uint_lt, lt_bool).
-binop_return_type(uint_gt, lt_bool).
-binop_return_type(uint_le, lt_bool).
-binop_return_type(uint_ge, lt_bool).
-binop_return_type(uint_add, lt_unsigned).
-binop_return_type(uint_sub, lt_unsigned).
-binop_return_type(uint_mul, lt_unsigned).
-binop_return_type(uint_div, lt_unsigned).
-binop_return_type(uint_mod, lt_unsigned).
-binop_return_type(uint_bitwise_and, lt_unsigned).
-binop_return_type(uint_bitwise_or, lt_unsigned).
-binop_return_type(uint_bitwise_xor, lt_unsigned).
-binop_return_type(uint_unchecked_left_shift, lt_unsigned).
-binop_return_type(uint_unchecked_right_shift, lt_unsigned).
 
 register_type(reg_r, lt_word).
 register_type(reg_f, lt_float).
diff --git a/compiler/llds_out_data.m b/compiler/llds_out_data.m
index bbcab36f4..a0111f038 100644
--- a/compiler/llds_out_data.m
+++ b/compiler/llds_out_data.m
@@ -161,6 +161,7 @@
 :- import_module mdbcomp.builtin_modules.
 :- import_module mdbcomp.sym_name.
 :- import_module parse_tree.
+:- import_module parse_tree.prog_data.
 :- import_module parse_tree.prog_foreign.
 
 :- import_module int.
@@ -548,13 +549,13 @@ output_double_stackvar_ptr(Info, StackType, SlotNum, !IO) :-
 :- pred llds_types_match(llds_type::in, llds_type::in) is semidet.
 
 llds_types_match(Type, Type).
-llds_types_match(lt_word, lt_unsigned).
-llds_types_match(lt_word, lt_integer).
+llds_types_match(lt_word, lt_int(int_type_int)).
+llds_types_match(lt_word, lt_int(int_type_int)).
 llds_types_match(lt_word, lt_bool).
-llds_types_match(lt_bool, lt_integer).
-llds_types_match(lt_bool, lt_unsigned).
+llds_types_match(lt_bool, lt_int(int_type_int)).
+llds_types_match(lt_bool, lt_int(int_type_uint)).
 llds_types_match(lt_bool, lt_word).
-llds_types_match(lt_integer, lt_bool).
+llds_types_match(lt_int(int_type_int), lt_bool).
 
 output_llds_type_cast(LLDSType, !IO) :-
     io.write_string("(", !IO),
@@ -575,10 +576,22 @@ output_llds_type(lt_uint_least32, !IO) :-
     io.write_string("MR_uint_least32_t", !IO).
 output_llds_type(lt_bool, !IO) :-
     io.write_string("MR_Integer", !IO).
-output_llds_type(lt_integer, !IO) :-
+output_llds_type(lt_int(int_type_int), !IO) :-
     io.write_string("MR_Integer", !IO).
-output_llds_type(lt_unsigned, !IO) :-
+output_llds_type(lt_int(int_type_uint), !IO) :-
     io.write_string("MR_Unsigned", !IO).
+output_llds_type(lt_int(int_type_int8), !IO) :-
+    io.write_string("int8_t", !IO).
+output_llds_type(lt_int(int_type_uint8), !IO) :-
+    io.write_string("uint8_t", !IO).
+output_llds_type(lt_int(int_type_int16), !IO) :-
+    io.write_string("int16_t", !IO).
+output_llds_type(lt_int(int_type_uint16), !IO) :-
+    io.write_string("uint16_t", !IO).
+output_llds_type(lt_int(int_type_int32), !IO) :-
+    io.write_string("int32_t", !IO).
+output_llds_type(lt_int(int_type_uint32), !IO) :-
+    io.write_string("uint32_t", !IO).
 output_llds_type(lt_float, !IO) :-
     io.write_string("MR_Float", !IO).
 output_llds_type(lt_word, !IO) :-
@@ -869,14 +882,14 @@ output_rval(Info, Rval, !IO) :-
             io.write_string("(", !IO),
             output_rval_as_type(Info, SubRvalA, lt_data_ptr, !IO),
             io.write_string(")[", !IO),
-            output_rval_as_type(Info, SubRvalB, lt_integer, !IO),
+            output_rval_as_type(Info, SubRvalB, lt_int(int_type_int), !IO),
             io.write_string("]", !IO)
         ;
             Op = string_unsafe_index_code_unit,
             io.write_string("MR_nth_code_unit(", !IO),
             output_rval_as_type(Info, SubRvalA, lt_data_ptr, !IO),
             io.write_string(", ", !IO),
-            output_rval_as_type(Info, SubRvalB, lt_integer, !IO),
+            output_rval_as_type(Info, SubRvalB, lt_int(int_type_int), !IO),
             io.write_string(")", !IO)
         ;
             Op = pointer_equal_conservative,
@@ -941,40 +954,40 @@ output_rval(Info, Rval, !IO) :-
         ;
             Op = unsigned_le,
             io.write_string("(", !IO),
-            output_rval_as_type(Info, SubRvalA, lt_unsigned, !IO),
+            output_rval_as_type(Info, SubRvalA, lt_int(int_type_uint), !IO),
             io.write_string(" <= ", !IO),
-            output_rval_as_type(Info, SubRvalB, lt_unsigned, !IO),
+            output_rval_as_type(Info, SubRvalB, lt_int(int_type_uint), !IO),
             io.write_string(")", !IO)
         ;
-            ( Op = int_add, OpStr = "+"
-            ; Op = int_sub, OpStr = "-"
-            ; Op = int_mul, OpStr = "*"
-            ; Op = int_div, OpStr = "/"
-            ; Op = int_mod, OpStr = "%"
-            ; Op = eq, OpStr = "=="
-            ; Op = ne, OpStr = "!="
-            ; Op = int_lt, OpStr = "<"
-            ; Op = int_gt, OpStr = ">"
-            ; Op = int_le, OpStr = "<="
-            ; Op = int_ge, OpStr = ">="
-            ; Op = unchecked_left_shift, OpStr = "<<"
-            ; Op = unchecked_right_shift, OpStr = ">>"
-            ; Op = bitwise_and, OpStr = "&"
-            ; Op = bitwise_or, OpStr = "|"
-            ; Op = bitwise_xor, OpStr = "^"
-            ; Op = logical_and, OpStr = "&&"
-            ; Op = logical_or, OpStr = "||"
+            ( Op = int_add(IntType), OpStr = "+"
+            ; Op = int_sub(IntType), OpStr = "-"
+            ; Op = int_mul(IntType), OpStr = "*"
+            ; Op = int_div(IntType), OpStr = "/"
+            ; Op = int_mod(IntType), OpStr = "%"
+            ; Op = eq(IntType), OpStr = "=="
+            ; Op = ne(IntType), OpStr = "!="
+            ; Op = int_lt(IntType), OpStr = "<"
+            ; Op = int_gt(IntType), OpStr = ">"
+            ; Op = int_le(IntType), OpStr = "<="
+            ; Op = int_ge(IntType), OpStr = ">="
+            ; Op = bitwise_and(IntType), OpStr = "&"
+            ; Op = bitwise_or(IntType), OpStr = "|"
+            ; Op = bitwise_xor(IntType), OpStr = "^"
             ),
             ( if
                 % Special-case equality ops to avoid some unnecessary casts --
                 % there is no difference between signed and unsigned equality,
                 % so if both args are unsigned, we don't need to cast them to
                 % MR_Integer.
-                ( Op = eq ; Op = ne ),
+                ( Op = eq(_) ; Op = ne(_) ),
                 llds.rval_type(SubRvalA, SubRvalAType),
-                ( SubRvalAType = lt_word ; SubRvalAType = lt_unsigned ),
+                ( SubRvalAType = lt_word
+                ; SubRvalAType = lt_int(int_type_uint)
+                ),
                 llds.rval_type(SubRvalB, SubRvalBType),
-                ( SubRvalBType = lt_word ; SubRvalBType = lt_unsigned )
+                ( SubRvalBType = lt_word
+                ; SubRvalBType = lt_int(int_type_uint)
+                )
             then
                 io.write_string("(", !IO),
                 output_rval(Info, SubRvalA, !IO),
@@ -1002,37 +1015,36 @@ output_rval(Info, Rval, !IO) :-
         %       io.write_string(")")
             else
                 io.write_string("(", !IO),
-                output_rval_as_type(Info, SubRvalA, lt_integer, !IO),
+                output_rval_as_type(Info, SubRvalA, lt_int(IntType), !IO),
                 io.write_string(" ", !IO),
                 io.write_string(OpStr, !IO),
                 io.write_string(" ", !IO),
-                output_rval_as_type(Info, SubRvalB, lt_integer, !IO),
+                output_rval_as_type(Info, SubRvalB, lt_int(IntType), !IO),
                 io.write_string(")", !IO)
             )
         ;
-            ( Op = uint_eq, OpStr = "=="
-            ; Op = uint_ne, OpStr = "!="
-            ; Op = uint_lt, OpStr = "<"
-            ; Op = uint_gt, OpStr = ">"
-            ; Op = uint_le, OpStr = "<="
-            ; Op = uint_ge, OpStr = ">="
-            ; Op = uint_add, OpStr = "+"
-            ; Op = uint_sub, OpStr = "-"
-            ; Op = uint_mul, OpStr = "*"
-            ; Op = uint_div, OpStr = "/"
-            ; Op = uint_mod, OpStr = "%"
-            ; Op = uint_bitwise_and, OpStr = "&"
-            ; Op = uint_bitwise_or, OpStr = "|"
-            ; Op = uint_bitwise_xor, OpStr = "^"
-            ; Op = uint_unchecked_left_shift, OpStr = "<<"
-            ; Op = uint_unchecked_right_shift, OpStr = ">>"
+            ( Op = logical_and, OpStr = "&&"
+            ; Op = logical_or, OpStr = "||"
             ),
             io.write_string("(", !IO),
-            output_rval_as_type(Info, SubRvalA, lt_unsigned, !IO),
+            output_rval_as_type(Info, SubRvalA, lt_int(int_type_int), !IO),
             io.write_string(" ", !IO),
             io.write_string(OpStr, !IO),
             io.write_string(" ", !IO),
-            output_rval_as_type(Info, SubRvalB, lt_unsigned, !IO),
+            output_rval_as_type(Info, SubRvalB, lt_int(int_type_int), !IO),
+            io.write_string(")", !IO)
+        ;
+            % The second operand of the shift operatators always has type
+            % `int'.
+            ( Op = unchecked_left_shift(IntType), OpStr = "<<"
+            ; Op = unchecked_right_shift(IntType), OpStr = ">>"
+            ),
+            io.write_string("(", !IO),
+            output_rval_as_type(Info, SubRvalA, lt_int(IntType), !IO),
+            io.write_string(" ", !IO),
+            io.write_string(OpStr, !IO),
+            io.write_string(" ", !IO),
+            output_rval_as_type(Info, SubRvalB, lt_int(int_type_int), !IO),
             io.write_string(")", !IO)
         ;
             Op = str_cmp,
@@ -1053,16 +1065,16 @@ output_rval(Info, Rval, !IO) :-
         ;
             Op = body,
             io.write_string("MR_body(", !IO),
-            output_rval_as_type(Info, SubRvalA, lt_integer, !IO),
+            output_rval_as_type(Info, SubRvalA, lt_int(int_type_int), !IO),
             io.write_string(", ", !IO),
-            output_rval_as_type(Info, SubRvalB, lt_integer, !IO),
+            output_rval_as_type(Info, SubRvalB, lt_int(int_type_int), !IO),
             io.write_string(")", !IO)
         ;
             Op = float_word_bits,
             io.write_string("MR_float_word_bits(", !IO),
             output_rval_as_type(Info, SubRvalA, lt_float, !IO),
             io.write_string(", ", !IO),
-            output_rval_as_type(Info, SubRvalB, lt_integer, !IO),
+            output_rval_as_type(Info, SubRvalB, lt_int(int_type_int), !IO),
             io.write_string(")", !IO)
         ;
             Op = float_from_dword,
@@ -1150,7 +1162,7 @@ output_rval(Info, Rval, !IO) :-
             ( if SubRval = const(llconst_int(SlotNum)) then
                 io.write_int(SlotNum, !IO)
             else
-                output_rval_as_type(Info, SubRval, lt_integer, !IO)
+                output_rval_as_type(Info, SubRval, lt_int(int_type_int), !IO)
             ),
             io.write_string(")", !IO)
         ;
@@ -1160,7 +1172,8 @@ output_rval(Info, Rval, !IO) :-
             ( if SubRval = const(llconst_int(SlotNum)) then
                 io.write_int(SlotNum, !IO)
             else
-                output_rval_as_type(Info, SubRval, lt_integer, !IO)
+                output_rval_as_type(Info, SubRval, lt_int(int_type_int),
+                    !IO)
             ),
             io.write_string(")", !IO)
         ;
@@ -1180,7 +1193,8 @@ output_rval(Info, Rval, !IO) :-
             ( if FieldNumRval = const(llconst_int(FieldNum)) then
                 io.write_int(FieldNum, !IO)
             else
-                output_rval_as_type(Info, FieldNumRval, lt_integer, !IO)
+                output_rval_as_type(Info, FieldNumRval, lt_int(int_type_int),
+                    !IO)
             ),
             io.write_string(")", !IO)
         )
@@ -1203,6 +1217,24 @@ output_rval_const(Info, Const, !IO) :-
         Const = llconst_uint(N),
         c_util.output_uint_expr_cur_stream(N, !IO)
     ;
+        Const = llconst_int8(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = llconst_uint8(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = llconst_int16(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = llconst_uint16(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = llconst_int32(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = llconst_uint32(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
         Const = llconst_foreign(Value, Type),
         io.write_char('(', !IO),
         output_llds_type_cast(Type, !IO),
@@ -1296,6 +1328,18 @@ output_type_ctor_addr(Module0, Name, Arity, !IO) :-
                 Macro = "MR_INT_CTOR_ADDR"
             else if Name = "uint" then
                 Macro = "MR_UINT_CTOR_ADDR"
+            else if Name = "int8" then
+                Macro = "MR_INT8_CTOR_ADDR"
+            else if Name = "uint8" then
+                Macro = "MR_UINT8_CTOR_ADDR"
+            else if Name = "int16" then
+                Macro = "MR_INT16_CTOR_ADDR"
+            else if Name = "uint16" then
+                Macro = "MR_UINT16_CTOR_ADDR"
+            else if Name = "int32" then
+                Macro = "MR_INT32_CTOR_ADDR"
+            else if Name = "uint32" then
+                Macro = "MR_UINT32_CTOR_ADDR"
             else if Name = "float" then
                 Macro = "MR_FLOAT_CTOR_ADDR"
             else if Name = "string" then
@@ -1346,7 +1390,7 @@ output_rval_as_type(Info, Rval, DesiredType, !IO) :-
         output_rval(Info, Rval, !IO)
     else
         % We need to convert to the right type first.
-        % Convertions to/from float must be treated specially;
+        % Conversions to/from float must be treated specially;
         % for the others, we can just use a cast.
         ( if DesiredType = lt_float then
             io.write_string("MR_word_to_float(", !IO),
@@ -1568,27 +1612,27 @@ is_int_cmp(Test, Left, RightConst, OpStr, NegOpStr) :-
     Test = binop(Op, Left, Right),
     Right = const(llconst_int(RightConst)),
     (
-        Op = eq,
+        Op = eq(int_type_int),
         OpStr = "MR_INT_EQ",
         NegOpStr = "MR_INT_NE"
     ;
-        Op = ne,
+        Op = ne(int_type_int),
         OpStr = "MR_INT_NE",
         NegOpStr = "MR_INT_EQ"
     ;
-        Op = int_lt,
+        Op = int_lt(int_type_int),
         OpStr = "MR_INT_LT",
         NegOpStr = "MR_INT_GE"
     ;
-        Op = int_gt,
+        Op = int_gt(int_type_int),
         OpStr = "MR_INT_GT",
         NegOpStr = "MR_INT_LT"
     ;
-        Op = int_le,
+        Op = int_le(int_type_int),
         OpStr = "MR_INT_LE",
         NegOpStr = "MR_INT_GT"
     ;
-        Op = int_ge,
+        Op = int_ge(int_type_int),
         OpStr = "MR_INT_GE",
         NegOpStr = "MR_INT_LT"
     ).
@@ -1600,17 +1644,17 @@ is_ptag_test(Test, Rval, Ptag, Negated) :-
     Left = unop(tag, Rval),
     Right = unop(mktag, const(llconst_int(Ptag))),
     (
-        Op = eq,
+        Op = eq(_),
         Negated = no
     ;
-        Op = ne,
+        Op = ne(_),
         Negated = yes
     ).
 
 :- pred is_remote_stag_test(rval::in, rval::in, int::in, int::out) is semidet.
 
 is_remote_stag_test(Test, Rval, Ptag, Stag) :-
-    Test = binop(eq, Left, Right),
+    Test = binop(eq(int_type_int), Left, Right),
     Left = lval(field(yes(Ptag), Rval, Zero)),
     Zero = const(llconst_int(0)),
     Right = const(llconst_int(Stag)).
@@ -1622,10 +1666,10 @@ is_local_stag_test(Test, Rval, Ptag, Stag, Negated) :-
     Test = binop(Op, Rval, Right),
     Right = mkword(Ptag, unop(mkbody, const(llconst_int(Stag)))),
     (
-        Op = eq,
+        Op = eq(_),
         Negated = no
     ;
-        Op = ne,
+        Op = ne(_),
         Negated = yes
     ).
 
@@ -1641,8 +1685,7 @@ direct_field_int_constant(lt_int_least16) = yes.
 direct_field_int_constant(lt_uint_least16) = yes.
 direct_field_int_constant(lt_int_least32) = yes.
 direct_field_int_constant(lt_uint_least32) = yes.
-direct_field_int_constant(lt_integer) = yes.
-direct_field_int_constant(lt_unsigned) = yes.
+direct_field_int_constant(lt_int(_)) = yes.
 direct_field_int_constant(lt_float) = no.
 direct_field_int_constant(lt_string) = no.
 direct_field_int_constant(lt_data_ptr) = no.
diff --git a/compiler/llds_out_global.m b/compiler/llds_out_global.m
index eb470c0b8..2d9c0cf11 100644
--- a/compiler/llds_out_global.m
+++ b/compiler/llds_out_global.m
@@ -60,6 +60,7 @@
 :- import_module mdbcomp.
 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.
+:- import_module parse_tree.prog_data.
 :- import_module parse_tree.prog_data_pragma.
 
 :- import_module assoc_list.
@@ -727,8 +728,8 @@ ok_int_const(_N, lt_int_least32).
 ok_int_const(_N, lt_uint_least32).
 ok_int_const(_N, lt_bool) :-
     unexpected($module, $pred, "not integer constant").
-ok_int_const(_N, lt_integer).
-ok_int_const(_N, lt_unsigned).
+ok_int_const(_N, lt_int(int_type_int)).
+ok_int_const(_N, lt_int(int_type_uint)).
 ok_int_const(_, lt_float) :-
     unexpected($module, $pred, "not integer constant").
 ok_int_const(_, lt_word) :-
diff --git a/compiler/llds_out_instr.m b/compiler/llds_out_instr.m
index 7bc51b5a8..e35511f8f 100644
--- a/compiler/llds_out_instr.m
+++ b/compiler/llds_out_instr.m
@@ -659,7 +659,7 @@ output_instruction(Info, Instr, LabelOutputInfo, !IO) :-
     ;
         Instr = computed_goto(Rval, MaybeLabels),
         io.write_string("\tMR_COMPUTED_GOTO(", !IO),
-        output_rval_as_type(Info, Rval, lt_unsigned, !IO),
+        output_rval_as_type(Info, Rval, lt_int(int_type_uint), !IO),
         io.write_string(",\n\t\t", !IO),
         output_label_list_or_not_reached(MaybeLabels, !IO),
         io.write_string(");\n", !IO)
@@ -2089,12 +2089,7 @@ output_foreign_proc_output(Info, Output, !IO) :-
                     io.write_string("(MR_UnsignedChar) ", !IO),
                     io.write_string(VarName, !IO)
                 ;
-                    BuiltinType = builtin_type_int,
-                    output_lval_as_word(Info, Lval, !IO),
-                    io.write_string(" = ", !IO),
-                    io.write_string(VarName, !IO)
-                ;
-                    BuiltinType = builtin_type_uint,
+                    BuiltinType = builtin_type_int(_),
                     output_lval_as_word(Info, Lval, !IO),
                     io.write_string(" = ", !IO),
                     io.write_string(VarName, !IO)
diff --git a/compiler/lookup_switch.m b/compiler/lookup_switch.m
index 7e8c7df7e..0aba8ef26 100644
--- a/compiler/lookup_switch.m
+++ b/compiler/lookup_switch.m
@@ -335,7 +335,8 @@ generate_int_lookup_switch(VarRval, LookupSwitchInfo, EndLabel, StoreMap,
     ( if StartVal = 0 then
         IndexRval = VarRval
     else
-        IndexRval = binop(int_sub, VarRval, const(llconst_int(StartVal)))
+        IndexRval = binop(int_sub(int_type_int), VarRval,
+            const(llconst_int(StartVal)))
     ),
 
     % If the switch is not locally deterministic, we may need to check that
@@ -432,7 +433,7 @@ generate_simple_int_lookup_switch(IndexRval, StoreMap, StartVal, EndVal,
         ( if NumOutVars = 1 then
             BaseRval = IndexRval
         else
-            BaseRval = binop(int_mul,
+            BaseRval = binop(int_mul(int_type_int),
                 IndexRval, const(llconst_int(NumOutVars)))
         ),
         BaseRegInitCode = cord.singleton(
@@ -518,7 +519,7 @@ generate_several_soln_int_lookup_switch(IndexRval, EndLabel, StoreMap,
         unexpected($module, $pred, "bad FailCaseCount")
     ),
 
-    MainRowTypes = [lt_integer, lt_integer | OutTypes],
+    MainRowTypes = [lt_int(int_type_int), lt_int(int_type_int) | OutTypes],
     list.length(MainRowTypes, MainNumColumns),
     add_vector_static_cell(MainRowTypes, MainRows, MainVectorAddr, !CI),
     MainVectorAddrRval = const(llconst_data_addr(MainVectorAddr, no)),
@@ -540,7 +541,7 @@ generate_several_soln_int_lookup_switch(IndexRval, EndLabel, StoreMap,
         llds_instr(
             assign(BaseReg,
                 mem_addr(heap_ref(MainVectorAddrRval, yes(0),
-                    binop(int_mul,
+                    binop(int_mul(int_type_int),
                         IndexRval,
                         const(llconst_int(MainNumColumns)))))),
             "Compute base address for this case")
@@ -597,7 +598,7 @@ generate_code_for_each_kind([Kind | Kinds], NumPrevColumns,
         !MaybeEnd, Code, !CI) :-
     (
         Kind = kind_zero_solns,
-        TestOp = int_ge,
+        TestOp = int_ge(int_type_int),
         some [!CLD] (
             reset_to_position(BranchStart, !.CI, !:CLD),
             release_reg(BaseReg, !CLD),
@@ -605,7 +606,7 @@ generate_code_for_each_kind([Kind | Kinds], NumPrevColumns,
         )
     ;
         Kind = kind_one_soln,
-        TestOp = ne,
+        TestOp = ne(int_type_int),
         some [!CLD] (
             reset_to_position(BranchStart, !.CI, !:CLD),
             generate_offset_assigns(OutVars, NumPrevColumns + 2, BaseReg,
@@ -620,7 +621,7 @@ generate_code_for_each_kind([Kind | Kinds], NumPrevColumns,
         KindCode = BranchEndCode ++ GotoEndCode
     ;
         Kind = kind_several_solns,
-        TestOp = int_le,
+        TestOp = int_le(int_type_int),
         get_globals(!.CI, Globals),
         some [!CLD] (
             reset_to_position(BranchStart, !.CI, !:CLD),
@@ -693,12 +694,12 @@ generate_code_for_each_kind([Kind | Kinds], NumPrevColumns,
                 llds_instr(assign(LaterBaseReg, lval(CurSlot)),
                     "Init later base register"),
                 llds_instr(
-                    if_val(binop(int_ge,
+                    if_val(binop(int_ge(int_type_int),
                         lval(LaterBaseReg), lval(MaxSlot)),
                     code_label(UndoLabel)),
                     "Jump to undo hijack code if there are no more solutions"),
                 llds_instr(assign(CurSlot,
-                    binop(int_add,
+                    binop(int_add(int_type_int),
                         lval(CurSlot),
                         const(llconst_int(NumOutVars)))),
                     "Update current slot in the later solution array"),
@@ -877,7 +878,7 @@ generate_bitvec_test(IndexRval, CaseVals, Start, _End, CheckCode,
         % This is the same as
         % WordNum = binop(int_div, IndexRval, const(llconst_int(WordBits)))
         % except that it can generate more efficient code.
-        WordNum = binop(unchecked_right_shift, IndexRval,
+        WordNum = binop(unchecked_right_shift(int_type_int), IndexRval,
             const(llconst_int(Log2WordBits))),
 
         Word = lval(field(yes(0), BitVecRval, WordNum)),
@@ -885,11 +886,12 @@ generate_bitvec_test(IndexRval, CaseVals, Start, _End, CheckCode,
         % This is the same as
         % BitNum = binop(int_mod, IndexRval, const(llconst_int(WordBits)))
         % except that it can generate more efficient code.
-        BitNum = binop(bitwise_and, IndexRval,
+        BitNum = binop(bitwise_and(int_type_int), IndexRval,
             const(llconst_int(WordBits - 1)))
     ),
-    HasBit = binop(bitwise_and,
-        binop(unchecked_left_shift, const(llconst_int(1)), BitNum), Word),
+    HasBit = binop(bitwise_and(int_type_int),
+        binop(unchecked_left_shift(int_type_int), const(llconst_int(1)), BitNum),
+        Word),
     fail_if_rval_is_false(HasBit, CheckCode, !CI, !CLD).
 
     % We generate the bitvector by iterating through the cases marking the bit
@@ -948,8 +950,15 @@ default_value_for_type(lt_int_least16) = const(llconst_int(0)).
 default_value_for_type(lt_uint_least16) = const(llconst_int(0)).
 default_value_for_type(lt_int_least32) = const(llconst_int(0)).
 default_value_for_type(lt_uint_least32) = const(llconst_int(0)).
-default_value_for_type(lt_integer) = const(llconst_int(0)).
-default_value_for_type(lt_unsigned) = const(llconst_int(0)).
+default_value_for_type(lt_int(int_type_int)) = const(llconst_int(0)).
+default_value_for_type(lt_int(int_type_uint)) = const(llconst_uint(0u)).
+% XXX FIXED SIZE INT.
+default_value_for_type(lt_int(int_type_int8)) = const(llconst_int8(0)).
+default_value_for_type(lt_int(int_type_uint8)) = const(llconst_uint8(0)).
+default_value_for_type(lt_int(int_type_int16)) = const(llconst_int16(0)).
+default_value_for_type(lt_int(int_type_uint16)) = const(llconst_uint16(0)).
+default_value_for_type(lt_int(int_type_int32)) = const(llconst_int32(0)).
+default_value_for_type(lt_int(int_type_uint32)) = const(llconst_uint32(0)).
 default_value_for_type(lt_float) = const(llconst_float(0.0)).
 default_value_for_type(lt_string) = const(llconst_string("")).
 default_value_for_type(lt_data_ptr) = const(llconst_int(0)).
diff --git a/compiler/mercury_to_mercury.m b/compiler/mercury_to_mercury.m
index b8ff0f7e6..a88aeb0e1 100644
--- a/compiler/mercury_to_mercury.m
+++ b/compiler/mercury_to_mercury.m
@@ -267,6 +267,24 @@ mercury_format_cons_id(NeedsBrackets, ConsId, !U) :-
         ConsId = uint_const(UInt),
         add_uint(UInt, !U)
     ;
+        ConsId = int8_const(Int8),
+        add_int8(Int8, !U)
+    ;
+        ConsId = uint8_const(UInt8),
+        add_uint8(UInt8, !U)
+    ;
+        ConsId = int16_const(Int16),
+        add_int16(Int16, !U)
+    ;
+        ConsId = uint16_const(UInt16),
+        add_uint16(UInt16, !U)
+    ;
+        ConsId = int32_const(Int32),
+        add_int32(Int32, !U)
+    ;
+        ConsId = uint32_const(UInt32),
+        add_uint32(UInt32, !U)
+    ;
         ConsId = float_const(Float),
         add_float(Float, !U)
     ;
diff --git a/compiler/middle_rec.m b/compiler/middle_rec.m
index 2faf45cf6..1ab26884d 100644
--- a/compiler/middle_rec.m
+++ b/compiler/middle_rec.m
@@ -323,18 +323,21 @@ middle_rec_generate_switch(Var, BaseConsId, Base, Recursive, SwitchGoalInfo,
         IncrAuxReg = singleton(
             llds_instr(
                 assign(AuxReg,
-                    binop(int_add, lval(AuxReg), const(llconst_int(1)))),
+                    binop(int_add(int_type_int), lval(AuxReg),
+                        const(llconst_int(1)))),
                 "increment loop counter")
         ),
         DecrAuxReg = singleton(
             llds_instr(
                 assign(AuxReg,
-                    binop(int_sub, lval(AuxReg), const(llconst_int(1)))),
+                    binop(int_sub(int_type_int), lval(AuxReg),
+                        const(llconst_int(1)))),
                 "decrement loop counter")
         ),
         TestAuxReg = singleton(
             llds_instr(
-                if_val(binop(int_gt, lval(AuxReg), const(llconst_int(0))),
+                if_val(binop(
+                    int_gt(int_type_int), lval(AuxReg), const(llconst_int(0))),
                     code_label(Loop2Label)),
                 "test on upward loop")
         )
@@ -352,7 +355,8 @@ middle_rec_generate_switch(Var, BaseConsId, Base, Recursive, SwitchGoalInfo,
         IncrAuxReg = empty,
         DecrAuxReg = empty,
         TestAuxReg = singleton(
-            llds_instr(if_val(binop(int_gt, lval(sp), lval(AuxReg)),
+            llds_instr(if_val(binop(
+                int_gt(int_type_int), lval(sp), lval(AuxReg)),
                 code_label(Loop2Label)),
                 "test on upward loop")
         )
diff --git a/compiler/ml_accurate_gc.m b/compiler/ml_accurate_gc.m
index 09b175e58..61293ede8 100644
--- a/compiler/ml_accurate_gc.m
+++ b/compiler/ml_accurate_gc.m
@@ -252,8 +252,7 @@ ml_type_might_contain_pointers_for_gc(Type) = MightContainPointers :-
 
 ml_type_category_might_contain_pointers(CtorCat) = MayContainPointers :-
     (
-        ( CtorCat = ctor_cat_builtin(cat_builtin_int)
-        ; CtorCat = ctor_cat_builtin(cat_builtin_uint)
+        ( CtorCat = ctor_cat_builtin(cat_builtin_int(_))
         ; CtorCat = ctor_cat_builtin(cat_builtin_char)
         ; CtorCat = ctor_cat_builtin(cat_builtin_float)
         ; CtorCat = ctor_cat_builtin_dummy
diff --git a/compiler/ml_call_gen.m b/compiler/ml_call_gen.m
index 932a1c5fb..1c82ec4c4 100644
--- a/compiler/ml_call_gen.m
+++ b/compiler/ml_call_gen.m
@@ -807,6 +807,12 @@ ml_gen_builtin(PredId, ProcId, ArgVars, CodeModel, Context, Decls, Stmts,
 ml_gen_simple_expr(leaf(Lval)) = ml_lval(Lval).
 ml_gen_simple_expr(int_const(Int)) = ml_const(mlconst_int(Int)).
 ml_gen_simple_expr(uint_const(UInt)) = ml_const(mlconst_uint(UInt)).
+ml_gen_simple_expr(int8_const(Int8)) = ml_const(mlconst_int8(Int8)).
+ml_gen_simple_expr(uint8_const(UInt8)) = ml_const(mlconst_uint8(UInt8)).
+ml_gen_simple_expr(int16_const(Int16)) = ml_const(mlconst_int16(Int16)).
+ml_gen_simple_expr(uint16_const(UInt16)) = ml_const(mlconst_uint16(UInt16)).
+ml_gen_simple_expr(int32_const(Int32)) = ml_const(mlconst_int32(Int32)).
+ml_gen_simple_expr(uint32_const(UInt32)) = ml_const(mlconst_uint32(UInt32)).
 ml_gen_simple_expr(float_const(Float)) = ml_const(mlconst_float(Float)).
 ml_gen_simple_expr(unary(Op, Expr)) =
     ml_unop(std_unop(Op), ml_gen_simple_expr(Expr)).
diff --git a/compiler/ml_code_util.m b/compiler/ml_code_util.m
index 206a5b9de..637d79d2a 100644
--- a/compiler/ml_code_util.m
+++ b/compiler/ml_code_util.m
@@ -783,7 +783,7 @@ ml_string_type =
         non_foreign_type(string_type)).
 
 ml_int_type =
-    mercury_type(int_type, ctor_cat_builtin(cat_builtin_int),
+    mercury_type(int_type, ctor_cat_builtin(cat_builtin_int(int_type_int)),
         non_foreign_type(int_type)).
 
 ml_char_type =
@@ -1342,8 +1342,7 @@ ml_must_box_field_type(ModuleInfo, Type, Width) :-
 
 ml_must_box_field_type_category(CtorCat, UnboxedFloat, Width) = MustBox :-
     (
-        ( CtorCat = ctor_cat_builtin(cat_builtin_int)
-        ; CtorCat = ctor_cat_builtin(cat_builtin_uint)
+        ( CtorCat = ctor_cat_builtin(cat_builtin_int(_))
         ; CtorCat = ctor_cat_builtin(cat_builtin_string)
         ; CtorCat = ctor_cat_builtin_dummy
         ; CtorCat = ctor_cat_higher_order
diff --git a/compiler/ml_disj_gen.m b/compiler/ml_disj_gen.m
index 397fbf4f5..292c162e2 100644
--- a/compiler/ml_disj_gen.m
+++ b/compiler/ml_disj_gen.m
@@ -342,13 +342,15 @@ ml_gen_lookup_disj(OutVars, Solns, Context, Stmts, !Info) :-
 
     IncrSlotVarStmt = ml_stmt_atomic(
         assign(SlotVarLval,
-            ml_binop(int_add, SlotVarRval, ml_const(mlconst_int(1)))),
+            ml_binop(int_add(int_type_int), SlotVarRval,
+                ml_const(mlconst_int(1)))),
         Context),
 
     LoopBodyStmt = ml_stmt_block([],
         LookupStmts ++ [CallContStmt, IncrSlotVarStmt], Context),
 
-    LoopCond = ml_binop(int_lt, SlotVarRval, ml_const(mlconst_int(NumRows))),
+    LoopCond = ml_binop(int_lt(int_type_int), SlotVarRval,
+        ml_const(mlconst_int(NumRows))),
     LoopStmt = ml_stmt_while(loop_at_least_once, LoopCond, LoopBodyStmt,
         Context),
 
diff --git a/compiler/ml_foreign_proc_gen.m b/compiler/ml_foreign_proc_gen.m
index 1c7daf6a7..172e91c7e 100644
--- a/compiler/ml_foreign_proc_gen.m
+++ b/compiler/ml_foreign_proc_gen.m
@@ -79,7 +79,7 @@ ml_generate_runtime_cond_code(Expr, CondRval, !Info) :-
         ml_gen_info_add_env_var_name(EnvVar, !Info),
         EnvVarRval = ml_lval(ml_global_var_ref(env_var_ref(EnvVar))),
         ZeroRval = ml_const(mlconst_int(0)),
-        CondRval = ml_binop(ne, EnvVarRval, ZeroRval)
+        CondRval = ml_binop(ne(int_type_int), EnvVarRval, ZeroRval)
     ;
         Expr = trace_not(ExprA),
         ml_generate_runtime_cond_code(ExprA, RvalA, !Info),
diff --git a/compiler/ml_global_data.m b/compiler/ml_global_data.m
index 66ab01d03..fb5327e06 100644
--- a/compiler/ml_global_data.m
+++ b/compiler/ml_global_data.m
@@ -558,20 +558,20 @@ ml_specialize_generic_array_rval(!Rval) :-
 
 ml_specialize_generic_array_binop(Op, IsFloat) :-
     (
-        ( Op = int_add
-        ; Op = int_sub
-        ; Op = int_mul
-        ; Op = int_div
-        ; Op = int_mod
-        ; Op = unchecked_left_shift
-        ; Op = unchecked_right_shift
-        ; Op = bitwise_and
-        ; Op = bitwise_or
-        ; Op = bitwise_xor
+        ( Op = int_add(_)
+        ; Op = int_sub(_)
+        ; Op = int_mul(_)
+        ; Op = int_div(_)
+        ; Op = int_mod(_)
+        ; Op = unchecked_left_shift(_)
+        ; Op = unchecked_right_shift(_)
+        ; Op = bitwise_and(_)
+        ; Op = bitwise_or(_)
+        ; Op = bitwise_xor(_)
         ; Op = logical_and
         ; Op = logical_or
-        ; Op = eq
-        ; Op = ne
+        ; Op = eq(_)
+        ; Op = ne(_)
         ; Op = offset_str_eq(_)
         ; Op = str_eq
         ; Op = str_ne
@@ -580,27 +580,11 @@ ml_specialize_generic_array_binop(Op, IsFloat) :-
         ; Op = str_le
         ; Op = str_ge
         ; Op = str_cmp
-        ; Op = int_lt
-        ; Op = int_gt
-        ; Op = int_le
-        ; Op = int_ge
+        ; Op = int_lt(_)
+        ; Op = int_gt(_)
+        ; Op = int_le(_)
+        ; Op = int_ge(_)
         ; Op = unsigned_le
-        ; Op = uint_eq
-        ; Op = uint_ne
-        ; Op = uint_lt
-        ; Op = uint_gt
-        ; Op = uint_le
-        ; Op = uint_ge
-        ; Op = uint_add
-        ; Op = uint_sub
-        ; Op = uint_mul
-        ; Op = uint_div
-        ; Op = uint_mod
-        ; Op = uint_bitwise_and
-        ; Op = uint_bitwise_or
-        ; Op = uint_bitwise_xor
-        ; Op = uint_unchecked_left_shift
-        ; Op = uint_unchecked_right_shift
         ; Op = float_eq
         ; Op = float_ne
         ; Op = float_lt
@@ -807,6 +791,12 @@ cons_id_to_alloc_site_string(ConsId) = TypeStr :-
     ;
         ( ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
diff --git a/compiler/ml_lookup_switch.m b/compiler/ml_lookup_switch.m
index 96b3d19d6..0aada5377 100644
--- a/compiler/ml_lookup_switch.m
+++ b/compiler/ml_lookup_switch.m
@@ -266,7 +266,7 @@ ml_gen_atomic_lookup_switch(SwitchVar, TaggedCases, LookupSwitchInfo,
         IndexRval = SwitchVarRval
     else
         StartRval = ml_const(mlconst_int(StartVal)),
-        IndexRval = ml_binop(int_sub, SwitchVarRval, StartRval)
+        IndexRval = ml_binop(int_sub(int_type_int), SwitchVarRval, StartRval)
     ),
     (
         CaseIdConstMap = all_one_soln(CaseIdValueMap),
@@ -510,7 +510,8 @@ ml_gen_several_soln_lookup_code(Context, SlotVarRval,
     LaterLookupSucceedStmt = ml_stmt_block([],
         LaterSolnLookupStmts ++ [CallContStmt, IncrLaterSlotVarStmt], Context),
 
-    MoreSolnsLoopCond = ml_binop(int_lt, LaterSlotVarRval, LimitVarRval),
+    MoreSolnsLoopCond = ml_binop(int_lt(int_type_int),
+        LaterSlotVarRval, LimitVarRval),
     MoreSolnsLoopStmt = ml_stmt_while(may_loop_zero_times, MoreSolnsLoopCond,
         LaterLookupSucceedStmt, Context),
 
@@ -524,7 +525,7 @@ ml_gen_several_soln_lookup_code(Context, SlotVarRval,
         OneOrMoreSolnsBlockStmt =
             ml_stmt_block([], OneOrMoreSolnsStmts, Context),
 
-        AnySolnsCond = ml_binop(int_ge,
+        AnySolnsCond = ml_binop(int_ge(int_type_int),
             NumLaterSolnsVarRval, ml_const(mlconst_int(0))),
         ZeroOrMoreSolnsStmt = ml_stmt_if_then_else(AnySolnsCond,
             OneOrMoreSolnsBlockStmt, no, Context),
@@ -560,10 +561,11 @@ make_several_soln_lookup_vars(Context, SeveralSolnLookupVars, !Info) :-
     LaterSlotVarRval = ml_lval(LaterSlotVarLval),
     NumLaterSolnsVarRval = ml_lval(NumLaterSolnsVarLval),
     LimitAssign = assign(LimitVarLval,
-        ml_binop(int_add, LaterSlotVarRval, NumLaterSolnsVarRval)),
+        ml_binop(int_add(int_type_int), LaterSlotVarRval, NumLaterSolnsVarRval)),
     LimitAssignStmt = ml_stmt_atomic(LimitAssign, Context),
     IncrLaterSlotVar = assign(LaterSlotVarLval,
-        ml_binop(int_add, LaterSlotVarRval, ml_const(mlconst_int(1)))),
+        ml_binop(int_add(int_type_int), LaterSlotVarRval,
+            ml_const(mlconst_int(1)))),
     IncrLaterSlotVarStmt = ml_stmt_atomic(IncrLaterSlotVar, Context),
 
     SeveralSolnLookupVars = ml_several_soln_lookup_vars(NumLaterSolnsVarLval,
@@ -605,7 +607,7 @@ ml_generate_bitvec_test(MLDS_ModuleName, Context, IndexRval, CaseVals,
         % WordNumRval = ml_binop(int_div, IndexRval,
         %   ml_const(mlconst_int(WordBits)))
         % except that it can generate more efficient code.
-        WordNumRval = ml_binop(unchecked_right_shift, IndexRval,
+        WordNumRval = ml_binop(unchecked_right_shift(int_type_int), IndexRval,
             ml_const(mlconst_int(Log2WordBits))),
 
         ArrayElemType = array_elem_scalar(scalar_elem_int),
@@ -616,11 +618,12 @@ ml_generate_bitvec_test(MLDS_ModuleName, Context, IndexRval, CaseVals,
         % BitNumRval = ml_binop(int_mod, IndexRval,
         %   ml_const(mlconst_int(WordBits)))
         % except that it can generate more efficient code.
-        BitNumRval = ml_binop(bitwise_and, IndexRval,
+        BitNumRval = ml_binop(bitwise_and(int_type_int), IndexRval,
             ml_const(mlconst_int(WordBits - 1)))
     ),
-    CheckRval = ml_binop(bitwise_and, WordRval,
-        ml_binop(unchecked_left_shift, ml_const(mlconst_int(1)), BitNumRval)).
+    CheckRval = ml_binop(bitwise_and(int_type_int), WordRval,
+        ml_binop(unchecked_left_shift(int_type_int),
+            ml_const(mlconst_int(1)), BitNumRval)).
 
     % We generate the bitvector by iterating through the cases marking the bit
     % for each case. We represent the bitvector here as a map from the word
diff --git a/compiler/ml_simplify_switch.m b/compiler/ml_simplify_switch.m
index 7100f71ec..4995b11b7 100644
--- a/compiler/ml_simplify_switch.m
+++ b/compiler/ml_simplify_switch.m
@@ -150,8 +150,7 @@ is_integral_type(MLDSType) = IsIntegral :-
     ;
         MLDSType = mercury_type(_, CtorCat, _),
         (
-            ( CtorCat = ctor_cat_builtin(cat_builtin_int)
-            ; CtorCat = ctor_cat_builtin(cat_builtin_uint)
+            ( CtorCat = ctor_cat_builtin(cat_builtin_int(_))
             ; CtorCat = ctor_cat_builtin(cat_builtin_char)
             ; CtorCat = ctor_cat_enum(cat_enum_mercury)
             ),
@@ -288,7 +287,8 @@ generate_dense_switch(Cases, Default, FirstVal, LastVal, NeedRangeCheck,
     ( if FirstVal = 0 then
         Index = Rval
     else
-        Index = ml_binop(int_sub, Rval, ml_const(mlconst_int(FirstVal)))
+        Index = ml_binop(int_sub(int_type_int), Rval,
+            ml_const(mlconst_int(FirstVal)))
     ),
 
     % Now generate the jump table.
@@ -500,11 +500,11 @@ ml_gen_case_match_conds([Cond1, Cond2 | Conds], SwitchRval) =
 :- func ml_gen_case_match_cond(mlds_case_match_cond, mlds_rval) = mlds_rval.
 
 ml_gen_case_match_cond(match_value(CaseRval), SwitchRval) =
-    ml_binop(eq, CaseRval, SwitchRval).
+    ml_binop(eq(int_type_int), CaseRval, SwitchRval).
 ml_gen_case_match_cond(match_range(MinRval, MaxRval), SwitchRval) =
     ml_binop(logical_and,
-        ml_binop(int_gt, SwitchRval, MinRval),
-        ml_binop(int_le, SwitchRval, MaxRval)).
+        ml_binop(int_gt(int_type_int), SwitchRval, MinRval),
+        ml_binop(int_le(int_type_int), SwitchRval, MaxRval)).
 
 %-----------------------------------------------------------------------------%
 :- end_module ml_backend.ml_simplify_switch.
diff --git a/compiler/ml_string_switch.m b/compiler/ml_string_switch.m
index 5fdd2f27d..f7b6cff86 100644
--- a/compiler/ml_string_switch.m
+++ b/compiler/ml_string_switch.m
@@ -269,8 +269,8 @@ ml_generate_string_trie_simple_lookup_switch(MaxCaseNum,
             FailStmts = [_, _ | _],
             FailStmt = ml_stmt_block([], FailStmts, Context)
         ),
-        IsCaseNumNegCond = ml_binop(int_lt, ml_lval(CaseNumVarLval),
-            ml_const(mlconst_int(0))),
+        IsCaseNumNegCond = ml_binop(int_lt(int_type_int),
+            ml_lval(CaseNumVarLval), ml_const(mlconst_int(0))),
         ResultStmt = ml_stmt_if_then_else(IsCaseNumNegCond, FailStmt,
             yes(LookupStmt), Context)
     ),
@@ -362,8 +362,8 @@ ml_generate_string_trie_several_soln_lookup_switch(MaxCaseNum,
         SuccessStmts, Context),
     (
         CanFail = can_fail,
-        IsCaseNumNonNegCond = ml_binop(int_ge, ml_lval(CaseNumVarLval),
-            ml_const(mlconst_int(0))),
+        IsCaseNumNonNegCond = ml_binop(int_ge(int_type_int),
+            ml_lval(CaseNumVarLval), ml_const(mlconst_int(0))),
         ResultStmt = ml_stmt_if_then_else(IsCaseNumNonNegCond,
             SuccessBlockStmt, no, Context)
     ;
@@ -620,7 +620,8 @@ convert_trie_to_nested_switches(Encoding, VarRval, CaseNumVarLval, Context,
         then
             OneChoicePair = OneCodeUnit - OneSubTrieNode,
             OneCodeUnitConst = ml_const(mlconst_int(OneCodeUnit)),
-            FirstCond = ml_binop(eq, CurCodeUnitRval, OneCodeUnitConst),
+            FirstCond = ml_binop(eq(int_type_int),
+                CurCodeUnitRval, OneCodeUnitConst),
             chase_one_cond_trie_nodes(Encoding, VarRval, CaseNumVarLval,
                 Context, NumMatched + 1, OneSubTrieNode, FirstCond, AllCond,
                 ThenStmt),
@@ -708,7 +709,8 @@ chase_one_cond_trie_nodes(Encoding, VarRval, CaseNumVarLval, Context,
         CurCodeUnitRval = ml_binop(string_unsafe_index_code_unit,
             VarRval, ml_const(mlconst_int(NumMatched))),
         OneCodeUnitConst = ml_const(mlconst_int(OneCodeUnit)),
-        CurCond = ml_binop(eq, CurCodeUnitRval, OneCodeUnitConst),
+        CurCond = ml_binop(eq(int_type_int), CurCodeUnitRval,
+            OneCodeUnitConst),
         RevCond1 = ml_binop(logical_and, RevCond0, CurCond),
         chase_one_cond_trie_nodes(Encoding, VarRval, CaseNumVarLval, Context,
             NumMatched + 1, OneSubTrieNode, RevCond1, RevCond, ThenStmt)
@@ -1445,14 +1447,15 @@ ml_gen_string_hash_switch_search(InitialComment,
         ml_stmt_atomic(comment("compute the hash value of the input string"),
             Context),
         ml_stmt_atomic(assign(SlotVarLval,
-            ml_binop(bitwise_and,
+            ml_binop(bitwise_and(int_type_int),
                 ml_unop(std_unop(HashOp), VarRval),
                 ml_const(mlconst_int(HashMask)))),
             Context)
         ],
     FoundMatchCond =
         ml_binop(logical_and,
-            ml_binop(ne, StringVarRval, ml_const(mlconst_null(StringVarType))),
+            ml_binop(ne(int_type_int), StringVarRval,
+                ml_const(mlconst_null(StringVarType))),
             ml_binop(str_eq, StringVarRval, VarRval)
         ),
     LookForMatchPrepareStmts = [
@@ -1465,7 +1468,8 @@ ml_gen_string_hash_switch_search(InitialComment,
             Context),
         ml_stmt_atomic(comment("did we find a match?"), Context)
     ],
-    SlotTest = ml_binop(int_ge, SlotVarRval, ml_const(mlconst_int(0))),
+    SlotTest = ml_binop(int_ge(int_type_int), SlotVarRval,
+        ml_const(mlconst_int(0))),
     (
         MaybeStopLoopVarLval = no,
         InitStopLoopVarStmts = [],
@@ -1495,7 +1499,7 @@ ml_gen_string_hash_switch_search(InitialComment,
             % the success continuation for each solution.
             InitSuccessStmts = []
         ),
-        StopLoopTest = ml_binop(eq,
+        StopLoopTest = ml_binop(eq(int_type_int),
             ml_lval(StopLoopVarLval), ml_const(mlconst_int(0))),
         LoopTest = ml_binop(logical_and, StopLoopTest, SlotTest)
     ),
@@ -1975,12 +1979,12 @@ ml_gen_string_binary_switch_search(Context, InitialComment,
     InitHiVarStmt = ml_stmt_atomic(
         assign(HiVarLval, ml_const(mlconst_int(TableSize - 1))),
         Context),
-    CrossingTest = ml_binop(int_le, LoVarRval, HiVarRval),
+    CrossingTest = ml_binop(int_le(int_type_int), LoVarRval, HiVarRval),
 
     AssignMidVarStmt = ml_stmt_atomic(
         assign(MidVarLval,
-            ml_binop(int_div,
-                ml_binop(int_add, LoVarRval, HiVarRval),
+            ml_binop(int_div(int_type_int),
+                ml_binop(int_add(int_type_int), LoVarRval, HiVarRval),
                 ml_const(mlconst_int(2)))),
         Context),
     AssignResultVarStmt = ml_stmt_atomic(
@@ -1991,17 +1995,21 @@ ml_gen_string_binary_switch_search(Context, InitialComment,
                     ml_vector_common_row_addr(VectorCommon, MidVarRval),
                 StringFieldId, MLDS_StringType, StructType)))),
         Context),
-    ResultTest = ml_binop(eq, ResultVarRval, ml_const(mlconst_int(0))),
+    ResultTest = ml_binop(eq(int_type_int), ResultVarRval,
+        ml_const(mlconst_int(0))),
     UpdateLoOrHiVarStmt =
         ml_stmt_if_then_else(
-            ml_binop(int_lt, ResultVarRval, ml_const(mlconst_int(0))),
+            ml_binop(int_lt(int_type_int), ResultVarRval,
+                ml_const(mlconst_int(0))),
             ml_stmt_atomic(
                 assign(HiVarLval,
-                    ml_binop(int_sub, MidVarRval, ml_const(mlconst_int(1)))),
+                    ml_binop(int_sub(int_type_int), MidVarRval,
+                        ml_const(mlconst_int(1)))),
                 Context),
             yes(ml_stmt_atomic(
                 assign(LoVarLval,
-                    ml_binop(int_add, MidVarRval, ml_const(mlconst_int(1)))),
+                    ml_binop(int_add(int_type_int), MidVarRval,
+                        ml_const(mlconst_int(1)))),
                 Context)),
             Context),
 
@@ -2026,7 +2034,7 @@ ml_gen_string_binary_switch_search(Context, InitialComment,
         InitStopLoopVarStmt = ml_stmt_atomic(
             assign(StopLoopVarLval, ml_const(mlconst_int(0))),
             Context),
-        StopLoopTest = ml_binop(eq,
+        StopLoopTest = ml_binop(eq(int_type_int),
             ml_lval(StopLoopVarLval), ml_const(mlconst_int(0))),
         LoopBodyStmts = [
             AssignMidVarStmt,
@@ -2253,7 +2261,7 @@ ml_wrap_loop_break(CodeModel, LoopPresent, Context, MaybeStopLoopVarLval,
                 OnlyFailAfterStmt =
                     ml_stmt_block([], OnlyFailAfterStmts, Context)
             ),
-            SuccessTest = ml_binop(eq,
+            SuccessTest = ml_binop(eq(int_type_int),
                 ml_lval(StopLoopVarLval),
                 ml_const(mlconst_int(0))),
             AfterStmt =
diff --git a/compiler/ml_switch_gen.m b/compiler/ml_switch_gen.m
index 7522f4531..a2d9aec21 100644
--- a/compiler/ml_switch_gen.m
+++ b/compiler/ml_switch_gen.m
@@ -602,6 +602,24 @@ ml_tagged_cons_id_to_match_cond(MLDS_Type, TaggedConsId, MatchCond) :-
         Tag = uint_tag(UInt),
         Rval = ml_const(mlconst_uint(UInt))
     ;
+        Tag = int8_tag(Int8),
+        Rval = ml_const(mlconst_int8(Int8))
+    ;
+        Tag = uint8_tag(UInt8),
+        Rval = ml_const(mlconst_uint8(UInt8))
+    ;
+        Tag = int16_tag(Int16),
+        Rval = ml_const(mlconst_int16(Int16))
+    ;
+        Tag = uint16_tag(UInt16),
+        Rval = ml_const(mlconst_uint16(UInt16))
+    ;
+        Tag = int32_tag(Int32),
+        Rval = ml_const(mlconst_int32(Int32))
+    ;
+        Tag = uint32_tag(UInt32),
+        Rval = ml_const(mlconst_uint32(UInt32))
+    ;
         Tag = string_tag(String),
         Rval = ml_const(mlconst_string(String))
     ;
diff --git a/compiler/ml_tailcall.m b/compiler/ml_tailcall.m
index 1dbebadd7..eb5d685ee 100644
--- a/compiler/ml_tailcall.m
+++ b/compiler/ml_tailcall.m
@@ -893,6 +893,12 @@ check_const(Const, Locals) = MayYieldDanglingStackRef :-
         ; Const = mlconst_false
         ; Const = mlconst_int(_)
         ; Const = mlconst_uint(_)
+        ; Const = mlconst_int8(_)
+        ; Const = mlconst_uint8(_)
+        ; Const = mlconst_int16(_)
+        ; Const = mlconst_uint16(_)
+        ; Const = mlconst_int32(_)
+        ; Const = mlconst_uint32(_)
         ; Const = mlconst_enum(_, _)
         ; Const = mlconst_char(_)
         ; Const = mlconst_foreign(_, _, _)
diff --git a/compiler/ml_type_gen.m b/compiler/ml_type_gen.m
index 11f5883db..ed41a6ac1 100644
--- a/compiler/ml_type_gen.m
+++ b/compiler/ml_type_gen.m
@@ -353,6 +353,12 @@ ml_gen_hld_enum_constant(Context, TypeCtor, ConsTagValues, MLDS_Type, Ctor)
             mlconst_foreign(ForeignLang, ForeignTagValue, MLDS_Type))
     ;
         ( TagVal = uint_tag(_)
+        ; TagVal = int8_tag(_)
+        ; TagVal = uint8_tag(_)
+        ; TagVal = int16_tag(_)
+        ; TagVal = uint16_tag(_)
+        ; TagVal = int32_tag(_)
+        ; TagVal = uint32_tag(_)
         ; TagVal = string_tag(_)
         ; TagVal = float_tag(_)
         ; TagVal = closure_tag(_, _, _)
@@ -1193,6 +1199,12 @@ ml_tag_uses_base_class(Tag) = UsesBaseClass :-
         ; Tag = float_tag(_)
         ; Tag = int_tag(_)
         ; Tag = uint_tag(_)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = foreign_tag(_, _)
         ; Tag = closure_tag(_, _, _)
         ; Tag = type_ctor_info_tag(_, _, _)
@@ -1260,6 +1272,12 @@ generate_foreign_enum_constant(TypeCtor, Mapping, TagValues, MLDS_Type, Ctor,
         ( TagVal = string_tag(_)
         ; TagVal = float_tag(_)
         ; TagVal = uint_tag(_)
+        ; TagVal = int8_tag(_)
+        ; TagVal = uint8_tag(_)
+        ; TagVal = int16_tag(_)
+        ; TagVal = uint16_tag(_)
+        ; TagVal = int32_tag(_)
+        ; TagVal = uint32_tag(_)
         ; TagVal = closure_tag(_, _, _)
         ; TagVal = type_ctor_info_tag(_, _, _)
         ; TagVal = base_typeclass_info_tag(_, _, _)
diff --git a/compiler/ml_unify_gen.m b/compiler/ml_unify_gen.m
index b4e7bd2fc..1ebee09f1 100644
--- a/compiler/ml_unify_gen.m
+++ b/compiler/ml_unify_gen.m
@@ -203,12 +203,15 @@ ml_gen_unification(Unification, CodeModel, Context, Stmts, !Info) :-
         Unification = simple_test(VarA, VarB),
         expect(unify(CodeModel, model_semi), $pred, "simple_test not semidet"),
         ml_variable_type(!.Info, VarA, Type),
+        % XXX this should be a switch.
         ( if Type = builtin_type(builtin_type_string) then
             EqualityOp = str_eq
         else if Type = builtin_type(builtin_type_float) then
             EqualityOp = float_eq
+        else if Type = builtin_type(builtin_type_int(IntType)) then
+            EqualityOp = eq(IntType)
         else
-            EqualityOp = eq
+            EqualityOp = eq(int_type_int)
         ),
         ml_gen_var(!.Info, VarA, VarALval),
         ml_gen_var(!.Info, VarB, VarBLval),
@@ -399,6 +402,12 @@ ml_gen_construct_tag(Tag, Type, Var, ConsId, Args, ArgModes, TakeAddr,
         % Constants.
         ( Tag = int_tag(_)
         ; Tag = uint_tag(_)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = foreign_tag(_, _)
         ; Tag = float_tag(_)
         ; Tag = string_tag(_)
@@ -452,6 +461,24 @@ ml_gen_constant(Tag, VarType, MLDS_VarType, Rval, !Info) :-
         Tag = uint_tag(UInt),
         Rval = ml_const(mlconst_uint(UInt))
     ;
+        Tag = int8_tag(Int8),
+        Rval = ml_const(mlconst_int8(Int8))
+    ;
+        Tag = uint8_tag(UInt8),
+        Rval = ml_const(mlconst_uint8(UInt8))
+    ;
+        Tag = int16_tag(Int16),
+        Rval = ml_const(mlconst_int16(Int16))
+    ;
+        Tag = uint16_tag(UInt16),
+        Rval = ml_const(mlconst_uint16(UInt16))
+    ;
+        Tag = int32_tag(Int32),
+        Rval = ml_const(mlconst_int32(Int32))
+    ;
+        Tag = uint32_tag(UInt32),
+        Rval = ml_const(mlconst_uint32(UInt32))
+    ;
         Tag = float_tag(Float),
         Rval = ml_const(mlconst_float(Float))
     ;
@@ -1470,6 +1497,12 @@ ml_gen_det_deconstruct_tag(Tag, Type, Var, ConsId, Args, Modes, Context,
         ( Tag = string_tag(_String)
         ; Tag = int_tag(_Int)
         ; Tag = uint_tag(_UInt)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = foreign_tag(_, _)
         ; Tag = float_tag(_Float)
         ; Tag = shared_local_tag(_Bits1, _Num1)
@@ -1575,6 +1608,12 @@ ml_tag_offset_and_argnum(Tag, TagBits, Offset, ArgNum) :-
         ( Tag = string_tag(_String)
         ; Tag = int_tag(_Int)
         ; Tag = uint_tag(_)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = foreign_tag(_, _)
         ; Tag = float_tag(_Float)
         ; Tag = closure_tag(_, _, _)
@@ -2195,15 +2234,40 @@ ml_gen_tag_test_rval(Tag, Type, ModuleInfo, Rval) = TagTestRval :-
             MLDS_Type = mercury_type_to_mlds_type(ModuleInfo, Type),
             ConstRval = ml_const(mlconst_enum(Int, MLDS_Type))
         ),
-        TagTestRval = ml_binop(eq, Rval, ConstRval)
+        TagTestRval = ml_binop(eq(int_type_int), Rval, ConstRval)
     ;
         Tag = uint_tag(UInt),
-        TagTestRval = ml_binop(uint_eq, Rval, ml_const(mlconst_uint(UInt)))
+        TagTestRval = ml_binop(eq(int_type_uint), Rval,
+            ml_const(mlconst_uint(UInt)))
+    ;
+        Tag = int8_tag(Int8),
+        TagTestRval = ml_binop(eq(int_type_int8), Rval,
+            ml_const(mlconst_int8(Int8)))
+    ;
+        Tag = uint8_tag(UInt8),
+        TagTestRval = ml_binop(eq(int_type_uint8), Rval,
+            ml_const(mlconst_uint8(UInt8)))
+    ;
+        Tag = int16_tag(Int16),
+        TagTestRval = ml_binop(eq(int_type_int16), Rval,
+            ml_const(mlconst_int16(Int16)))
+    ;
+        Tag = uint16_tag(UInt16),
+        TagTestRval = ml_binop(eq(int_type_uint16), Rval,
+            ml_const(mlconst_uint16(UInt16)))
+    ;
+        Tag = int32_tag(Int32),
+        TagTestRval = ml_binop(eq(int_type_int32), Rval,
+            ml_const(mlconst_int32(Int32)))
+    ;
+        Tag = uint32_tag(UInt32),
+        TagTestRval = ml_binop(eq(int_type_uint32), Rval,
+            ml_const(mlconst_uint32(UInt32)))
     ;
         Tag = foreign_tag(ForeignLang, ForeignVal),
         MLDS_Type = mercury_type_to_mlds_type(ModuleInfo, Type),
         Const = ml_const(mlconst_foreign(ForeignLang, ForeignVal, MLDS_Type)),
-        TagTestRval = ml_binop(eq, Rval, Const)
+        TagTestRval = ml_binop(eq(int_type_int), Rval, Const)
     ;
         ( Tag = closure_tag(_, _, _)
         ; Tag = type_ctor_info_tag(_, _, _)
@@ -2229,13 +2293,13 @@ ml_gen_tag_test_rval(Tag, Type, ModuleInfo, Rval) = TagTestRval :-
         RvalTag = ml_unop(std_unop(tag), Rval),
         UnsharedTag = ml_unop(std_unop(mktag),
             ml_const(mlconst_int(UnsharedTagNum))),
-        TagTestRval = ml_binop(eq, RvalTag, UnsharedTag)
+        TagTestRval = ml_binop(eq(int_type_int), RvalTag, UnsharedTag)
     ;
         Tag = shared_remote_tag(PrimaryTagNum, SecondaryTagNum),
         SecondaryTagField = ml_gen_secondary_tag_rval(ModuleInfo,
             PrimaryTagNum, Type, Rval),
-        SecondaryTagTestRval = ml_binop(eq, SecondaryTagField,
-            ml_const(mlconst_int(SecondaryTagNum))),
+        SecondaryTagTestRval = ml_binop(eq(int_type_int),
+            SecondaryTagField, ml_const(mlconst_int(SecondaryTagNum))),
         module_info_get_globals(ModuleInfo, Globals),
         globals.lookup_int_option(Globals, num_tag_bits, NumTagBits),
         ( if NumTagBits = 0 then
@@ -2245,14 +2309,15 @@ ml_gen_tag_test_rval(Tag, Type, ModuleInfo, Rval) = TagTestRval :-
             RvalPTag = ml_unop(std_unop(tag), Rval),
             PrimaryTagRval = ml_unop(std_unop(mktag),
                 ml_const(mlconst_int(PrimaryTagNum))),
-            PrimaryTagTestRval = ml_binop(eq, RvalPTag, PrimaryTagRval),
+            PrimaryTagTestRval = ml_binop(eq(int_type_int), RvalPTag,
+                PrimaryTagRval),
             TagTestRval = ml_binop(logical_and,
                 PrimaryTagTestRval, SecondaryTagTestRval)
         )
     ;
         Tag = shared_local_tag(Bits, Num),
         MLDS_Type = mercury_type_to_mlds_type(ModuleInfo, Type),
-        TagTestRval = ml_binop(eq, Rval,
+        TagTestRval = ml_binop(eq(int_type_int), Rval,
             ml_unop(cast(MLDS_Type),
                 ml_mkword(Bits,
                     ml_unop(std_unop(mkbody), ml_const(mlconst_int(Num))))))
@@ -2261,7 +2326,7 @@ ml_gen_tag_test_rval(Tag, Type, ModuleInfo, Rval) = TagTestRval :-
         MLDS_Type = mercury_type_to_mlds_type(ModuleInfo, Type),
         ReservedAddrRval = ml_gen_reserved_address(ModuleInfo, ReservedAddr,
             MLDS_Type),
-        TagTestRval = ml_binop(eq, Rval, ReservedAddrRval)
+        TagTestRval = ml_binop(eq(int_type_int), Rval, ReservedAddrRval)
     ;
         Tag = shared_with_reserved_addresses_tag(ReservedAddrs, ThisTag),
         % We first check that the Rval doesn't match any of the ReservedAddrs,
@@ -2501,6 +2566,24 @@ ml_gen_ground_term_conjunct_tag(ModuleInfo, Target, HighLevelData, VarTypes,
             ConsTag = uint_tag(UInt),
             ConstRval = ml_const(mlconst_uint(UInt))
         ;
+            ConsTag = int8_tag(Int8),
+            ConstRval = ml_const(mlconst_int8(Int8))
+        ;
+            ConsTag = uint8_tag(UInt8),
+            ConstRval = ml_const(mlconst_uint8(UInt8))
+        ;
+            ConsTag = int16_tag(Int16),
+            ConstRval = ml_const(mlconst_int16(Int16))
+        ;
+            ConsTag = uint16_tag(UInt16),
+            ConstRval = ml_const(mlconst_uint16(UInt16))
+        ;
+            ConsTag = int32_tag(Int32),
+            ConstRval = ml_const(mlconst_int32(Int32))
+        ;
+            ConsTag = uint32_tag(UInt32),
+            ConstRval = ml_const(mlconst_uint32(UInt32))
+        ;
             ConsTag = float_tag(Float),
             ConstRval = ml_const(mlconst_float(Float))
         ;
@@ -2895,6 +2978,12 @@ ml_gen_const_struct_tag(Info, ConstNum, Type, MLDS_Type, ConsId, ConsTag,
         % These tags don't build heap cells.
         ( ConsTag = int_tag(_)
         ; ConsTag = uint_tag(_)
+        ; ConsTag = int8_tag(_)
+        ; ConsTag = uint8_tag(_)
+        ; ConsTag = int16_tag(_)
+        ; ConsTag = uint16_tag(_)
+        ; ConsTag = int32_tag(_)
+        ; ConsTag = uint32_tag(_)
         ; ConsTag = float_tag(_)
         ; ConsTag = string_tag(_)
         ; ConsTag = reserved_address_tag(_)
@@ -3075,6 +3164,24 @@ ml_gen_const_struct_arg_tag(ModuleInfo, ConsId, ConsTag, Type, MLDS_Type,
         ConsTag = uint_tag(UInt),
         Rval = ml_const(mlconst_uint(UInt))
     ;
+        ConsTag = int8_tag(Int8),
+        Rval = ml_const(mlconst_int8(Int8))
+    ;
+        ConsTag = uint8_tag(UInt8),
+        Rval = ml_const(mlconst_uint8(UInt8))
+    ;
+        ConsTag = int16_tag(Int16),
+        Rval = ml_const(mlconst_int16(Int16))
+    ;
+        ConsTag = uint16_tag(UInt16),
+        Rval = ml_const(mlconst_uint16(UInt16))
+    ;
+        ConsTag = int32_tag(Int32),
+        Rval = ml_const(mlconst_int32(Int32))
+    ;
+        ConsTag = uint32_tag(UInt32),
+        Rval = ml_const(mlconst_uint32(UInt32))
+    ;
         ConsTag = float_tag(Float),
         Rval = ml_const(mlconst_float(Float))
     ;
@@ -3225,11 +3332,11 @@ ml_lshift(Rval0, Shift) = Rval :-
     else if Shift = 0 then
         Rval = Rval0
     else if Rval0 = ml_unop(box(Type), Rval1) then
-        Rval2 = ml_binop(unchecked_left_shift, Rval1,
+        Rval2 = ml_binop(unchecked_left_shift(int_type_int), Rval1,
             ml_const(mlconst_int(Shift))),
         Rval = ml_unop(box(Type), Rval2)
     else
-        Rval = ml_binop(unchecked_left_shift, Rval0,
+        Rval = ml_binop(unchecked_left_shift(int_type_int), Rval0,
             ml_const(mlconst_int(Shift)))
     ).
 
@@ -3239,7 +3346,8 @@ ml_rshift(Rval, Shift) =
     ( if Shift = 0 then
         Rval
     else
-        ml_binop(unchecked_right_shift, Rval, ml_const(mlconst_int(Shift)))
+        ml_binop(unchecked_right_shift(int_type_int), Rval,
+            ml_const(mlconst_int(Shift)))
     ).
 
 :- func ml_bitwise_or(mlds_rval, mlds_rval) = mlds_rval.
@@ -3259,7 +3367,7 @@ ml_bitwise_or(RvalA, RvalB) = Rval :-
         else
             UnboxRvalB = RvalB
         ),
-        UnboxRval = ml_binop(bitwise_or, UnboxRvalA, UnboxRvalB),
+        UnboxRval = ml_binop(bitwise_or(int_type_int), UnboxRvalA, UnboxRvalB),
         (
             !.MaybeType = yes(BoxType),
             Rval = ml_unop(box(BoxType), UnboxRval)
@@ -3272,7 +3380,7 @@ ml_bitwise_or(RvalA, RvalB) = Rval :-
 :- func ml_bitwise_and(mlds_rval, int) = mlds_rval.
 
 ml_bitwise_and(Rval, Mask) =
-    ml_binop(bitwise_and, Rval, ml_const(mlconst_int(Mask))).
+    ml_binop(bitwise_and(int_type_int), Rval, ml_const(mlconst_int(Mask))).
 
 %-----------------------------------------------------------------------------%
 :- end_module ml_backend.ml_unify_gen.
diff --git a/compiler/ml_util.m b/compiler/ml_util.m
index 2954560d8..870520033 100644
--- a/compiler/ml_util.m
+++ b/compiler/ml_util.m
@@ -928,6 +928,12 @@ rval_contains_var(Rval, SearchVarName) = ContainsVar :-
             ; Const = mlconst_false
             ; Const = mlconst_int(_)
             ; Const = mlconst_uint(_)
+            ; Const = mlconst_int8(_)
+            ; Const = mlconst_uint8(_)
+            ; Const = mlconst_int16(_)
+            ; Const = mlconst_uint16(_)
+            ; Const = mlconst_int32(_)
+            ; Const = mlconst_uint32(_)
             ; Const = mlconst_enum(_, _)
             ; Const = mlconst_char(_)
             ; Const = mlconst_float(_)
@@ -1253,6 +1259,12 @@ method_ptrs_in_rval(Rval, !CodeAddrsInConsts) :-
             ; RvalConst = mlconst_false
             ; RvalConst = mlconst_int(_)
             ; RvalConst = mlconst_uint(_)
+            ; RvalConst = mlconst_int8(_)
+            ; RvalConst = mlconst_uint8(_)
+            ; RvalConst = mlconst_int16(_)
+            ; RvalConst = mlconst_uint16(_)
+            ; RvalConst = mlconst_int32(_)
+            ; RvalConst = mlconst_uint32(_)
             ; RvalConst = mlconst_char(_)
             ; RvalConst = mlconst_enum(_, _)
             ; RvalConst = mlconst_foreign(_, _, _)
diff --git a/compiler/mlds.m b/compiler/mlds.m
index 436a96c20..4aa1ed4a7 100644
--- a/compiler/mlds.m
+++ b/compiler/mlds.m
@@ -1790,6 +1790,12 @@
     ;       mlconst_false
     ;       mlconst_int(int)
     ;       mlconst_uint(uint)
+    ;       mlconst_int8(int)
+    ;       mlconst_uint8(int)
+    ;       mlconst_int16(int)
+    ;       mlconst_uint16(int)
+    ;       mlconst_int32(int)
+    ;       mlconst_uint32(int)
     ;       mlconst_enum(int, mlds_type)
     ;       mlconst_char(int)
     ;       mlconst_float(float)
diff --git a/compiler/mlds_to_c.m b/compiler/mlds_to_c.m
index dce79f11e..22a7a2b1d 100644
--- a/compiler/mlds_to_c.m
+++ b/compiler/mlds_to_c.m
@@ -2915,12 +2915,30 @@ mlds_output_mercury_type_prefix(Opts, Type, CtorCat, !IO) :-
         CtorCat = ctor_cat_builtin(cat_builtin_char),
         io.write_string("MR_Char", !IO)
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_int),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int)),
         io.write_string("MR_Integer", !IO)
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_uint),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint)),
         io.write_string("MR_Unsigned", !IO)
     ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int8)),
+        io.write_string("int8_t", !IO)
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint8)),
+        io.write_string("uint8_t", !IO)
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int16)),
+        io.write_string("int16_t", !IO)
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint16)),
+        io.write_string("uint16_t", !IO)
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int32)),
+        io.write_string("int32_t", !IO)
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint32)),
+        io.write_string("uint32_t", !IO)
+    ;
         CtorCat = ctor_cat_builtin(cat_builtin_string),
         io.write_string("MR_String", !IO)
     ;
@@ -4544,6 +4562,12 @@ is_an_address(Rval) = IsAddr :-
             ; Const = mlconst_multi_string(_)
             ; Const = mlconst_int(_)
             ; Const = mlconst_uint(_)
+            ; Const = mlconst_int8(_)
+            ; Const = mlconst_uint8(_)
+            ; Const = mlconst_int16(_)
+            ; Const = mlconst_uint16(_)
+            ; Const = mlconst_int32(_)
+            ; Const = mlconst_uint32(_)
             ; Const = mlconst_float(_)
             ; Const = mlconst_foreign(_, _, _)
             ),
@@ -4681,22 +4705,22 @@ mlds_output_binop(Opts, Op, X, Y, !IO) :-
         mlds_output_rval(Opts, Y, !IO),
         io.write_string("))", !IO)
     ;
-        ( Op = int_add, OpStr = "+"
-        ; Op = int_sub, OpStr = "-"
-        ; Op = int_mul, OpStr = "*"
-        ; Op = int_div, OpStr = "/"
-        ; Op = int_mod, OpStr = "%"
-        ; Op = eq, OpStr = "=="
-        ; Op = ne, OpStr = "!="
-        ; Op = int_lt, OpStr = "<"
-        ; Op = int_gt, OpStr = ">"
-        ; Op = int_le, OpStr = "<="
-        ; Op = int_ge, OpStr = ">="
-        ; Op = unchecked_left_shift, OpStr = "<<"
-        ; Op = unchecked_right_shift, OpStr = ">>"
-        ; Op = bitwise_and, OpStr = "&"
-        ; Op = bitwise_or, OpStr = "|"
-        ; Op = bitwise_xor, OpStr = "^"
+        ( Op = int_add(_), OpStr = "+"
+        ; Op = int_sub(_), OpStr = "-"
+        ; Op = int_mul(_), OpStr = "*"
+        ; Op = int_div(_), OpStr = "/"
+        ; Op = int_mod(_), OpStr = "%"
+        ; Op = eq(_), OpStr = "=="
+        ; Op = ne(_), OpStr = "!="
+        ; Op = int_lt(_), OpStr = "<"
+        ; Op = int_gt(_), OpStr = ">"
+        ; Op = int_le(_), OpStr = "<="
+        ; Op = int_ge(_), OpStr = ">="
+        ; Op = unchecked_left_shift(_), OpStr = "<<"
+        ; Op = unchecked_right_shift(_), OpStr = ">>"
+        ; Op = bitwise_and(_), OpStr = "&"
+        ; Op = bitwise_or(_), OpStr = "|"
+        ; Op = bitwise_xor(_), OpStr = "^"
         ; Op = logical_and, OpStr = "&&"
         ; Op = logical_or, OpStr = "||"
         ),
@@ -4710,31 +4734,6 @@ mlds_output_binop(Opts, Op, X, Y, !IO) :-
         mlds_output_rval_as_op_arg(Opts, Y, !IO),
         io.write_string(")", !IO)
     ;
-        ( Op = uint_eq, OpStr = "=="
-        ; Op = uint_ne, OpStr = "!="
-        ; Op = uint_lt, OpStr = "<"
-        ; Op = uint_gt, OpStr = ">"
-        ; Op = uint_le, OpStr = "<="
-        ; Op = uint_ge, OpStr = ">="
-        ; Op = uint_add, OpStr = "+"
-        ; Op = uint_sub, OpStr = "-"
-        ; Op = uint_mul, OpStr = "*"
-        ; Op = uint_div, OpStr = "/"
-        ; Op = uint_mod, OpStr = "%"
-        ; Op = uint_bitwise_and, OpStr = "&"
-        ; Op = uint_bitwise_or, OpStr = "|"
-        ; Op = uint_bitwise_xor, OpStr = "^"
-        ; Op = uint_unchecked_left_shift, OpStr = "<<"
-        ; Op = uint_unchecked_right_shift, OpStr = ">>"
-        ),
-        io.write_string("(", !IO),
-        mlds_output_rval_as_op_arg(Opts, X, !IO),
-        io.write_string(" ", !IO),
-        io.write_string(OpStr, !IO),
-        io.write_string(" ", !IO),
-        mlds_output_rval_as_op_arg(Opts, Y, !IO),
-        io.write_string(")", !IO)
-    ;
         Op = str_cmp,
         io.write_string("MR_strcmp(", !IO),
         mlds_output_rval_as_op_arg(Opts, X, !IO),
@@ -4799,6 +4798,24 @@ mlds_output_rval_const(_Opts, Const, !IO) :-
         Const = mlconst_uint(U),
         c_util.output_uint_expr_cur_stream(U, !IO)
     ;
+        Const = mlconst_int8(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = mlconst_uint8(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = mlconst_int16(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = mlconst_uint16(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = mlconst_int32(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
+        Const = mlconst_uint32(N),
+        c_util.output_int_expr_cur_stream(N, !IO)
+    ;
         Const = mlconst_char(C),
         io.write_string("(MR_Char) ", !IO),
         io.write_int(C, !IO)
diff --git a/compiler/mlds_to_cs.m b/compiler/mlds_to_cs.m
index b63593bde..494bcc309 100644
--- a/compiler/mlds_to_cs.m
+++ b/compiler/mlds_to_cs.m
@@ -1067,12 +1067,20 @@ get_type_initializer(Info, Type) = Initializer :-
     (
         Type = mercury_type(_, CtorCat, _),
         (
-            ( CtorCat = ctor_cat_builtin(cat_builtin_int)
+            ( CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int))
+            ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int8))
+            ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int16))
+            ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int32))
+            % C# byte and ushort literals don't have a suffix.
+            ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint8))
+            ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint16))
             ; CtorCat = ctor_cat_builtin(cat_builtin_float)
             ),
             Initializer = "0"
         ;
-            CtorCat = ctor_cat_builtin(cat_builtin_uint),
+            ( CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint))
+            ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint32))
+            ),
             Initializer = "0U"
         ;
             CtorCat = ctor_cat_builtin(cat_builtin_char),
@@ -1905,11 +1913,35 @@ mercury_type_to_string_for_csharp(Info, Type, CtorCat, String, ArrayDims) :-
         String = "int",
         ArrayDims = []
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_int),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int)),
+        String = "int",
+        ArrayDims = []
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint)),
+        String = "uint",
+        ArrayDims = []
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int8)),
+        String = "sbyte",
+        ArrayDims = []
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint8)),
+        String = "byte",
+        ArrayDims = []
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int16)),
+        String = "short",
+        ArrayDims = []
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint16)),
+        String = "ushort",
+        ArrayDims = []
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int32)),
         String = "int",
         ArrayDims = []
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_uint),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint32)),
         String = "uint",
         ArrayDims = []
     ;
@@ -2184,7 +2216,7 @@ output_per_instance_for_csharp(PerInstance, !IO) :-
     ).
 
 % :- pred output_virtuality_for_csharp(virtuality::in, io::di, io::uo) is det.
-% 
+%
 % output_virtuality_for_csharp(Virtual, !IO) :-
 %     (
 %         Virtual = virtual,
@@ -2217,7 +2249,7 @@ output_constness_for_csharp(Constness, !IO) :-
 
 % :- pred output_abstractness_for_csharp(abstractness::in,
 %     io::di, io::uo) is det.
-% 
+%
 % output_abstractness_for_csharp(Abstractness, !IO) :-
 %     (
 %         Abstractness = abstract,
@@ -3181,11 +3213,29 @@ csharp_builtin_type(Type, TargetType) :-
             MerType = builtin_type(BuiltinType),
             require_complete_switch [BuiltinType] (
                 ( BuiltinType = builtin_type_char
-                ; BuiltinType = builtin_type_int
+                ; BuiltinType = builtin_type_int(int_type_int)
                 ),
                 TargetType = "int"
             ;
-                BuiltinType = builtin_type_uint,
+                BuiltinType = builtin_type_int(int_type_uint),
+                TargetType = "uint"
+            ;
+                BuiltinType = builtin_type_int(int_type_int8),
+                TargetType = "sbyte"
+            ;
+                BuiltinType = builtin_type_int(int_type_uint8),
+                TargetType = "byte"
+            ;
+                BuiltinType = builtin_type_int(int_type_int16),
+                TargetType = "short"
+            ;
+                BuiltinType = builtin_type_int(int_type_uint16),
+                TargetType = "ushort"
+            ;
+                BuiltinType = builtin_type_int(int_type_int32),
+                TargetType = "int"
+            ;
+                BuiltinType = builtin_type_int(int_type_uint32),
                 TargetType = "uint"
             ;
                 BuiltinType = builtin_type_float,
@@ -3262,7 +3312,10 @@ output_std_unop_for_csharp(Info, UnaryOp, Expr, !IO) :-
         ; UnaryOp = strip_tag, UnaryOpStr = "/* strip_tag */ "
         ; UnaryOp = mkbody,    UnaryOpStr = "/* mkbody */ "
         ; UnaryOp = unmkbody,   UnaryOpStr = "/* unmkbody */ "
-        ; UnaryOp = bitwise_complement, UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_int), UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_uint), UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_int32), UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_uint32), UnaryOpStr = "~"
         ; UnaryOp = logical_not, UnaryOpStr = "!"
         ; UnaryOp = hash_string,  UnaryOpStr = "mercury.String.hash_1_f_0"
         ; UnaryOp = hash_string2, UnaryOpStr = "mercury.String.hash2_1_f_0"
@@ -3270,12 +3323,31 @@ output_std_unop_for_csharp(Info, UnaryOp, Expr, !IO) :-
         ; UnaryOp = hash_string4, UnaryOpStr = "mercury.String.hash4_1_f_0"
         ; UnaryOp = hash_string5, UnaryOpStr = "mercury.String.hash5_1_f_0"
         ; UnaryOp = hash_string6, UnaryOpStr = "mercury.String.hash6_1_f_0"
-        ; UnaryOp = uint_bitwise_complement, UnaryOpStr = "~"
         ),
         io.write_string(UnaryOpStr, !IO),
         io.write_string("(", !IO),
         output_rval_for_csharp(Info, Expr, !IO),
         io.write_string(")", !IO)
+    ;
+        (
+            UnaryOp = bitwise_complement(int_type_int8),
+            CastStr = "(sbyte)"
+        ;
+            UnaryOp = bitwise_complement(int_type_uint8),
+            CastStr = "(byte)"
+        ;
+            UnaryOp = bitwise_complement(int_type_int16),
+            CastStr = "(short)"
+        ;
+            UnaryOp = bitwise_complement(int_type_uint16),
+            CastStr = "(ushort)"
+        ),
+        UnaryOpStr = "~",
+        io.write_string(CastStr, !IO),
+        io.write_string(UnaryOpStr, !IO),
+        io.write_string("(", !IO),
+        output_rval_for_csharp(Info, Expr, !IO),
+        io.write_string(")", !IO)
     ).
 
 :- pred output_binop_for_csharp(csharp_out_info::in, binary_op::in,
@@ -3324,44 +3396,58 @@ output_binop_for_csharp(Info, Op, X, Y, !IO) :-
         io.write_string(")", !IO)
     ;
         % XXX Should we abort for some of these?
-        ( Op = int_add
-        ; Op = int_sub
-        ; Op = int_mul
-        ; Op = int_div
-        ; Op = int_mod
-        ; Op = unchecked_left_shift
-        ; Op = unchecked_right_shift
-        ; Op = bitwise_and
-        ; Op = bitwise_or
-        ; Op = bitwise_xor
+        ( Op = int_add(int_type_int)
+        ; Op = int_sub(int_type_int)
+        ; Op = int_mul(int_type_int)
+        ; Op = int_div(int_type_int)
+        ; Op = int_mod(int_type_int)
+        ; Op = unchecked_left_shift(int_type_int)
+        ; Op = unchecked_right_shift(int_type_int)
+        ; Op = bitwise_and(int_type_int)
+        ; Op = bitwise_or(int_type_int)
+        ; Op = bitwise_xor(int_type_int)
         ; Op = logical_and
         ; Op = logical_or
-        ; Op = eq
-        ; Op = ne
+        ; Op = eq(_)
+        ; Op = ne(_)
         ; Op = body
         ; Op = string_unsafe_index_code_unit
         ; Op = offset_str_eq(_)
-        ; Op = int_lt
-        ; Op = int_gt
-        ; Op = int_le
-        ; Op = int_ge
+        ; Op = int_lt(_)
+        ; Op = int_gt(_)
+        ; Op = int_le(_)
+        ; Op = int_ge(_)
         ; Op = unsigned_le
-        ; Op = uint_eq
-        ; Op = uint_ne
-        ; Op = uint_lt
-        ; Op = uint_gt
-        ; Op = uint_le
-        ; Op = uint_ge
-        ; Op = uint_add
-        ; Op = uint_sub
-        ; Op = uint_mul
-        ; Op = uint_div
-        ; Op = uint_mod
-        ; Op = uint_bitwise_and
-        ; Op = uint_bitwise_or
-        ; Op = uint_bitwise_xor
-        ; Op = uint_unchecked_left_shift
-        ; Op = uint_unchecked_right_shift
+        ; Op = int_add(int_type_uint)
+        ; Op = int_sub(int_type_uint)
+        ; Op = int_mul(int_type_uint)
+        ; Op = int_div(int_type_uint)
+        ; Op = int_mod(int_type_uint)
+        ; Op = bitwise_and(int_type_uint)
+        ; Op = bitwise_or(int_type_uint)
+        ; Op = bitwise_xor(int_type_uint)
+        ; Op = unchecked_left_shift(int_type_uint)
+        ; Op = unchecked_right_shift(int_type_uint)
+        ; Op = int_add(int_type_int32)
+        ; Op = int_sub(int_type_int32)
+        ; Op = int_mul(int_type_int32)
+        ; Op = int_div(int_type_int32)
+        ; Op = int_mod(int_type_int32)
+        ; Op = bitwise_and(int_type_int32)
+        ; Op = bitwise_or(int_type_int32)
+        ; Op = bitwise_xor(int_type_int32)
+        ; Op = unchecked_left_shift(int_type_int32)
+        ; Op = unchecked_right_shift(int_type_int32)
+        ; Op = int_add(int_type_uint32)
+        ; Op = int_sub(int_type_uint32)
+        ; Op = int_mul(int_type_uint32)
+        ; Op = int_div(int_type_uint32)
+        ; Op = int_mod(int_type_uint32)
+        ; Op = bitwise_and(int_type_uint32)
+        ; Op = bitwise_or(int_type_uint32)
+        ; Op = bitwise_xor(int_type_uint32)
+        ; Op = unchecked_left_shift(int_type_uint32)
+        ; Op = unchecked_right_shift(int_type_uint32)
         ; Op = float_plus
         ; Op = float_minus
         ; Op = float_times
@@ -3384,48 +3470,106 @@ output_binop_for_csharp(Info, Op, X, Y, !IO) :-
         io.write_string(" ", !IO),
         output_rval_for_csharp(Info, Y, !IO),
         io.write_string(")", !IO)
+    ;
+        ( Op = int_add(int_type_int8)
+        ; Op = int_sub(int_type_int8)
+        ; Op = int_mul(int_type_int8)
+        ; Op = int_div(int_type_int8)
+        ; Op = int_mod(int_type_int8)
+        ; Op = bitwise_and(int_type_int8)
+        ; Op = bitwise_or(int_type_int8)
+        ; Op = bitwise_xor(int_type_int8)
+        ; Op = unchecked_left_shift(int_type_int8)
+        ; Op = unchecked_right_shift(int_type_int8)
+        ),
+        io.write_string("(sbyte)(", !IO),
+        output_rval_for_csharp(Info, X, !IO),
+        io.write_string(" ", !IO),
+        output_binary_op_for_csharp(Op, !IO),
+        io.write_string(" ", !IO),
+        output_rval_for_csharp(Info, Y, !IO),
+        io.write_string(")", !IO)
+    ;
+        ( Op = int_add(int_type_uint8)
+        ; Op = int_sub(int_type_uint8)
+        ; Op = int_mul(int_type_uint8)
+        ; Op = int_div(int_type_uint8)
+        ; Op = int_mod(int_type_uint8)
+        ; Op = bitwise_and(int_type_uint8)
+        ; Op = bitwise_or(int_type_uint8)
+        ; Op = bitwise_xor(int_type_uint8)
+        ; Op = unchecked_left_shift(int_type_uint8)
+        ; Op = unchecked_right_shift(int_type_uint8)
+        ),
+        io.write_string("(byte)(", !IO),
+        output_rval_for_csharp(Info, X, !IO),
+        io.write_string(" ", !IO),
+        output_binary_op_for_csharp(Op, !IO),
+        io.write_string(" ", !IO),
+        output_rval_for_csharp(Info, Y, !IO),
+        io.write_string(")", !IO)
+    ;
+        ( Op = int_add(int_type_int16)
+        ; Op = int_sub(int_type_int16)
+        ; Op = int_mul(int_type_int16)
+        ; Op = int_div(int_type_int16)
+        ; Op = int_mod(int_type_int16)
+        ; Op = bitwise_and(int_type_int16)
+        ; Op = bitwise_or(int_type_int16)
+        ; Op = bitwise_xor(int_type_int16)
+        ; Op = unchecked_left_shift(int_type_int16)
+        ; Op = unchecked_right_shift(int_type_int16)
+        ),
+        io.write_string("(short)(", !IO),
+        output_rval_for_csharp(Info, X, !IO),
+        io.write_string(" ", !IO),
+        output_binary_op_for_csharp(Op, !IO),
+        io.write_string(" ", !IO),
+        output_rval_for_csharp(Info, Y, !IO),
+        io.write_string(")", !IO)
+    ;
+        ( Op = int_add(int_type_uint16)
+        ; Op = int_sub(int_type_uint16)
+        ; Op = int_mul(int_type_uint16)
+        ; Op = int_div(int_type_uint16)
+        ; Op = int_mod(int_type_uint16)
+        ; Op = bitwise_and(int_type_uint16)
+        ; Op = bitwise_or(int_type_uint16)
+        ; Op = bitwise_xor(int_type_uint16)
+        ; Op = unchecked_left_shift(int_type_uint16)
+        ; Op = unchecked_right_shift(int_type_uint16)
+        ),
+        io.write_string("(ushort)(", !IO),
+        output_rval_for_csharp(Info, X, !IO),
+        io.write_string(" ", !IO),
+        output_binary_op_for_csharp(Op, !IO),
+        io.write_string(" ", !IO),
+        output_rval_for_csharp(Info, Y, !IO),
+        io.write_string(")", !IO)
     ).
 
 :- pred output_binary_op_for_csharp(binary_op::in, io::di, io::uo) is det.
 
 output_binary_op_for_csharp(Op, !IO) :-
     (
-        ( Op = int_add, OpStr = "+"
-        ; Op = int_sub, OpStr = "-"
-        ; Op = int_mul, OpStr = "*"
-        ; Op = int_div, OpStr = "/"
-        ; Op = int_mod, OpStr = "%"
-        ; Op = unchecked_left_shift, OpStr = "<<"
-        ; Op = unchecked_right_shift, OpStr = ">>"
-        ; Op = bitwise_and, OpStr = "&"
-        ; Op = bitwise_or, OpStr = "|"
-        ; Op = bitwise_xor, OpStr = "^"
+        ( Op = int_add(_), OpStr = "+"
+        ; Op = int_sub(_), OpStr = "-"
+        ; Op = int_mul(_), OpStr = "*"
+        ; Op = int_div(_), OpStr = "/"
+        ; Op = int_mod(_), OpStr = "%"
+        ; Op = unchecked_left_shift(_), OpStr = "<<"
+        ; Op = unchecked_right_shift(_), OpStr = ">>"
+        ; Op = bitwise_and(_), OpStr = "&"
+        ; Op = bitwise_or(_), OpStr = "|"
+        ; Op = bitwise_xor(_), OpStr = "^"
         ; Op = logical_and, OpStr = "&&"
         ; Op = logical_or, OpStr = "||"
-        ; Op = eq, OpStr = "=="
-        ; Op = ne, OpStr = "!="
-        ; Op = int_lt, OpStr = "<"
-        ; Op = int_gt, OpStr = ">"
-        ; Op = int_le, OpStr = "<="
-        ; Op = int_ge, OpStr = ">="
-
-        ; Op = uint_eq, OpStr = "=="
-        ; Op = uint_ne, OpStr = "!="
-        ; Op = uint_lt, OpStr = "<"
-        ; Op = uint_gt, OpStr = ">"
-        ; Op = uint_le, OpStr = "<="
-        ; Op = uint_ge, OpStr = ">="
-
-        ; Op = uint_add, OpStr = "+"
-        ; Op = uint_sub, OpStr = "-"
-        ; Op = uint_mul, OpStr = "*"
-        ; Op = uint_div, OpStr = "/"
-        ; Op = uint_mod, OpStr = "%"
-        ; Op = uint_bitwise_and, OpStr = "&"
-        ; Op = uint_bitwise_or, OpStr = "|"
-        ; Op = uint_bitwise_xor, OpStr = "^"
-        ; Op = uint_unchecked_left_shift, OpStr = "<<"
-        ; Op = uint_unchecked_right_shift, OpStr = ">>"
+        ; Op = eq(_), OpStr = "=="
+        ; Op = ne(_), OpStr = "!="
+        ; Op = int_lt(_), OpStr = "<"
+        ; Op = int_gt(_), OpStr = ">"
+        ; Op = int_le(_), OpStr = "<="
+        ; Op = int_ge(_), OpStr = ">="
 
         ; Op = float_eq, OpStr = "=="
         ; Op = float_ne, OpStr = "!="
@@ -3479,6 +3623,24 @@ output_rval_const_for_csharp(Info, Const, !IO) :-
         Const = mlconst_uint(U),
         output_uint_const_for_csharp(U, !IO)
     ;
+        Const = mlconst_int8(N),
+        output_int_const_for_csharp(N, !IO)
+    ;
+        Const = mlconst_uint8(N),
+        output_int_const_for_csharp(N, !IO)
+    ;
+        Const = mlconst_int16(N),
+        output_int_const_for_csharp(N, !IO)
+    ;
+        Const = mlconst_uint16(N),
+        output_int_const_for_csharp(N, !IO)
+    ;
+        Const = mlconst_int32(N),
+        output_int_const_for_csharp(N, !IO)
+    ;
+        Const = mlconst_uint32(N),
+        output_int_const_for_csharp(N, !IO)
+    ;
         Const = mlconst_char(N),
         io.write_string("( ", !IO),
         output_int_const_for_csharp(N, !IO),
diff --git a/compiler/mlds_to_java.m b/compiler/mlds_to_java.m
index 42e16d4c2..ee1b1c4d7 100644
--- a/compiler/mlds_to_java.m
+++ b/compiler/mlds_to_java.m
@@ -1535,6 +1535,12 @@ rename_class_names_rval_const(Renaming, !Const) :-
         ; !.Const = mlconst_false
         ; !.Const = mlconst_int(_)
         ; !.Const = mlconst_uint(_)
+        ; !.Const = mlconst_int8(_)
+        ; !.Const = mlconst_uint8(_)
+        ; !.Const = mlconst_int16(_)
+        ; !.Const = mlconst_uint16(_)
+        ; !.Const = mlconst_int32(_)
+        ; !.Const = mlconst_uint32(_)
         ; !.Const = mlconst_char(_)
         ; !.Const = mlconst_enum(_, _)
         ; !.Const = mlconst_float(_)
@@ -2284,8 +2290,7 @@ get_java_type_initializer(Type) = Initializer :-
     (
         Type = mercury_type(_, CtorCat, _),
         (
-            ( CtorCat = ctor_cat_builtin(cat_builtin_int)
-            ; CtorCat = ctor_cat_builtin(cat_builtin_uint)
+            ( CtorCat = ctor_cat_builtin(cat_builtin_int(_))
             ; CtorCat = ctor_cat_builtin(cat_builtin_float)
             ),
             Initializer = "0"
@@ -3054,12 +3059,24 @@ mercury_type_to_string_for_java(Info, Type, CtorCat, String, ArrayDims) :-
         String = "int",
         ArrayDims = []
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_int),
+        ( CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int))
+        ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint))
+        ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int32))
+        ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint32))
+        ),
         String = "int",
         ArrayDims = []
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_uint),
-        String = "int",     % Java has no unsigned types.
+        ( CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int8))
+        ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint8))
+        ),
+        String = "byte",
+        ArrayDims = []
+    ;
+        ( CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int16))
+        ; CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint16))
+        ),
+        String = "short",
         ArrayDims = []
     ;
         CtorCat = ctor_cat_builtin(cat_builtin_string),
@@ -4432,13 +4449,29 @@ java_builtin_type(MLDS_Type, JavaUnboxedType, JavaBoxedType, UnboxMethod) :-
                 % The rationale for the handling of `char' and `uint' here is
                 % the same as for the mlds_native types above.
                 ( BuiltinType = builtin_type_char
-                ; BuiltinType = builtin_type_int
-                ; BuiltinType = builtin_type_uint
+                ; BuiltinType = builtin_type_int(int_type_int)
+                ; BuiltinType = builtin_type_int(int_type_uint)
+                ; BuiltinType = builtin_type_int(int_type_int32)
+                ; BuiltinType = builtin_type_int(int_type_uint32)
                 ),
                 JavaUnboxedType = "int",
                 JavaBoxedType = "java.lang.Integer",
                 UnboxMethod = "intValue"
             ;
+                ( BuiltinType = builtin_type_int(int_type_int8)
+                ; BuiltinType = builtin_type_int(int_type_uint8)
+                ),
+                JavaUnboxedType = "byte",
+                JavaBoxedType = "java.lang.Byte",
+                UnboxMethod = "byteValue"
+            ;
+                ( BuiltinType = builtin_type_int(int_type_int16)
+                ; BuiltinType = builtin_type_int(int_type_uint16)
+                ),
+                JavaUnboxedType = "short",
+                JavaBoxedType = "java.lang.Short",
+                UnboxMethod = "shortValue"
+            ;
                 BuiltinType = builtin_type_float,
                 JavaUnboxedType = "double",
                 JavaBoxedType = "java.lang.Double",
@@ -4585,7 +4618,7 @@ output_std_unop_for_java(Info, UnaryOp, Expr, !IO) :-
         ; UnaryOp = strip_tag, UnaryOpStr = "/* strip_tag */ "
         ; UnaryOp = mkbody,    UnaryOpStr = "/* mkbody */ "
         ; UnaryOp = unmkbody,   UnaryOpStr = "/* unmkbody */ "
-        ; UnaryOp = bitwise_complement, UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_int), UnaryOpStr = "~"
         ; UnaryOp = logical_not, UnaryOpStr = "!"
         ; UnaryOp = hash_string,  UnaryOpStr = "mercury.String.hash_1_f_0"
         ; UnaryOp = hash_string2, UnaryOpStr = "mercury.String.hash2_1_f_0"
@@ -4593,12 +4626,32 @@ output_std_unop_for_java(Info, UnaryOp, Expr, !IO) :-
         ; UnaryOp = hash_string4, UnaryOpStr = "mercury.String.hash4_1_f_0"
         ; UnaryOp = hash_string5, UnaryOpStr = "mercury.String.hash5_1_f_0"
         ; UnaryOp = hash_string6, UnaryOpStr = "mercury.String.hash6_1_f_0"
-        ; UnaryOp = uint_bitwise_complement, UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_uint), UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_int32), UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_uint32), UnaryOpStr = "~"
         ),
         io.write_string(UnaryOpStr, !IO),
         io.write_string("(", !IO),
         output_rval_for_java(Info, Expr, !IO),
         io.write_string(")", !IO)
+    ;
+        ( UnaryOp = bitwise_complement(int_type_int8), UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_uint8), UnaryOpStr = "~"
+        ),
+        io.write_string("(byte)(", !IO),
+        io.write_string(UnaryOpStr, !IO),
+        io.write_string("(", !IO),
+        output_rval_for_java(Info, Expr, !IO),
+        io.write_string("))", !IO)
+    ;
+        ( UnaryOp = bitwise_complement(int_type_int16), UnaryOpStr = "~"
+        ; UnaryOp = bitwise_complement(int_type_uint16), UnaryOpStr = "~"
+        ),
+        io.write_string("(short)(", !IO),
+        io.write_string(UnaryOpStr, !IO),
+        io.write_string("(", !IO),
+        output_rval_for_java(Info, Expr, !IO),
+        io.write_string("))", !IO)
     ).
 
 :- pred output_binop_for_java(java_out_info::in, binary_op::in, mlds_rval::in,
@@ -4647,27 +4700,57 @@ output_binop_for_java(Info, Op, X, Y, !IO) :-
         io.write_string(") ", !IO)
     ;
         % XXX Should we abort for some of these?
-        ( Op = int_add
-        ; Op = int_sub
-        ; Op = int_mul
-        ; Op = int_div
-        ; Op = int_mod
-        ; Op = unchecked_left_shift
-        ; Op = unchecked_right_shift
-        ; Op = bitwise_and
-        ; Op = bitwise_or
-        ; Op = bitwise_xor
+        ( Op = int_add(int_type_int)
+        ; Op = int_sub(int_type_int)
+        ; Op = int_mul(int_type_int)
+        ; Op = int_div(int_type_int)
+        ; Op = int_mod(int_type_int)
+        ; Op = unchecked_left_shift(int_type_int)
+        ; Op = unchecked_right_shift(int_type_int)
+        ; Op = bitwise_and(int_type_int)
+        ; Op = bitwise_or(int_type_int)
+        ; Op = bitwise_xor(int_type_int)
+        ; Op = int_lt(int_type_int32)
+        ; Op = int_gt(int_type_int32)
+        ; Op = int_le(int_type_int32)
+        ; Op = int_ge(int_type_int32)
+        ; Op = int_add(int_type_int32)
+        ; Op = int_sub(int_type_int32)
+        ; Op = int_mul(int_type_int32)
+        ; Op = int_div(int_type_int32)
+        ; Op = int_mod(int_type_int32)
+        ; Op = bitwise_and(int_type_int32)
+        ; Op = bitwise_or(int_type_int32)
+        ; Op = bitwise_xor(int_type_int32)
+        ; Op = unchecked_left_shift(int_type_int32)
+        ; Op = unchecked_right_shift(int_type_int32)
+        ; Op = int_add(int_type_uint)
+        ; Op = int_sub(int_type_uint)
+        ; Op = int_mul(int_type_uint)
+        ; Op = bitwise_and(int_type_uint)
+        ; Op = bitwise_or(int_type_uint)
+        ; Op = bitwise_xor(int_type_uint)
+        ; Op = unchecked_left_shift(int_type_uint)
+        ; Op = unchecked_right_shift(int_type_uint)
+        ; Op = int_add(int_type_uint32)
+        ; Op = int_sub(int_type_uint32)
+        ; Op = int_mul(int_type_uint32)
+        ; Op = bitwise_and(int_type_uint32)
+        ; Op = bitwise_or(int_type_uint32)
+        ; Op = bitwise_xor(int_type_uint32)
+        ; Op = unchecked_left_shift(int_type_uint32)
+        ; Op = unchecked_right_shift(int_type_uint32)
         ; Op = logical_and
         ; Op = logical_or
-        ; Op = eq
-        ; Op = ne
+        ; Op = eq(_)
+        ; Op = ne(_)
         ; Op = body
         ; Op = string_unsafe_index_code_unit
         ; Op = offset_str_eq(_)
-        ; Op = int_lt
-        ; Op = int_gt
-        ; Op = int_le
-        ; Op = int_ge
+        ; Op = int_lt(int_type_int)
+        ; Op = int_gt(int_type_int)
+        ; Op = int_le(int_type_int)
+        ; Op = int_ge(int_type_int)
         ; Op = unsigned_le
         ; Op = float_plus
         ; Op = float_minus
@@ -4683,6 +4766,14 @@ output_binop_for_java(Info, Op, X, Y, !IO) :-
         ; Op = float_from_dword
         ; Op = compound_eq
         ; Op = compound_lt
+        ; Op = int_lt(int_type_int8)
+        ; Op = int_gt(int_type_int8)
+        ; Op = int_le(int_type_int8)
+        ; Op = int_ge(int_type_int8)
+        ; Op = int_lt(int_type_int16)
+        ; Op = int_gt(int_type_int16)
+        ; Op = int_le(int_type_int16)
+        ; Op = int_ge(int_type_int16)
         ),
         ( if rval_is_enum_object(X) then
             io.write_string("(", !IO),
@@ -4702,18 +4793,56 @@ output_binop_for_java(Info, Op, X, Y, !IO) :-
             io.write_string(")", !IO)
         )
     ;
-        ( Op = uint_eq
-        ; Op = uint_ne
-        ; Op = uint_add
-        ; Op = uint_sub
-        ; Op = uint_mul
-        ; Op = uint_bitwise_and
-        ; Op = uint_bitwise_or
-        ; Op = uint_bitwise_xor
-        ; Op = uint_unchecked_left_shift
-        ; Op = uint_unchecked_right_shift
+        ( Op = int_lt(int_type_uint)
+        ; Op = int_gt(int_type_uint)
+        ; Op = int_le(int_type_uint)
+        ; Op = int_ge(int_type_uint)
+        ; Op = int_lt(int_type_uint32)
+        ; Op = int_gt(int_type_uint32)
+        ; Op = int_le(int_type_uint32)
+        ; Op = int_ge(int_type_uint32)
         ),
-        io.write_string("(", !IO),
+        io.write_string("(((", !IO),
+        output_rval_for_java(Info, X, !IO),
+        io.write_string(") & 0xffffffffL) ", !IO),
+        output_binary_op_for_java(Op, !IO),
+        io.write_string(" ((", !IO),
+        output_rval_for_java(Info, Y, !IO),
+        io.write_string(") & 0xffffffffL))", !IO)
+    ;
+        ( Op = int_div(int_type_uint)
+        ; Op = int_mod(int_type_uint)
+        ; Op = int_div(int_type_uint32)
+        ; Op = int_mod(int_type_uint32)
+        ),
+        io.write_string("((int)(((", !IO),
+        output_rval_for_java(Info, X, !IO),
+        io.write_string(") & 0xffffffffL) ", !IO),
+        output_binary_op_for_java(Op, !IO),
+        io.write_string(" ((", !IO),
+        output_rval_for_java(Info, Y, !IO),
+        io.write_string(") & 0xffffffffL)))", !IO)
+    ;
+        ( Op = int_add(int_type_int8)
+        ; Op = int_sub(int_type_int8)
+        ; Op = int_mul(int_type_int8)
+        ; Op = int_div(int_type_int8)
+        ; Op = int_mod(int_type_int8)
+        ; Op = bitwise_and(int_type_int8)
+        ; Op = bitwise_or(int_type_int8)
+        ; Op = bitwise_xor(int_type_int8)
+        ; Op = unchecked_left_shift(int_type_int8)
+        ; Op = unchecked_right_shift(int_type_int8)
+        ; Op = int_add(int_type_uint8)
+        ; Op = int_sub(int_type_uint8)
+        ; Op = int_mul(int_type_uint8)
+        ; Op = bitwise_and(int_type_uint8)
+        ; Op = bitwise_or(int_type_uint8)
+        ; Op = bitwise_xor(int_type_uint8)
+        ; Op = unchecked_left_shift(int_type_uint8)
+        ; Op = unchecked_right_shift(int_type_uint8)
+        ),
+        io.write_string("(byte)(", !IO),
         output_rval_for_java(Info, X, !IO),
         io.write_string(" ", !IO),
         output_binary_op_for_java(Op, !IO),
@@ -4721,29 +4850,80 @@ output_binop_for_java(Info, Op, X, Y, !IO) :-
         output_rval_for_java(Info, Y, !IO),
         io.write_string(")", !IO)
     ;
-        ( Op = uint_lt
-        ; Op = uint_gt
-        ; Op = uint_le
-        ; Op = uint_ge
+        ( Op = int_lt(int_type_uint8)
+        ; Op = int_gt(int_type_uint8)
+        ; Op = int_le(int_type_uint8)
+        ; Op = int_ge(int_type_uint8)
         ),
         io.write_string("(((", !IO),
         output_rval_for_java(Info, X, !IO),
-        io.write_string(") & 0xffffffffL) ", !IO),
+        io.write_string(") & 0xff) ", !IO),
         output_binary_op_for_java(Op, !IO),
         io.write_string(" ((", !IO),
         output_rval_for_java(Info, Y, !IO),
-        io.write_string(") & 0xffffffffL))", !IO)
+        io.write_string(") & 0xff))", !IO)
     ;
-        ( Op = uint_div
-        ; Op = uint_mod
+        ( Op = int_div(int_type_uint8)
+        ; Op = int_mod(int_type_uint8)
         ),
-        io.write_string("((int)(((", !IO),
+        io.write_string("((byte)(((", !IO),
         output_rval_for_java(Info, X, !IO),
-        io.write_string(") & 0xffffffffL) ", !IO),
+        io.write_string(") & 0xff) ", !IO),
         output_binary_op_for_java(Op, !IO),
         io.write_string(" ((", !IO),
         output_rval_for_java(Info, Y, !IO),
-        io.write_string(") & 0xffffffffL)))", !IO)
+        io.write_string(") & 0xff)))", !IO)
+    ;
+        ( Op = int_add(int_type_int16)
+        ; Op = int_sub(int_type_int16)
+        ; Op = int_mul(int_type_int16)
+        ; Op = int_div(int_type_int16)
+        ; Op = int_mod(int_type_int16)
+        ; Op = bitwise_and(int_type_int16)
+        ; Op = bitwise_or(int_type_int16)
+        ; Op = bitwise_xor(int_type_int16)
+        ; Op = unchecked_left_shift(int_type_int16)
+        ; Op = unchecked_right_shift(int_type_int16)
+        ; Op = int_add(int_type_uint16)
+        ; Op = int_sub(int_type_uint16)
+        ; Op = int_mul(int_type_uint16)
+        ; Op = bitwise_and(int_type_uint16)
+        ; Op = bitwise_or(int_type_uint16)
+        ; Op = bitwise_xor(int_type_uint16)
+        ; Op = unchecked_left_shift(int_type_uint16)
+        ; Op = unchecked_right_shift(int_type_uint16)
+        ),
+        io.write_string("(short)(", !IO),
+        output_rval_for_java(Info, X, !IO),
+        io.write_string(" ", !IO),
+        output_binary_op_for_java(Op, !IO),
+        io.write_string(" ", !IO),
+        output_rval_for_java(Info, Y, !IO),
+        io.write_string(")", !IO)
+    ;
+        ( Op = int_lt(int_type_uint16)
+        ; Op = int_gt(int_type_uint16)
+        ; Op = int_le(int_type_uint16)
+        ; Op = int_ge(int_type_uint16)
+        ),
+        io.write_string("(((", !IO),
+        output_rval_for_java(Info, X, !IO),
+        io.write_string(") & 0xffff) ", !IO),
+        output_binary_op_for_java(Op, !IO),
+        io.write_string(" ((", !IO),
+        output_rval_for_java(Info, Y, !IO),
+        io.write_string(") & 0xffff))", !IO)
+    ;
+        ( Op = int_div(int_type_uint16)
+        ; Op = int_mod(int_type_uint16)
+        ),
+        io.write_string("((short)(((", !IO),
+        output_rval_for_java(Info, X, !IO),
+        io.write_string(") & 0xffff) ", !IO),
+        output_binary_op_for_java(Op, !IO),
+        io.write_string(" ((", !IO),
+        output_rval_for_java(Info, Y, !IO),
+        io.write_string(") & 0xffff)))", !IO)
     ).
 
     % Output an Rval and if the Rval is an enumeration object append the string
@@ -4772,48 +4952,27 @@ output_rval_maybe_with_enum_for_java(Info, Rval, !IO) :-
 
 output_binary_op_for_java(Op, !IO) :-
     (
-        ( Op = int_add, OpStr = "+"
-        ; Op = int_sub, OpStr = "-"
-        ; Op = int_mul, OpStr = "*"
-        ; Op = int_div, OpStr = "/"
-        ; Op = int_mod, OpStr = "%"
-        ; Op = unchecked_left_shift, OpStr = "<<"
-        ; Op = unchecked_right_shift, OpStr = ">>"
-        ; Op = bitwise_and, OpStr = "&"
-        ; Op = bitwise_or, OpStr = "|"
-        ; Op = bitwise_xor, OpStr = "^"
+        ( Op = int_add(_), OpStr = "+"
+        ; Op = int_sub(_), OpStr = "-"
+        ; Op = int_mul(_), OpStr = "*"
+        % NOTE: unsigned div and mode require special handling in Java.
+        % See output_binop/6 above.
+        ; Op = int_div(_), OpStr = "/"
+        ; Op = int_mod(_), OpStr = "%"
+        ; Op = unchecked_left_shift(_), OpStr = "<<"
+        ; Op = bitwise_and(_), OpStr = "&"
+        ; Op = bitwise_or(_), OpStr = "|"
+        ; Op = bitwise_xor(_), OpStr = "^"
         ; Op = logical_and, OpStr = "&&"
         ; Op = logical_or, OpStr = "||"
-        ; Op = eq, OpStr = "=="
-        ; Op = ne, OpStr = "!="
-        ; Op = int_lt, OpStr = "<"
-        ; Op = int_gt, OpStr = ">"
-        ; Op = int_le, OpStr = "<="
-        ; Op = int_ge, OpStr = ">="
-
-        ; Op = uint_eq, OpStr = "=="
-        ; Op = uint_ne, OpStr = "!="
         % NOTE: unsigned comparisons require special handling in Java.
         % See output_binop/6 above.
-        ; Op = uint_lt, OpStr = "<"
-        ; Op = uint_gt, OpStr = ">"
-        ; Op = uint_le, OpStr = "<="
-        ; Op = uint_ge, OpStr = ">="
-
-        ; Op = uint_add, OpStr = "+"
-        ; Op = uint_sub, OpStr = "-"
-        ; Op = uint_mul, OpStr = "*"
-
-        % NOTE: unsigned div and mod require special handling in Java.
-        % See output_binop/6 above.
-        ; Op = uint_div, OpStr = "/"
-        ; Op = uint_mod, OpStr = "%"
-
-        ; Op = uint_bitwise_and, OpStr = "&"
-        ; Op = uint_bitwise_or, OpStr = "|"
-        ; Op = uint_bitwise_xor, OpStr = "^"
-        ; Op = uint_unchecked_left_shift, OpStr = "<<"
-        ; Op = uint_unchecked_right_shift, OpStr = ">>>"
+        ; Op = eq(_), OpStr = "=="
+        ; Op = ne(_), OpStr = "!="
+        ; Op = int_lt(_), OpStr = "<"
+        ; Op = int_gt(_), OpStr = ">"
+        ; Op = int_le(_), OpStr = "<="
+        ; Op = int_ge(_), OpStr = ">="
 
         ; Op = float_eq, OpStr = "=="
         ; Op = float_ne, OpStr = "!="
@@ -4829,6 +4988,24 @@ output_binary_op_for_java(Op, !IO) :-
         ),
         io.write_string(OpStr, !IO)
     ;
+        Op = unchecked_right_shift(IntType),
+        (
+            ( IntType = int_type_int
+            ; IntType = int_type_int8
+            ; IntType = int_type_int16
+            ; IntType = int_type_int32
+            ),
+            OpStr = ">>"
+        ;
+            (IntType = int_type_uint
+            ; IntType = int_type_uint8
+            ; IntType = int_type_uint16
+            ; IntType = int_type_uint32
+            ),
+            OpStr = ">>>"
+        ),
+        io.write_string(OpStr, !IO)
+    ;
         ( Op = array_index(_)
         ; Op = body
         ; Op = float_from_dword
@@ -4869,6 +5046,24 @@ output_rval_const_for_java(Info, Const, !IO) :-
         % XXX perhaps we should output this in hexadecimal?
         output_int_const_for_java(uint.cast_to_int(U), !IO)
     ;
+        Const = mlconst_int8(I8),
+        output_int_const_for_java(I8, !IO)
+    ;
+        Const = mlconst_uint8(U8),
+        output_int_const_for_java(U8, !IO)
+    ;
+        Const = mlconst_int16(I16),
+        output_int_const_for_java(I16, !IO)
+    ;
+        Const = mlconst_uint16(U16),
+        output_int_const_for_java(U16, !IO)
+    ;
+        Const = mlconst_int32(I32),
+        output_int_const_for_java(I32, !IO)
+    ;
+        Const = mlconst_uint32(U32),
+        output_int_const_for_java(U32, !IO)
+    ;
         Const = mlconst_char(N),
         io.write_string("(", !IO),
         output_int_const_for_java(N, !IO),
diff --git a/compiler/mode_util.m b/compiler/mode_util.m
index e86b308ac..2ba11a809 100644
--- a/compiler/mode_util.m
+++ b/compiler/mode_util.m
@@ -1894,6 +1894,12 @@ cons_id_to_shared_inst(ModuleInfo, ConsId, NumArgs) = MaybeInst :-
         % we used to handle character constants as user-defined cons_ids.
         ( ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
diff --git a/compiler/module_qual.qualify_items.m b/compiler/module_qual.qualify_items.m
index 6cada7769..322154b88 100644
--- a/compiler/module_qual.qualify_items.m
+++ b/compiler/module_qual.qualify_items.m
@@ -475,12 +475,30 @@ qualify_type(InInt, ErrorContext, Type0, Type, !Info, !Specs) :-
         % `character', since the corresponding library module `char'
         % will be flagged as used in the interface if the type `char' is used.
         (
-            BuiltinType = builtin_type_int,
+            BuiltinType = builtin_type_int(int_type_int),
             mq_info_set_module_used(InInt, unqualified("int"), !Info)
         ;
-            BuiltinType = builtin_type_uint,
+            BuiltinType = builtin_type_int(int_type_uint),
             mq_info_set_module_used(InInt, unqualified("uint"), !Info)
         ;
+            BuiltinType = builtin_type_int(int_type_int8),
+            mq_info_set_module_used(InInt, unqualified("int8"), !Info)
+        ;
+            BuiltinType = builtin_type_int(int_type_uint8),
+            mq_info_set_module_used(InInt, unqualified("uint8"), !Info)
+        ;
+            BuiltinType = builtin_type_int(int_type_int16),
+            mq_info_set_module_used(InInt, unqualified("int16"), !Info)
+        ;
+            BuiltinType = builtin_type_int(int_type_uint16),
+            mq_info_set_module_used(InInt, unqualified("uint16"), !Info)
+        ;
+            BuiltinType = builtin_type_int(int_type_int32),
+            mq_info_set_module_used(InInt, unqualified("int32"), !Info)
+        ;
+            BuiltinType = builtin_type_int(int_type_uint32),
+            mq_info_set_module_used(InInt, unqualified("uint32"), !Info)
+        ;
             BuiltinType = builtin_type_float,
             mq_info_set_module_used(InInt, unqualified("float"), !Info)
         ;
@@ -723,6 +741,12 @@ qualify_bound_inst(InInt, ErrorContext, BoundInst0, BoundInst,
         ; ConsId = closure_cons(_, _)
         ; ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
diff --git a/compiler/opt_debug.m b/compiler/opt_debug.m
index 40ee7cab4..6fff4b72e 100644
--- a/compiler/opt_debug.m
+++ b/compiler/opt_debug.m
@@ -444,6 +444,24 @@ dump_const(MaybeProcLabel, Const) = Str :-
         Const = llconst_uint(U),
         Str = uint_to_string(U)
     ;
+        Const = llconst_int8(I8),
+        Str = int_to_string(I8)
+    ;
+        Const = llconst_uint8(U8),
+        Str = int_to_string(U8)
+    ;
+        Const = llconst_int16(I16),
+        Str = int_to_string(I16)
+    ;
+        Const = llconst_uint16(U16),
+        Str = int_to_string(U16)
+    ;
+        Const = llconst_int32(I32),
+        Str = int_to_string(I32)
+    ;
+        Const = llconst_uint32(U32),
+        Str = int_to_string(U32)
+    ;
         Const = llconst_foreign(F, _),
         Str = F
     ;
@@ -835,14 +853,13 @@ dump_unop(strip_tag) = "strip_tag".
 dump_unop(mkbody) = "mkbody".
 dump_unop(unmkbody) = "unmkbody".
 dump_unop(logical_not) = "not".
-dump_unop(bitwise_complement) = "bitwise_complement".
+dump_unop(bitwise_complement(_)) = "bitwise_complement".
 dump_unop(hash_string) = "hash_string".
 dump_unop(hash_string2) = "hash_string2".
 dump_unop(hash_string3) = "hash_string3".
 dump_unop(hash_string4) = "hash_string4".
 dump_unop(hash_string5) = "hash_string5".
 dump_unop(hash_string6) = "hash_string6".
-dump_unop(uint_bitwise_complement) = "uint_bitwise_complement".
 
 dump_binop(array_index(_)) = "array_index".
 dump_binop(string_unsafe_index_code_unit) = "string_unsafe_index_code_unit".
@@ -856,22 +873,6 @@ dump_binop(str_ge) = "str>=".
 dump_binop(str_lt) = "str<".
 dump_binop(str_gt) = "str>".
 dump_binop(unsigned_le) = "unsigned<=".
-dump_binop(uint_eq) = "uint==".
-dump_binop(uint_ne) = "uint!=".
-dump_binop(uint_lt) = "uint<".
-dump_binop(uint_gt) = "uint>".
-dump_binop(uint_le) = "uint<=".
-dump_binop(uint_ge) = "uint>=".
-dump_binop(uint_add) = "uint+".
-dump_binop(uint_sub) = "uint-".
-dump_binop(uint_mul) = "uint*".
-dump_binop(uint_div) = "uint/".
-dump_binop(uint_mod) = "uint%".
-dump_binop(uint_bitwise_and) = "uint&".
-dump_binop(uint_bitwise_or) = "uint|".
-dump_binop(uint_bitwise_xor) = "uint^".
-dump_binop(uint_unchecked_left_shift) = "uint_unchecked<<".
-dump_binop(uint_unchecked_right_shift) = "uint_unchecked>>".
 dump_binop(float_plus) = "fl+".
 dump_binop(float_minus) = "fl-".
 dump_binop(float_times) = "fl*".
@@ -884,24 +885,24 @@ dump_binop(float_lt) = "fl<".
 dump_binop(float_gt) = "fl>".
 dump_binop(float_word_bits) = "float_word_bits".
 dump_binop(float_from_dword) = "float_from_dword".
-dump_binop(int_add) = "+".
-dump_binop(int_sub) = "-".
-dump_binop(int_mul) = "*".
-dump_binop(int_div) = "/".
-dump_binop(unchecked_left_shift) = "unchecked<<".
-dump_binop(unchecked_right_shift) = "unchecked>>".
-dump_binop(bitwise_and) = "&".
-dump_binop(bitwise_or) = "|".
-dump_binop(bitwise_xor) = "^".
-dump_binop(int_mod) = "%".
-dump_binop(eq) = "==".
-dump_binop(ne) = "!=".
+dump_binop(int_add(_)) = "+".
+dump_binop(int_sub(_)) = "-".
+dump_binop(int_mul(_)) = "*".
+dump_binop(int_div(_)) = "/".
+dump_binop(unchecked_left_shift(_)) = "unchecked<<".
+dump_binop(unchecked_right_shift(_)) = "unchecked>>".
+dump_binop(bitwise_and(_)) = "&".
+dump_binop(bitwise_or(_)) = "|".
+dump_binop(bitwise_xor(_)) = "^".
+dump_binop(int_mod(_)) = "%".
+dump_binop(eq(_)) = "==".
+dump_binop(ne(_)) = "!=".
 dump_binop(logical_and) = "&&".
 dump_binop(logical_or) = "||".
-dump_binop(int_lt) = "<".
-dump_binop(int_gt) = ">".
-dump_binop(int_le) = "<=".
-dump_binop(int_ge) = ">=".
+dump_binop(int_lt(_)) = "<".
+dump_binop(int_gt(_)) = ">".
+dump_binop(int_le(_)) = "<=".
+dump_binop(int_ge(_)) = ">=".
 dump_binop(str_cmp) = "strcmp".
 dump_binop(body) = "body".
 dump_binop(pointer_equal_conservative) = "pointer_equal_conservative".
diff --git a/compiler/opt_util.m b/compiler/opt_util.m
index b8c219d19..d1527bcfc 100644
--- a/compiler/opt_util.m
+++ b/compiler/opt_util.m
@@ -1060,11 +1060,13 @@ is_const_condition(unop(Op, Rval1), Taken) :-
     Op = logical_not,
     is_const_condition(Rval1, Taken1),
     bool.not(Taken1, Taken).
+% XXX FIXED SIZE INTS - we should handle the other integer types here.
 is_const_condition(binop(Op, Rval1, Rval2), Taken) :-
-    Op = eq,
+    Op = eq(int_type_int),
     Rval1 = Rval2,
     Taken = yes.
 
+
 can_instr_branch_away(Uinstr) = CanBranchAway :-
     (
         ( Uinstr = comment(_)
@@ -2616,6 +2618,12 @@ replace_labels_rval_const(Const0, Const, ReplMap) :-
         ; Const0 = llconst_false
         ; Const0 = llconst_int(_)
         ; Const0 = llconst_uint(_)
+        ; Const0 = llconst_int8(_)
+        ; Const0 = llconst_uint8(_)
+        ; Const0 = llconst_int16(_)
+        ; Const0 = llconst_uint16(_)
+        ; Const0 = llconst_int32(_)
+        ; Const0 = llconst_uint32(_)
         ; Const0 = llconst_foreign(_, _)
         ; Const0 = llconst_float(_)
         ; Const0 = llconst_string(_)
diff --git a/compiler/par_loop_control.m b/compiler/par_loop_control.m
index 424af7170..6d64c5645 100644
--- a/compiler/par_loop_control.m
+++ b/compiler/par_loop_control.m
@@ -1371,8 +1371,8 @@ update_outer_proc(PredProcId, InnerPredProcId, InnerPredName, ModuleInfo,
         % (for auto-parallelisation), but for now we just set it using
         % a runtime call so that it can be tuned.
         varset.new_named_var("NumContexts", NumContextsVar, !VarSet),
-        add_var_type(NumContextsVar, builtin_type(builtin_type_int),
-            !VarTypes),
+        add_var_type(NumContextsVar,
+            builtin_type(builtin_type_int(int_type_int)), !VarTypes),
         get_lc_default_num_contexts_proc(ModuleInfo,
             LCDefaultNumContextsPredId, LCDefaultNumContextsProcId),
         goal_info_init(set_of_var.list_to_set([NumContextsVar]),
@@ -1463,7 +1463,7 @@ loop_control_var_type = defined_type(Sym, [], kind_star) :-
 
 :- func loop_control_slot_var_type = mer_type.
 
-loop_control_slot_var_type = builtin_type(builtin_type_int).
+loop_control_slot_var_type = builtin_type(builtin_type_int(int_type_int)).
 
 %----------------------------------------------------------------------------%
 
diff --git a/compiler/parse_tree_out_info.m b/compiler/parse_tree_out_info.m
index 4634de671..abd088fc4 100644
--- a/compiler/parse_tree_out_info.m
+++ b/compiler/parse_tree_out_info.m
@@ -107,6 +107,13 @@
     pred add_char(char::in, U::di, U::uo) is det,
     pred add_int(int::in, U::di, U::uo) is det,
     pred add_uint(uint::in, U::di, U::uo) is det,
+    % XXX FIXED SIZE INT
+    pred add_int8(int::in, U::di, U::uo) is det,
+    pred add_uint8(int::in, U::di, U::uo) is det,
+    pred add_int16(int::in, U::di, U::uo) is det,
+    pred add_uint16(int::in, U::di, U::uo) is det,
+    pred add_int32(int::in, U::di, U::uo) is det,
+    pred add_uint32(int::in, U::di, U::uo) is det,
     pred add_float(float::in, U::di, U::uo) is det,
     pred add_purity_prefix(purity::in, U::di, U::uo) is det,
     pred add_quoted_atom(string::in, U::di, U::uo) is det,
@@ -192,6 +199,12 @@ maybe_unqualify_sym_name(Info, SymName, OutSymName) :-
     pred(add_char/3) is io.write_char,
     pred(add_int/3) is io.write_int,
     pred(add_uint/3) is write_uint_literal,
+    pred(add_int8/3) is io.write_int,
+    pred(add_uint8/3) is io.write_int,
+    pred(add_int16/3) is io.write_int,
+    pred(add_uint16/3) is io.write_int,
+    pred(add_int32/3) is io.write_int,
+    pred(add_uint32/3) is io.write_int,
     pred(add_float/3) is io.write_float,
     pred(add_purity_prefix/3) is prog_out.write_purity_prefix,
     pred(add_quoted_atom/3) is term_io.quote_atom,
@@ -210,6 +223,12 @@ maybe_unqualify_sym_name(Info, SymName, OutSymName) :-
     pred(add_char/3) is output_char,
     pred(add_int/3) is output_int,
     pred(add_uint/3) is output_uint,
+    pred(add_int8/3) is output_int8,
+    pred(add_uint8/3) is output_uint8,
+    pred(add_int16/3) is output_int16,
+    pred(add_uint16/3) is output_uint16,
+    pred(add_int32/3) is output_int32,
+    pred(add_uint32/3) is output_uint32,
     pred(add_float/3) is output_float,
     pred(add_purity_prefix/3) is output_purity_prefix,
     pred(add_quoted_atom/3) is output_quoted_atom,
@@ -275,6 +294,43 @@ output_uint(U, Str0, Str) :-
     S = uint_to_string(U) ++ "u",
     string.append(Str0, S, Str).
 
+% XXX FIXED SIZE INT
+:- pred output_int8(int::in, string::di, string::uo) is det.
+
+output_int8(I, Str0, Str) :-
+    string.int_to_string(I, S),
+    string.append(Str0, S, Str).
+
+:- pred output_uint8(int::in, string::di, string::uo) is det.
+
+output_uint8(I, Str0, Str) :-
+    string.int_to_string(I, S),
+    string.append(Str0, S, Str).
+
+:- pred output_int16(int::in, string::di, string::uo) is det.
+
+output_int16(I, Str0, Str) :-
+    string.int_to_string(I, S),
+    string.append(Str0, S, Str).
+
+:- pred output_uint16(int::in, string::di, string::uo) is det.
+
+output_uint16(I, Str0, Str) :-
+    string.int_to_string(I, S),
+    string.append(Str0, S, Str).
+
+:- pred output_int32(int::in, string::di, string::uo) is det.
+
+output_int32(I, Str0, Str) :-
+    string.int_to_string(I, S),
+    string.append(Str0, S, Str).
+
+:- pred output_uint32(int::in, string::di, string::uo) is det.
+
+output_uint32(I, Str0, Str) :-
+    string.int_to_string(I, S),
+    string.append(Str0, S, Str).
+
 :- pred output_float(float::in, string::di, string::uo) is det.
 
 output_float(F, Str0, Str) :-
diff --git a/compiler/parse_tree_to_term.m b/compiler/parse_tree_to_term.m
index 98dce6735..8cfb45ec7 100644
--- a/compiler/parse_tree_to_term.m
+++ b/compiler/parse_tree_to_term.m
@@ -652,6 +652,30 @@ cons_id_and_args_to_term_full(ConsId, ArgTerms, Term) :-
         term.context_init(Context),
         Term = uint_to_decimal_term(UInt, Context)
     ;
+        ConsId = int8_const(Int8),
+        term.context_init(Context),
+        Term = int_to_decimal_term(Int8, Context)
+    ;
+        ConsId = uint8_const(UInt8),
+        term.context_init(Context),
+        Term = int_to_decimal_term(UInt8, Context)
+    ;
+        ConsId = int16_const(Int16),
+        term.context_init(Context),
+        Term = int_to_decimal_term(Int16, Context)
+    ;
+        ConsId = uint16_const(UInt16),
+        term.context_init(Context),
+        Term = int_to_decimal_term(UInt16, Context)
+    ;
+        ConsId = int32_const(Int32),
+        term.context_init(Context),
+        Term = int_to_decimal_term(Int32, Context)
+    ;
+        ConsId = uint32_const(UInt32),
+        term.context_init(Context),
+        Term = int_to_decimal_term(UInt32, Context)
+    ;
         ConsId = float_const(Float),
         term.context_init(Context),
         Term = term.functor(term.float(Float), [], Context)
diff --git a/compiler/parse_type_name.m b/compiler/parse_type_name.m
index b72728403..a21552067 100644
--- a/compiler/parse_type_name.m
+++ b/compiler/parse_type_name.m
@@ -639,10 +639,28 @@ is_known_type_name_args(Name, Args, KnownType) :-
         % Known types which are always simple.
         (
             Name = "int",
-            BuiltinType = builtin_type_int
+            BuiltinType = builtin_type_int(int_type_int)
         ;
             Name = "uint",
-            BuiltinType = builtin_type_uint
+            BuiltinType = builtin_type_int(int_type_uint)
+        ;
+            Name = "int8",
+            BuiltinType = builtin_type_int(int_type_int8)
+        ;
+            Name = "uint8",
+            BuiltinType = builtin_type_int(int_type_uint8)
+        ;
+            Name = "int16",
+            BuiltinType = builtin_type_int(int_type_int16)
+        ;
+            Name = "uint16",
+            BuiltinType = builtin_type_int(int_type_uint16)
+        ;
+            Name = "int32",
+            BuiltinType = builtin_type_int(int_type_int32)
+        ;
+            Name = "uint32",
+            BuiltinType = builtin_type_int(int_type_uint32)
         ;
             Name = "float",
             BuiltinType = builtin_type_float
diff --git a/compiler/peephole.m b/compiler/peephole.m
index 7ac26aed4..a86d4fab1 100644
--- a/compiler/peephole.m
+++ b/compiler/peephole.m
@@ -36,6 +36,7 @@
 
 :- import_module backend_libs.builtin_ops.
 :- import_module ll_backend.opt_util.
+:- import_module parse_tree.prog_data.
 
 :- import_module int.
 :- import_module map.
@@ -178,7 +179,8 @@ peephole_match(Instr0, Instrs0, _, Instrs) :-
         peephole_pick_one_val_label(LabelVals1, LabelVals2, OneValLabel,
             Val, OtherLabel)
     then
-        CondRval = binop(eq, SelectorRval, const(llconst_int(Val))),
+        CondRval = binop(eq(int_type_int), SelectorRval,
+            const(llconst_int(Val))),
         CommentInstr = llds_instr(comment(Comment0), ""),
         BranchInstr = llds_instr(if_val(CondRval, code_label(OneValLabel)),
             ""),
diff --git a/compiler/polymorphism.m b/compiler/polymorphism.m
index 295410fab..6d42ccd37 100644
--- a/compiler/polymorphism.m
+++ b/compiler/polymorphism.m
@@ -3588,12 +3588,30 @@ get_special_proc_det(Type, SpecialPredId, ModuleInfo, PredName,
 
 get_category_name(CtorCat) = MaybeName :-
     (
-        CtorCat = ctor_cat_builtin(cat_builtin_int),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int)),
         MaybeName = yes("int")
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_uint),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint)),
         MaybeName = yes("uint")
     ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int8)),
+        MaybeName = yes("int8")
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint8)),
+        MaybeName = yes("uint8")
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int16)),
+        MaybeName = yes("int16")
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint16)),
+        MaybeName = yes("uint16")
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int32)),
+        MaybeName = yes("int32")
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint32)),
+        MaybeName = yes("uint32")
+    ;
         CtorCat = ctor_cat_builtin(cat_builtin_char),
         MaybeName = yes("character")
     ;
diff --git a/compiler/pragma_c_gen.m b/compiler/pragma_c_gen.m
index 024eb285f..60401ebe1 100644
--- a/compiler/pragma_c_gen.m
+++ b/compiler/pragma_c_gen.m
@@ -422,7 +422,7 @@ generate_runtime_cond_code(Expr, CondRval, !CI) :-
         set_used_env_vars(UsedEnvVars, !CI),
         EnvVarRval = lval(global_var_ref(env_var_ref(EnvVar))),
         ZeroRval = const(llconst_int(0)),
-        CondRval = binop(ne, EnvVarRval, ZeroRval)
+        CondRval = binop(ne(int_type_int), EnvVarRval, ZeroRval)
     ;
         Expr = trace_not(ExprA),
         generate_runtime_cond_code(ExprA, RvalA, !CI),
diff --git a/compiler/prog_data.m b/compiler/prog_data.m
index 1362c09ee..0c2be1ea2 100644
--- a/compiler/prog_data.m
+++ b/compiler/prog_data.m
@@ -107,6 +107,12 @@
 
     ;       int_const(int)
     ;       uint_const(uint)
+    ;       int8_const(int)     % XXX FIXED SIZE INT
+    ;       uint8_const(int)    % XXX FIXED SIZE INT
+    ;       int16_const(int)    % XXX FIXED SIZE INT
+    ;       uint16_const(int)   % XXX FIXED SIZE INT
+    ;       int32_const(int)    % XXX FIXED SIZE INT
+    ;       uint32_const(int)   % XXX FIXED SIZE INT
     ;       float_const(float)
     ;       char_const(char)
     ;       string_const(string)
@@ -224,6 +230,12 @@ cons_id_is_const_struct(ConsId, ConstNum) :-
         ; ConsId = closure_cons(_, _)
         ; ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
@@ -503,12 +515,21 @@ cons_id_is_const_struct(ConsId, ConstNum) :-
     %     - type_util.classify_type_ctor/2
     %
 :- type builtin_type
-    --->    builtin_type_int
-    ;       builtin_type_uint
+    --->    builtin_type_int(int_type)
     ;       builtin_type_float
     ;       builtin_type_string
     ;       builtin_type_char.
 
+:- type int_type
+    --->    int_type_int
+    ;       int_type_uint
+    ;       int_type_int8
+    ;       int_type_uint8
+    ;       int_type_int16
+    ;       int_type_uint16
+    ;       int_type_int32
+    ;       int_type_uint32.
+
 :- pred is_builtin_type_sym_name(sym_name::in) is semidet.
 
 :- pred is_builtin_type_name(string::in) is semidet.
@@ -569,8 +590,14 @@ is_builtin_type_sym_name(SymName) :-
 is_builtin_type_name(Name) :-
     builtin_type_to_string(_, Name).
 
-builtin_type_to_string(builtin_type_int, "int").
-builtin_type_to_string(builtin_type_uint, "uint").
+builtin_type_to_string(builtin_type_int(int_type_int), "int").
+builtin_type_to_string(builtin_type_int(int_type_uint), "uint").
+builtin_type_to_string(builtin_type_int(int_type_int8), "int8").
+builtin_type_to_string(builtin_type_int(int_type_uint8), "uint8").
+builtin_type_to_string(builtin_type_int(int_type_int16), "int16").
+builtin_type_to_string(builtin_type_int(int_type_uint16), "uint16").
+builtin_type_to_string(builtin_type_int(int_type_int32), "int32").
+builtin_type_to_string(builtin_type_int(int_type_uint32), "uint32").
 builtin_type_to_string(builtin_type_float, "float").
 builtin_type_to_string(builtin_type_string, "string").
 builtin_type_to_string(builtin_type_char, "character").
diff --git a/compiler/prog_out.m b/compiler/prog_out.m
index 3fb778ecc..923ff5908 100644
--- a/compiler/prog_out.m
+++ b/compiler/prog_out.m
@@ -371,6 +371,30 @@ cons_id_and_arity_to_string_maybe_quoted(MangleCons, QuoteCons, ConsId)
         ConsId = uint_const(UInt),
         String = uint_to_string(UInt)
     ;
+        % XXX FIXED SIZE INT
+        ConsId = int8_const(Int8),
+        string.int_to_string(Int8, String)
+    ;
+        % XXX FIXED SIZE INT
+        ConsId = uint8_const(UInt8),
+        string.int_to_string(UInt8, String)
+    ;
+        % XXX FIXED SIZE INT
+        ConsId = int16_const(Int16),
+        string.int_to_string(Int16, String)
+    ;
+        % XXX FIXED SIZE INT
+        ConsId = uint16_const(UInt16),
+        string.int_to_string(UInt16, String)
+    ;
+        % XXX FIXED SIZE INT
+        ConsId = int32_const(Int32),
+        string.int_to_string(Int32, String)
+    ;
+        % XXX FIXED SIZE INT
+        ConsId = uint32_const(UInt32),
+        string.int_to_string(UInt32, String)
+    ;
         ConsId = float_const(Float),
         String = float_to_string(Float)
     ;
diff --git a/compiler/prog_rep.m b/compiler/prog_rep.m
index 266e88b73..46758c9bb 100644
--- a/compiler/prog_rep.m
+++ b/compiler/prog_rep.m
@@ -868,6 +868,12 @@ cons_id_rep(cons(SymName, _, _)) =
 cons_id_rep(tuple_cons(_)) = "{}".
 cons_id_rep(int_const(Int)) = string.int_to_string(Int).
 cons_id_rep(uint_const(UInt)) = string.uint_to_string(UInt).
+cons_id_rep(int8_const(Int8)) = string.int_to_string(Int8).
+cons_id_rep(uint8_const(UInt8)) = string.int_to_string(UInt8).
+cons_id_rep(int16_const(Int16)) = string.int_to_string(Int16).
+cons_id_rep(uint16_const(UInt16)) = string.int_to_string(UInt16).
+cons_id_rep(int32_const(Int32)) = string.int_to_string(Int32).
+cons_id_rep(uint32_const(UInt32)) = string.int_to_string(UInt32).
 cons_id_rep(float_const(Float)) = string.float_to_string(Float).
 cons_id_rep(char_const(Char)) = string.char_to_string(Char).
 cons_id_rep(string_const(String)) = """" ++ String ++ """".
diff --git a/compiler/prog_rep_tables.m b/compiler/prog_rep_tables.m
index 306c9daee..6f4bb5fb5 100644
--- a/compiler/prog_rep_tables.m
+++ b/compiler/prog_rep_tables.m
@@ -130,7 +130,7 @@ lookup_string_in_table(String, StringCode, !StringTable) :-
 is_var_name_in_special_form(String, KindCode, MaybeBaseName, N) :-
     % state_var.m constructs variable names that always contain
     % the state var name, and usually but not always a numeric suffix.
-    % The numeric suffic may be zero or positive. We could represent
+    % The numeric suffix may be zero or positive. We could represent
     % the lack of a suffix using a negative number, but mixing unsigned
     % and signed fields in a single word is tricky, especially since
     % the size of the variable name descriptor word we generate (32 bits)
@@ -327,10 +327,10 @@ add_type_to_table(Type, TypeCode, !StringTable, !TypeTable) :-
     ;
         Type = builtin_type(BuiltinType),
         (
-            BuiltinType = builtin_type_int,
+            BuiltinType = builtin_type_int(int_type_int),
             Selector = 5
         ;
-            BuiltinType = builtin_type_uint,
+            BuiltinType = builtin_type_int(int_type_uint),
             Selector = 6
         ;
             BuiltinType = builtin_type_float,
@@ -341,6 +341,30 @@ add_type_to_table(Type, TypeCode, !StringTable, !TypeTable) :-
         ;
             BuiltinType = builtin_type_char,
             Selector = 9
+        ;
+            % XXX in order to avoid bumping the deep profiler's binary
+            % compatibility version number when the fixed size integers were
+            % added, the newly added types were assigned unused Selector
+            % values.  The next time the format of the program representation
+            % file is changed for some unavoidable reason this should be tidied
+            % up.
+            BuiltinType = builtin_type_int(int_type_int8),
+            Selector = 14
+        ;
+            BuiltinType = builtin_type_int(int_type_uint8),
+            Selector = 15
+        ;
+            BuiltinType = builtin_type_int(int_type_int16),
+            Selector = 16
+        ;
+            BuiltinType = builtin_type_int(int_type_uint16),
+            Selector = 17
+        ;
+            BuiltinType = builtin_type_int(int_type_int32),
+            Selector = 18
+        ;
+            BuiltinType = builtin_type_int(int_type_uint32),
+            Selector = 19
         ),
         TypeBytesCord = cord.singleton(Selector)
     ;
diff --git a/compiler/prog_type.m b/compiler/prog_type.m
index 1333510be..d66dae14c 100644
--- a/compiler/prog_type.m
+++ b/compiler/prog_type.m
@@ -281,8 +281,7 @@
     ;       ctor_cat_user(type_ctor_cat_user).
 
 :- type type_ctor_cat_builtin
-    --->    cat_builtin_int
-    ;       cat_builtin_uint
+    --->    cat_builtin_int(int_type)
     ;       cat_builtin_float
     ;       cat_builtin_char
     ;       cat_builtin_string.
@@ -788,6 +787,12 @@ get_unconstrained_tvars(Tvars, Constraints, Unconstrained) :-
 builtin_type_ctors_with_no_hlds_type_defn =
     [ type_ctor(qualified(mercury_public_builtin_module, "int"), 0),
       type_ctor(qualified(mercury_public_builtin_module, "uint"), 0),
+      type_ctor(qualified(mercury_public_builtin_module, "int8"), 0),
+      type_ctor(qualified(mercury_public_builtin_module, "uint8"), 0),
+      type_ctor(qualified(mercury_public_builtin_module, "int16"), 0),
+      type_ctor(qualified(mercury_public_builtin_module, "uint16"), 0),
+      type_ctor(qualified(mercury_public_builtin_module, "int32"), 0),
+      type_ctor(qualified(mercury_public_builtin_module, "uint32"), 0),
       type_ctor(qualified(mercury_public_builtin_module, "string"), 0),
       type_ctor(qualified(mercury_public_builtin_module, "character"), 0),
       type_ctor(qualified(mercury_public_builtin_module, "float"), 0),
@@ -920,6 +925,12 @@ qualify_cons_id(Args, ConsId0, ConsId, InstConsId) :-
         ; ConsId0 = closure_cons(_, _)
         ; ConsId0 = int_const(_)
         ; ConsId0 = uint_const(_)
+        ; ConsId0 = int8_const(_)
+        ; ConsId0 = uint8_const(_)
+        ; ConsId0 = int16_const(_)
+        ; ConsId0 = uint16_const(_)
+        ; ConsId0 = int32_const(_)
+        ; ConsId0 = uint32_const(_)
         ; ConsId0 = float_const(_)
         ; ConsId0 = char_const(_)
         ; ConsId0 = string_const(_)
diff --git a/compiler/prog_util.m b/compiler/prog_util.m
index 69edd20f6..ca74d6350 100644
--- a/compiler/prog_util.m
+++ b/compiler/prog_util.m
@@ -665,6 +665,12 @@ cons_id_arity(ConsId) = Arity :-
     ;
         ( ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
@@ -690,6 +696,12 @@ cons_id_maybe_arity(cons(_, Arity, _)) = yes(Arity).
 cons_id_maybe_arity(tuple_cons(Arity)) = yes(Arity).
 cons_id_maybe_arity(int_const(_)) = yes(0).
 cons_id_maybe_arity(uint_const(_)) = yes(0).
+cons_id_maybe_arity(int8_const(_)) = yes(0).
+cons_id_maybe_arity(uint8_const(_)) = yes(0).
+cons_id_maybe_arity(int16_const(_)) = yes(0).
+cons_id_maybe_arity(uint16_const(_)) = yes(0).
+cons_id_maybe_arity(int32_const(_)) = yes(0).
+cons_id_maybe_arity(uint32_const(_)) = yes(0).
 cons_id_maybe_arity(float_const(_)) = yes(0).
 cons_id_maybe_arity(char_const(_)) = yes(0).
 cons_id_maybe_arity(string_const(_)) = yes(0).
diff --git a/compiler/rbmm.execution_path.m b/compiler/rbmm.execution_path.m
index 84c7782bf..0722da590 100644
--- a/compiler/rbmm.execution_path.m
+++ b/compiler/rbmm.execution_path.m
@@ -230,6 +230,12 @@ execution_paths_covered_cases(ProcInfo, Switch, [Case | Cases], !ExecPaths) :-
     ;
         ( MainConsId = int_const(_Int)
         ; MainConsId = uint_const(_UInt)
+        ; MainConsId = int8_const(_Int8)
+        ; MainConsId = uint8_const(_UInt8)
+        ; MainConsId = int16_const(_Int16)
+        ; MainConsId = uint16_const(_UInt16)
+        ; MainConsId = int32_const(_Int32)
+        ; MainConsId = uint32_const(_UInt32)
         ; MainConsId = float_const(_Float)
         ; MainConsId = char_const(_Char)
         ; MainConsId = string_const(_String)
diff --git a/compiler/rtti.m b/compiler/rtti.m
index 3bebb2db4..032cd9984 100644
--- a/compiler/rtti.m
+++ b/compiler/rtti.m
@@ -434,6 +434,12 @@
 :- type builtin_ctor
     --->    builtin_ctor_int
     ;       builtin_ctor_uint
+    ;       builtin_ctor_int8
+    ;       builtin_ctor_uint8
+    ;       builtin_ctor_int16
+    ;       builtin_ctor_uint16
+    ;       builtin_ctor_int32
+    ;       builtin_ctor_uint32
     ;       builtin_ctor_float
     ;       builtin_ctor_char
     ;       builtin_ctor_string
@@ -1725,6 +1731,12 @@ type_ctor_rep_to_string(TypeCtorData, RepStr) :-
 
 builtin_ctor_rep_to_string(builtin_ctor_int, "MR_TYPECTOR_REP_INT").
 builtin_ctor_rep_to_string(builtin_ctor_uint, "MR_TYPECTOR_REP_UINT").
+builtin_ctor_rep_to_string(builtin_ctor_int8, "MR_TYPECTOR_REP_INT8").
+builtin_ctor_rep_to_string(builtin_ctor_uint8, "MR_TYPECTOR_REP_UINT8").
+builtin_ctor_rep_to_string(builtin_ctor_int16, "MR_TYPECTOR_REP_INT16").
+builtin_ctor_rep_to_string(builtin_ctor_uint16, "MR_TYPECTOR_REP_UINT16").
+builtin_ctor_rep_to_string(builtin_ctor_int32, "MR_TYPECTOR_REP_INT32").
+builtin_ctor_rep_to_string(builtin_ctor_uint32, "MR_TYPECTOR_REP_UINT32").
 builtin_ctor_rep_to_string(builtin_ctor_string, "MR_TYPECTOR_REP_STRING").
 builtin_ctor_rep_to_string(builtin_ctor_float, "MR_TYPECTOR_REP_FLOAT").
 builtin_ctor_rep_to_string(builtin_ctor_char, "MR_TYPECTOR_REP_CHAR").
@@ -2363,8 +2375,22 @@ tabling_id_has_array_type(Id) = IsArray :-
     tabling_id_base_type(Id, _, IsArray).
 
 table_trie_step_to_c(table_trie_step_dummy, "MR_TABLE_STEP_DUMMY", no).
-table_trie_step_to_c(table_trie_step_int, "MR_TABLE_STEP_INT", no).
-table_trie_step_to_c(table_trie_step_uint, "MR_TABLE_STEP_UINT", no).
+table_trie_step_to_c(table_trie_step_int(int_type_int),
+    "MR_TABLE_STEP_INT", no).
+table_trie_step_to_c(table_trie_step_int(int_type_uint),
+    "MR_TABLE_STEP_UINT", no).
+table_trie_step_to_c(table_trie_step_int(int_type_int8),
+    "MR_TABLE_STEP_INT8", no).
+table_trie_step_to_c(table_trie_step_int(int_type_uint8),
+    "MR_TABLE_STEP_UINT8", no).
+table_trie_step_to_c(table_trie_step_int(int_type_int16),
+    "MR_TABLE_STEP_INT16", no).
+table_trie_step_to_c(table_trie_step_int(int_type_uint16),
+    "MR_TABLE_STEP_UINT16", no).
+table_trie_step_to_c(table_trie_step_int(int_type_int32),
+    "MR_TABLE_STEP_INT32", no).
+table_trie_step_to_c(table_trie_step_int(int_type_uint32),
+    "MR_TABLE_STEP_UINT32", no).
 table_trie_step_to_c(table_trie_step_char, "MR_TABLE_STEP_CHAR", no).
 table_trie_step_to_c(table_trie_step_string, "MR_TABLE_STEP_STRING", no).
 table_trie_step_to_c(table_trie_step_float, "MR_TABLE_STEP_FLOAT", no).
diff --git a/compiler/rtti_to_mlds.m b/compiler/rtti_to_mlds.m
index 3e0041df7..518b74c44 100644
--- a/compiler/rtti_to_mlds.m
+++ b/compiler/rtti_to_mlds.m
@@ -1830,6 +1830,12 @@ add_rtti_defn_arcs_const(DefnDataName, Const, !Graph) :-
         ; Const = mlconst_false
         ; Const = mlconst_int(_)
         ; Const = mlconst_uint(_)
+        ; Const = mlconst_int8(_)
+        ; Const = mlconst_uint8(_)
+        ; Const = mlconst_int16(_)
+        ; Const = mlconst_uint16(_)
+        ; Const = mlconst_int32(_)
+        ; Const = mlconst_uint32(_)
         ; Const = mlconst_enum(_, _)
         ; Const = mlconst_char(_)
         ; Const = mlconst_foreign(_, _, _)
diff --git a/compiler/stack_layout.m b/compiler/stack_layout.m
index ea6219c42..e69377165 100644
--- a/compiler/stack_layout.m
+++ b/compiler/stack_layout.m
@@ -1682,7 +1682,8 @@ construct_user_data_array(Params, VarNumMap, [MaybeAttr | MaybeAttrs],
         MaybeVarNum = yes(VarNum)
     ;
         MaybeAttr = no,
-        LocnTypedRval = typed_rval(const(llconst_int(0)), lt_unsigned),
+        LocnTypedRval = typed_rval(const(llconst_int(0)),
+            lt_int(int_type_uint)),
         MaybeVarNum = no
     ),
     construct_user_data_array(Params, VarNumMap, MaybeAttrs,
@@ -1786,12 +1787,13 @@ construct_type_param_locn_vector([TVar - Locns | TVarLocns], CurSlot,
         ),
         represent_locn_as_int_rval(Locn, Rval),
         construct_type_param_locn_vector(TVarLocns, NextSlot, VectorTail),
-        Vector = [typed_rval(Rval, lt_unsigned) | VectorTail]
+        Vector = [typed_rval(Rval, lt_int(int_type_uint)) | VectorTail]
     else if TVarNum > CurSlot then
         construct_type_param_locn_vector([TVar - Locns | TVarLocns], NextSlot,
             VectorTail),
         % This slot will never be referred to.
-        Vector = [typed_rval(const(llconst_int(0)), lt_unsigned) | VectorTail]
+        Vector = [typed_rval(const(llconst_int(0)),
+            lt_int(int_type_uint)) | VectorTail]
     else
         unexpected($module, $pred, "unsorted tvars")
     ).
@@ -2042,7 +2044,7 @@ construct_tvar_rvals(TVarLocnMap, Vector) :-
     construct_type_param_locn_vector(TVarLocns, 1, TypeParamLocs),
     list.length(TypeParamLocs, TypeParamsLength),
     LengthRval = const(llconst_int(TypeParamsLength)),
-    Vector = [typed_rval(LengthRval, lt_unsigned) | TypeParamLocs].
+    Vector = [typed_rval(LengthRval, lt_int(int_type_uint)) | TypeParamLocs].
 
 %---------------------------------------------------------------------------%
 %
@@ -2078,7 +2080,8 @@ construct_closure_arg_rvals(ClosureArgs, ClosureArgTypedRvals,
     list.map_foldl(construct_closure_arg_rval, ClosureArgs, ArgTypedRvals,
         !StaticCellInfo),
     list.length(ArgTypedRvals, Length),
-    LengthTypedRval = typed_rval(const(llconst_int(Length)), lt_integer),
+    LengthTypedRval = typed_rval(const(llconst_int(Length)),
+        lt_int(int_type_int)),
     ClosureArgTypedRvals = [LengthTypedRval| ArgTypedRvals].
 
 :- pred construct_closure_arg_rval(closure_arg_info::in,
@@ -2200,7 +2203,7 @@ represent_locn_or_const_as_int_rval(Params, LvalOrConst, Rval, Type,
     (
         LvalOrConst = lval(Lval),
         represent_locn_as_int_rval(locn_direct(Lval), Rval),
-        Type = lt_unsigned
+        Type = lt_int(int_type_uint)
     ;
         LvalOrConst = const(_Const),
         UnboxedFloats = Params ^ slp_unboxed_floats,
diff --git a/compiler/string_switch.m b/compiler/string_switch.m
index b172f51ee..bdf6607a0 100644
--- a/compiler/string_switch.m
+++ b/compiler/string_switch.m
@@ -135,7 +135,7 @@ generate_string_hash_switch(Cases, VarRval, VarName, CodeModel, CanFail,
         ArrayElemTypes = [scalar_elem_string]
     else
         NumColumns = 2,
-        RowElemTypes = [lt_string, lt_integer],
+        RowElemTypes = [lt_string, lt_int(int_type_int)],
         ArrayElemTypes = [scalar_elem_string, scalar_elem_int]
     ),
     add_vector_static_cell(RowElemTypes, TableRows, TableAddr, !CI),
@@ -283,7 +283,7 @@ generate_string_hash_simple_lookup_switch(VarRval, CaseValues,
         NumPrevColumns = 2,
         NumColumns = 2 + NumOutVars,
         ArrayElemTypes = [scalar_elem_string, scalar_elem_int | OutElemTypes],
-        RowElemTypes = [lt_string, lt_integer | OutTypes]
+        RowElemTypes = [lt_string, lt_int(int_type_int) | OutTypes]
     ),
     ArrayElemType = array_elem_struct(ArrayElemTypes),
 
@@ -403,14 +403,15 @@ generate_string_hash_several_soln_lookup_switch(VarRval, CaseSolns,
         NumPrevColumns = 1,
         ArrayElemTypes = [scalar_elem_string,
             scalar_elem_int, scalar_elem_int | OutElemTypes],
-        MainRowTypes = [lt_string, lt_integer, lt_integer | OutTypes]
+        MainRowTypes = [lt_string, lt_int(int_type_int),
+            lt_int(int_type_int) | OutTypes]
     else
         NumColumns = 4 + NumOutVars,
         NumPrevColumns = 2,
         ArrayElemTypes = [scalar_elem_string, scalar_elem_int,
             scalar_elem_int, scalar_elem_int | OutElemTypes],
-        MainRowTypes = [lt_string, lt_integer, lt_integer, lt_integer
-            | OutTypes]
+        MainRowTypes = [lt_string, lt_int(int_type_int), lt_int(int_type_int),
+            lt_int(int_type_int) | OutTypes]
     ),
     ArrayElemType = array_elem_struct(ArrayElemTypes),
 
@@ -619,14 +620,14 @@ generate_string_hash_switch_search(Info, VarRval, TableAddrRval,
             BaseReg = RowStartReg,
             MultiplyInstrs = [
                 llds_instr(assign(RowStartReg,
-                    binop(int_mul, lval(SlotReg),
+                    binop(int_mul(int_type_int), lval(SlotReg),
                         const(llconst_int(NumColumns)))),
                     "find the start of the row")
             ]
         ),
         Code = from_list([
             llds_instr(assign(SlotReg,
-                binop(bitwise_and, unop(HashOp, VarRval),
+                binop(bitwise_and(int_type_int), unop(HashOp, VarRval),
                     const(llconst_int(HashMask)))),
                 "compute the hash value of the input string") |
             MultiplyInstrs]) ++
@@ -637,7 +638,8 @@ generate_string_hash_switch_search(Info, VarRval, TableAddrRval,
                 "lookup the string for this hash slot"),
             llds_instr(if_val(
                     binop(logical_or,
-                        binop(eq, lval(StringReg), const(llconst_int(0))),
+                        binop(eq(int_type_int), lval(StringReg),
+                            const(llconst_int(0))),
                         binop(str_ne, lval(StringReg), VarRval)),
                 code_label(FailLabel)),
                 "did we find a match? nofulljump")
@@ -648,13 +650,14 @@ generate_string_hash_switch_search(Info, VarRval, TableAddrRval,
     else
         Code = from_list([
             llds_instr(assign(SlotReg,
-                binop(bitwise_and, unop(HashOp, VarRval),
+                binop(bitwise_and(int_type_int), unop(HashOp, VarRval),
                     const(llconst_int(HashMask)))),
                 "compute the hash value of the input string"),
             llds_instr(label(LoopStartLabel),
                 "begin hash chain loop, nofulljump"),
             llds_instr(assign(RowStartReg,
-                binop(int_mul, lval(SlotReg), const(llconst_int(NumColumns)))),
+                binop(int_mul(int_type_int), lval(SlotReg),
+                    const(llconst_int(NumColumns)))),
                 "find the start of the row"),
             llds_instr(assign(StringReg,
                 binop(array_index(ArrayElemType), TableAddrRval,
@@ -662,7 +665,8 @@ generate_string_hash_switch_search(Info, VarRval, TableAddrRval,
                 "lookup the string for this hash slot"),
             llds_instr(if_val(
                     binop(logical_or,
-                        binop(eq, lval(StringReg), const(llconst_int(0))),
+                        binop(eq(int_type_int), lval(StringReg),
+                            const(llconst_int(0))),
                         binop(str_ne, lval(StringReg), VarRval)),
                 code_label(NoMatchLabel)),
                 "did we find a match? nofulljump")
@@ -671,10 +675,12 @@ generate_string_hash_switch_search(Info, VarRval, TableAddrRval,
                 "no match yet, nofulljump"),
             llds_instr(assign(SlotReg,
                 binop(array_index(ArrayElemType), TableAddrRval,
-                    binop(int_add, lval(RowStartReg), const(llconst_int(1))))),
+                    binop(int_add(int_type_int), lval(RowStartReg),
+                        const(llconst_int(1))))),
                 "get next slot in hash chain"),
             llds_instr(
-                if_val(binop(int_ge, lval(SlotReg), const(llconst_int(0))),
+                if_val(binop(int_ge(int_type_int), lval(SlotReg),
+                        const(llconst_int(0))),
                     code_label(LoopStartLabel)),
                 "if we have not reached the end of the chain, keep searching"),
             llds_instr(label(FailLabel),
@@ -706,7 +712,7 @@ generate_string_binary_switch(Cases, VarRval, VarName, CodeModel, CanFail,
     list.reverse(RevTableRows, TableRows),
     list.reverse(RevTargets, Targets),
     NumColumns = 2,
-    RowElemTypes = [lt_string, lt_integer],
+    RowElemTypes = [lt_string, lt_int(int_type_int)],
     add_vector_static_cell(RowElemTypes, TableRows, TableAddr, !CI),
     ArrayElemTypes = [scalar_elem_string, scalar_elem_int],
     ArrayElemType = array_elem_struct(ArrayElemTypes),
@@ -722,8 +728,8 @@ generate_string_binary_switch(Cases, VarRval, VarName, CodeModel, CanFail,
         llds_instr(computed_goto(
             binop(array_index(ArrayElemType),
                 TableAddrRval,
-                    binop(int_add,
-                        binop(int_mul,
+                    binop(int_add(int_type_int),
+                        binop(int_mul(int_type_int),
                             lval(MidReg),
                             const(llconst_int(NumColumns))),
                         const(llconst_int(1)))),
@@ -836,7 +842,7 @@ generate_string_binary_simple_lookup_switch(VarRval, CaseValues,
                 assign(BaseReg,
                     mem_addr(
                         heap_ref(VectorAddrRval, yes(0),
-                            binop(int_mul,
+                            binop(int_mul(int_type_int),
                                 lval(MidReg),
                                 const(llconst_int(NumColumns)))))),
                 "set up base reg")
@@ -937,7 +943,8 @@ generate_string_binary_several_soln_lookup_switch(VarRval, CaseSolns,
     list.reverse(AscendingSortedCountKinds, DescendingSortedCountKinds),
     assoc_list.values(DescendingSortedCountKinds, DescendingSortedKinds),
 
-    MainRowTypes = [lt_string, lt_integer, lt_integer | OutTypes],
+    MainRowTypes = [lt_string, lt_int(int_type_int),
+        lt_int(int_type_int) | OutTypes],
     list.length(MainRowTypes, MainNumColumns),
     add_vector_static_cell(MainRowTypes, MainRows, MainVectorAddr, !CI),
     MainVectorAddrRval = const(llconst_data_addr(MainVectorAddr, no)),
@@ -954,7 +961,7 @@ generate_string_binary_several_soln_lookup_switch(VarRval, CaseSolns,
             assign(BaseReg,
                 mem_addr(
                     heap_ref(MainVectorAddrRval, yes(0),
-                        binop(int_mul,
+                        binop(int_mul(int_type_int),
                             lval(MidReg),
                             const(llconst_int(MainNumColumns)))))),
             "set up base reg")
@@ -1084,39 +1091,45 @@ generate_string_binary_switch_search(Info, VarRval, TableAddrRval,
         llds_instr(assign(HiReg, const(llconst_int(MaxIndex))), ""),
         llds_instr(label(LoopStartLabel),
             "begin table search loop, nofulljump"),
-        llds_instr(if_val(binop(int_gt, lval(LoReg), lval(HiReg)),
+        llds_instr(if_val(binop(
+            int_gt(int_type_int), lval(LoReg), lval(HiReg)),
             code_label(FailLabel)),
             "have we searched all of the table?"),
         llds_instr(assign(MidReg,
-            binop(int_div,
-                binop(int_add, lval(LoReg), lval(HiReg)),
+            binop(int_div(int_type_int),
+                binop(int_add(int_type_int), lval(LoReg), lval(HiReg)),
                 const(llconst_int(2)))), ""),
         llds_instr(assign(ResultReg,
             binop(str_cmp,
                 VarRval,
                 binop(array_index(ArrayElemType),
                     TableAddrRval,
-                        binop(int_mul,
+                        binop(int_mul(int_type_int),
                             lval(MidReg),
                             const(llconst_int(NumColumns)))))),
             "compare with the middle element"),
 
         llds_instr(if_val(
-            binop(int_ge, lval(ResultReg), const(llconst_int(0))),
+            binop(int_ge(int_type_int), lval(ResultReg),
+                const(llconst_int(0))),
             code_label(GtEqLabel)),
             "branch away unless key is in lo half"),
         llds_instr(assign(HiReg,
-            binop(int_sub, lval(MidReg), const(llconst_int(1)))), ""),
+            binop(int_sub(int_type_int), lval(MidReg),
+                const(llconst_int(1)))),
+            ""),
         llds_instr(goto(code_label(LoopStartLabel)),
             "go back to search the remaining lo half"),
         llds_instr(label(GtEqLabel), "nofulljump"),
 
         llds_instr(if_val(
-            binop(int_le, lval(ResultReg), const(llconst_int(0))),
+            binop(int_le(int_type_int), lval(ResultReg),
+                const(llconst_int(0))),
             code_label(EqLabel)),
             "branch away unless key is in hi half"),
         llds_instr(assign(LoReg,
-            binop(int_add, lval(MidReg), const(llconst_int(1)))), ""),
+            binop(int_add(int_type_int), lval(MidReg), const(llconst_int(1)))),
+            ""),
         llds_instr(goto(code_label(LoopStartLabel)),
             "go back to search the remaining hi half"),
         llds_instr(label(FailLabel),
diff --git a/compiler/switch_gen.m b/compiler/switch_gen.m
index fe10858e2..52c8e58be 100644
--- a/compiler/switch_gen.m
+++ b/compiler/switch_gen.m
@@ -457,6 +457,12 @@ is_reserved_addr_tag(ConsTag) = IsReservedAddr :-
     ;
         ( ConsTag = int_tag(_)
         ; ConsTag = uint_tag(_)
+        ; ConsTag = int8_tag(_)
+        ; ConsTag = uint8_tag(_)
+        ; ConsTag = int16_tag(_)
+        ; ConsTag = uint16_tag(_)
+        ; ConsTag = int32_tag(_)
+        ; ConsTag = uint32_tag(_)
         ; ConsTag = float_tag(_)
         ; ConsTag = string_tag(_)
         ; ConsTag = foreign_tag(_, _)
diff --git a/compiler/switch_util.m b/compiler/switch_util.m
index 7ec3360da..79423e4bc 100644
--- a/compiler/switch_util.m
+++ b/compiler/switch_util.m
@@ -506,8 +506,7 @@ num_cons_ids_in_tagged_cases_loop([TaggedCase | TaggedCases],
 type_ctor_cat_to_switch_cat(CtorCat) = SwitchCat :-
     (
         ( CtorCat = ctor_cat_enum(_)
-        ; CtorCat = ctor_cat_builtin(cat_builtin_int)
-        ; CtorCat = ctor_cat_builtin(cat_builtin_uint)
+        ; CtorCat = ctor_cat_builtin(cat_builtin_int(_))
         ; CtorCat = ctor_cat_builtin(cat_builtin_char)
         ),
         SwitchCat = atomic_switch
@@ -539,6 +538,12 @@ estimate_switch_tag_test_cost(Tag) = Cost :-
     (
         ( Tag = int_tag(_)
         ; Tag = uint_tag(_)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = foreign_tag(_, _)
         ; Tag = reserved_address_tag(_)
         ; Tag = shared_local_tag(_, _)
@@ -1238,6 +1243,12 @@ get_ptag_counts_loop([Tag | Tags], !MaxPrimary, !PtagCountMap) :-
         ; Tag = float_tag(_)
         ; Tag = int_tag(_)
         ; Tag = uint_tag(_)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = foreign_tag(_, _)
         ; Tag = closure_tag(_, _, _)
         ; Tag = type_ctor_info_tag(_, _, _)
@@ -1343,6 +1354,12 @@ group_case_by_ptag(CaseId, CaseRep, TaggedConsId,
         ; Tag = float_tag(_)
         ; Tag = int_tag(_)
         ; Tag = uint_tag(_)
+        ; Tag = int8_tag(_)
+        ; Tag = uint8_tag(_)
+        ; Tag = int16_tag(_)
+        ; Tag = uint16_tag(_)
+        ; Tag = int32_tag(_)
+        ; Tag = uint32_tag(_)
         ; Tag = foreign_tag(_, _)
         ; Tag = closure_tag(_, _, _)
         ; Tag = type_ctor_info_tag(_, _, _)
diff --git a/compiler/table_gen.m b/compiler/table_gen.m
index dc048dbf3..9300a75c4 100644
--- a/compiler/table_gen.m
+++ b/compiler/table_gen.m
@@ -2470,8 +2470,7 @@ gen_lookup_call_for_type(ArgTablingMethod0, CtorCat, Type, ArgVar, VarSeqNum,
         Type, bp_native_if_possible),
     (
         ( CtorCat = ctor_cat_enum(_)
-        ; CtorCat = ctor_cat_builtin(cat_builtin_int)
-        ; CtorCat = ctor_cat_builtin(cat_builtin_uint)
+        ; CtorCat = ctor_cat_builtin(cat_builtin_int(_))
         ; CtorCat = ctor_cat_builtin(cat_builtin_char)
         ; CtorCat = ctor_cat_void
         ),
@@ -2559,13 +2558,9 @@ gen_lookup_call_for_type(ArgTablingMethod0, CtorCat, Type, ArgVar, VarSeqNum,
                 ArgName ++ ", " ++ next_table_node_name ++ ");\n"
         ;
             (
-                CtorCat = ctor_cat_builtin(cat_builtin_int),
-                CatString = "int",
-                Step = table_trie_step_int
-            ;
-                CtorCat = ctor_cat_builtin(cat_builtin_uint),
-                CatString = "uint",
-                Step = table_trie_step_uint
+                CtorCat = ctor_cat_builtin(cat_builtin_int(IntType)),
+                CatString = int_type_to_cat_string(IntType),
+                Step = table_trie_step_int(IntType)
             ;
                 CtorCat = ctor_cat_builtin(cat_builtin_char),
                 CatString = "char",
@@ -2621,11 +2616,8 @@ gen_lookup_call_for_type(ArgTablingMethod0, CtorCat, Type, ArgVar, VarSeqNum,
             CtorCat = ctor_cat_enum(_),
             unexpected($module, $pred, "tabling enums by addr")
         ;
-            CtorCat = ctor_cat_builtin(cat_builtin_int),
-            unexpected($module, $pred, "tabling ints by addr")
-        ;
-            CtorCat = ctor_cat_builtin(cat_builtin_uint),
-            unexpected($module, $pred, "tabling uints by addr")
+            CtorCat = ctor_cat_builtin(cat_builtin_int(_)),
+            unexpected($module, $pred, "tabling integer type by addr")
         ;
             CtorCat = ctor_cat_builtin(cat_builtin_char),
             unexpected($module, $pred, "tabling chars by addr")
@@ -2673,6 +2665,17 @@ gen_lookup_call_for_type(ArgTablingMethod0, CtorCat, Type, ArgVar, VarSeqNum,
         CodeStr = LookupCodeStr ++ LookupStatsCodeStr ++ UpdateCurNodeCodeStr
     ).
 
+:- func int_type_to_cat_string(int_type) = string.
+
+int_type_to_cat_string(int_type_int) = "int".
+int_type_to_cat_string(int_type_uint) = "uint".
+int_type_to_cat_string(int_type_int8) = "int8".
+int_type_to_cat_string(int_type_uint8) = "uint8".
+int_type_to_cat_string(int_type_int16) = "int16".
+int_type_to_cat_string(int_type_uint16) = "uint16".
+int_type_to_cat_string(int_type_int32) = "int32".
+int_type_to_cat_string(int_type_uint32) = "uint32".
+
 :- pred gen_general_lookup_call(table_value_or_addr::in, string::in,
     mer_type::in, foreign_arg::in, string::in, int::in, maybe(string)::in,
     string::in, string::in, term.context::in,
@@ -3653,12 +3656,30 @@ type_save_category(CtorCat, Name) :-
         CtorCat = ctor_cat_enum(cat_enum_foreign),
         sorry($module, $pred, "tabling and foreign enumerations NYI.")
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_int),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int)),
         Name = "int"
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_uint),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint)),
         Name = "uint"
     ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int8)),
+        Name = "int8"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint8)),
+        Name = "uint8"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int16)),
+        Name = "int16"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint16)),
+        Name = "uint16"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int32)),
+        Name = "int32"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint32)),
+        Name = "uint32"
+    ;
         CtorCat = ctor_cat_builtin(cat_builtin_float),
         Name = "float"
     ;
diff --git a/compiler/tag_switch.m b/compiler/tag_switch.m
index 4b89f1050..6b47d4ca5 100644
--- a/compiler/tag_switch.m
+++ b/compiler/tag_switch.m
@@ -395,7 +395,7 @@ generate_primary_try_me_else_chain_case(PtagRval, StagReg,
         MainPtag, OtherPtags, PtagCase, MaxSecondary, VarRval, MaybeFailLabel,
         Code, !CaseLabelMap, !CI) :-
     get_next_label(ElseLabel, !CI),
-    TestRval0 = binop(ne, PtagRval,
+    TestRval0 = binop(ne(int_type_int), PtagRval,
         unop(mktag, const(llconst_int(MainPtag)))),
     generate_primary_try_me_else_chain_other_ptags(OtherPtags, PtagRval,
         TestRval0, TestRval),
@@ -418,7 +418,7 @@ generate_primary_try_me_else_chain_case(PtagRval, StagReg,
 generate_primary_try_me_else_chain_other_ptags([], _, TestRval, TestRval).
 generate_primary_try_me_else_chain_other_ptags([OtherPtag | OtherPtags],
         PtagRval, TestRval0, TestRval) :-
-    ThisTestRval = binop(ne, PtagRval,
+    ThisTestRval = binop(ne(int_type_int), PtagRval,
         unop(mktag, const(llconst_int(OtherPtag)))),
     TestRval1 = binop(logical_and, TestRval0, ThisTestRval),
     generate_primary_try_me_else_chain_other_ptags(OtherPtags,
@@ -495,7 +495,7 @@ generate_primary_try_chain_case(PtagRval, StagReg, MainPtag, OtherPtags,
         PrevTestsCode0, PrevTestsCode, PrevCasesCode0, PrevCasesCode,
         !CaseLabelMap, !CI) :-
     get_next_label(ThisPtagLabel, !CI),
-    TestRval0 = binop(eq, PtagRval,
+    TestRval0 = binop(eq(int_type_int), PtagRval,
         unop(mktag, const(llconst_int(MainPtag)))),
     generate_primary_try_chain_other_ptags(OtherPtags, PtagRval,
         TestRval0, TestRval),
@@ -520,7 +520,7 @@ generate_primary_try_chain_case(PtagRval, StagReg, MainPtag, OtherPtags,
 generate_primary_try_chain_other_ptags([], _, TestRval, TestRval).
 generate_primary_try_chain_other_ptags([OtherPtag | OtherPtags],
         PtagRval, TestRval0, TestRval) :-
-    ThisTestRval = binop(eq, PtagRval,
+    ThisTestRval = binop(eq(int_type_int), PtagRval,
         unop(mktag, const(llconst_int(OtherPtag)))),
     TestRval1 = binop(logical_or, TestRval0, ThisTestRval),
     generate_primary_try_chain_other_ptags(OtherPtags,
@@ -644,7 +644,7 @@ generate_primary_binary_search(PtagGroups, MinPtag, MaxPtag, PtagRval, StagReg,
         LabelComment = "code for ptags " ++
             HighStartStr ++ " to " ++ HighEndStr,
         LowRangeEndConst = const(llconst_int(LowRangeEnd)),
-        TestRval = binop(int_gt, PtagRval, LowRangeEndConst),
+        TestRval = binop(int_gt(int_type_int), PtagRval, LowRangeEndConst),
         IfCode = singleton(
             llds_instr(if_val(TestRval, code_label(NewLabel)), IfComment)
         ),
@@ -843,7 +843,8 @@ generate_secondary_try_me_else_chain_case(CaseLabel, StagRval, Secondary,
     get_next_label(ElseLabel, !CI),
     TestCode = singleton(
         llds_instr(
-            if_val(binop(ne, StagRval, const(llconst_int(Secondary))),
+            if_val(binop(ne(int_type_int), StagRval,
+                    const(llconst_int(Secondary))),
                 code_label(ElseLabel)),
             "test sec tag only")
     ),
@@ -898,7 +899,8 @@ generate_secondary_try_chain_case(CaseLabel, StagRval, Secondary,
     CaseInfo0 = case_label_info(Comment, _CaseCode, _CaseGenerated),
     TestCode = singleton(
         llds_instr(
-            if_val(binop(eq, StagRval, const(llconst_int(Secondary))),
+            if_val(binop(eq(int_type_int), StagRval,
+                    const(llconst_int(Secondary))),
                 code_label(CaseLabel)),
             "test sec tag only for " ++ Comment)
     ),
@@ -988,7 +990,7 @@ generate_secondary_binary_search(StagGoals, MinStag, MaxStag, StagRval,
         LabelComment = "code for stags " ++
             HighStartStr ++ " to " ++ HighEndStr,
         LowRangeEndConst = const(llconst_int(LowRangeEnd)),
-        TestRval = binop(int_gt, StagRval, LowRangeEndConst),
+        TestRval = binop(int_gt(int_type_int), StagRval, LowRangeEndConst),
         IfCode = singleton(
             llds_instr(if_val(TestRval, code_label(NewLabel)), IfComment)
         ),
diff --git a/compiler/trace_gen.m b/compiler/trace_gen.m
index c68e60b4d..c9ddce804 100644
--- a/compiler/trace_gen.m
+++ b/compiler/trace_gen.m
@@ -993,7 +993,8 @@ generate_tailrec_reset_slots_code(TraceInfo, Code, !CI) :-
         TailRecInfo = yes(TailRecLval - _),
         TailRecLvalCode = singleton(
             llds_instr(assign(TailRecLval,
-                binop(int_add, lval(TailRecLval), const(llconst_int(1)))),
+                binop(int_add(int_type_int), lval(TailRecLval),
+                    const(llconst_int(1)))),
                 "increment tail recursion counter")
         )
     ;
diff --git a/compiler/transform_llds.m b/compiler/transform_llds.m
index ff8cb9018..7e34ad677 100644
--- a/compiler/transform_llds.m
+++ b/compiler/transform_llds.m
@@ -45,6 +45,8 @@
 :- import_module mdbcomp.
 :- import_module mdbcomp.prim_data.
 :- import_module mdbcomp.sym_name.
+:- import_module parse_tree.
+:- import_module parse_tree.prog_data.
 
 :- import_module counter.
 :- import_module int.
@@ -195,8 +197,9 @@ split_computed_goto(Rval, Targets, Comment, Instrs, !C, MaxSize, NumTargets,
         counter.allocate(LabelNum, !C),
         Mid = NumTargets // 2,
         list.det_split_list(Mid, Targets, StartTargets, EndTargets),
-        Index     = binop(int_sub, Rval, const(llconst_int(Mid))),
-        Test      = binop(int_ge,  Rval, const(llconst_int(Mid))),
+        Index     = binop(int_sub(int_type_int), Rval, const(llconst_int(Mid))),
+        Test      = binop(int_ge(int_type_int),  Rval,
+            const(llconst_int(Mid))),
         ElseAddr  = code_label(internal_label(LabelNum, ProcLabel)),
         IfInstr   = llds_instr(if_val(Test, ElseAddr), "binary search"),
         ElseInstr = llds_instr(label(internal_label(LabelNum, ProcLabel)), ""),
diff --git a/compiler/type_constraints.m b/compiler/type_constraints.m
index fcc90cf32..f237ad33c 100644
--- a/compiler/type_constraints.m
+++ b/compiler/type_constraints.m
@@ -2095,7 +2095,14 @@ pred_has_arity(Preds, Arity, PredId) :-
     %
 :- pred builtin_atomic_type(cons_id::in, builtin_type::out) is semidet.
 
-builtin_atomic_type(int_const(_), builtin_type_int).
+builtin_atomic_type(int_const(_), builtin_type_int(int_type_int)).
+builtin_atomic_type(uint_const(_), builtin_type_int(int_type_uint)).
+builtin_atomic_type(int8_const(_), builtin_type_int(int_type_int8)).
+builtin_atomic_type(uint8_const(_), builtin_type_int(int_type_uint8)).
+builtin_atomic_type(int16_const(_), builtin_type_int(int_type_int16)).
+builtin_atomic_type(uint16_const(_), builtin_type_int(int_type_uint16)).
+builtin_atomic_type(int32_const(_), builtin_type_int(int_type_int32)).
+builtin_atomic_type(uint32_const(_), builtin_type_int(int_type_uint32)).
 builtin_atomic_type(float_const(_), builtin_type_float).
 builtin_atomic_type(string_const(_), builtin_type_string).
 builtin_atomic_type(cons(unqualified(String), 0, _), builtin_type_char) :-
@@ -2110,7 +2117,7 @@ builtin_atomic_type(impl_defined_const(Name), Type) :-
         Type = builtin_type_string
     ;
         Name = "line",
-        Type = builtin_type_int
+        Type = builtin_type_int(int_type_int)
     ).
 
     % Creates a new id for a type constraint, then maps each of the given type
@@ -2424,12 +2431,30 @@ type_to_string(TVarSet, Type, Name) :-
         SubtypeName = string.join_list(", ", SubtypeNames),
         Name = sym_name_to_string(SymName) ++ "(" ++ SubtypeName ++ ")"
     ;
-        Type = builtin_type(builtin_type_int),
+        Type = builtin_type(builtin_type_int(int_type_int)),
         Name = "int"
     ;
-        Type = builtin_type(builtin_type_uint),
+        Type = builtin_type(builtin_type_int(int_type_uint)),
         Name = "uint"
     ;
+        Type = builtin_type(builtin_type_int(int_type_int8)),
+        Name = "int8"
+    ;
+        Type = builtin_type(builtin_type_int(int_type_uint8)),
+        Name = "uint8"
+    ;
+        Type = builtin_type(builtin_type_int(int_type_int16)),
+        Name = "int16"
+    ;
+        Type = builtin_type(builtin_type_int(int_type_uint16)),
+        Name = "uint16"
+    ;
+        Type = builtin_type(builtin_type_int(int_type_int32)),
+        Name = "int32"
+    ;
+        Type = builtin_type(builtin_type_int(int_type_uint32)),
+        Name = "uint32"
+    ;
         Type = builtin_type(builtin_type_float),
         Name = "float"
     ;
diff --git a/compiler/type_ctor_info.m b/compiler/type_ctor_info.m
index b83b9d6d6..cc6569b8e 100644
--- a/compiler/type_ctor_info.m
+++ b/compiler/type_ctor_info.m
@@ -439,6 +439,12 @@ construct_type_ctor_info(TypeCtorGenInfo, ModuleInfo, RttiData) :-
 % to be done there as well.
 builtin_type_ctor("builtin", "int", 0, builtin_ctor_int).
 builtin_type_ctor("builtin", "uint", 0, builtin_ctor_uint).
+builtin_type_ctor("builtin", "int8", 0, builtin_ctor_int8).
+builtin_type_ctor("builtin", "uint8", 0, builtin_ctor_uint8).
+builtin_type_ctor("builtin", "int16", 0, builtin_ctor_int16).
+builtin_type_ctor("builtin", "uint16", 0, builtin_ctor_uint16).
+builtin_type_ctor("builtin", "int32", 0, builtin_ctor_int32).
+builtin_type_ctor("builtin", "uint32", 0, builtin_ctor_uint32).
 builtin_type_ctor("builtin", "string", 0, builtin_ctor_string).
 builtin_type_ctor("builtin", "float", 0, builtin_ctor_float).
 builtin_type_ctor("builtin", "character", 0, builtin_ctor_char).
@@ -656,6 +662,12 @@ make_foreign_enum_functors(TypeCtor, Lang, [Functor | Functors], NextOrdinal,
         ; ConsTag = float_tag(_)
         ; ConsTag = int_tag(_)
         ; ConsTag = uint_tag(_)
+        ; ConsTag = int8_tag(_)
+        ; ConsTag = uint8_tag(_)
+        ; ConsTag = int16_tag(_)
+        ; ConsTag = uint16_tag(_)
+        ; ConsTag = int32_tag(_)
+        ; ConsTag = uint32_tag(_)
         ; ConsTag = closure_tag(_, _, _)
         ; ConsTag = type_ctor_info_tag(_, _, _)
         ; ConsTag = base_typeclass_info_tag(_, _, _)
@@ -838,6 +850,12 @@ get_maybe_reserved_rep(ConsTag, ConsRep) :-
         ; ConsTag = string_tag(_)
         ; ConsTag = int_tag(_)
         ; ConsTag = uint_tag(_)
+        ; ConsTag = int8_tag(_)
+        ; ConsTag = uint8_tag(_)
+        ; ConsTag = int16_tag(_)
+        ; ConsTag = uint16_tag(_)
+        ; ConsTag = int32_tag(_)
+        ; ConsTag = uint32_tag(_)
         ; ConsTag = foreign_tag(_, _)
         ; ConsTag = float_tag(_)
         ; ConsTag = closure_tag(_, _, _)
diff --git a/compiler/type_util.m b/compiler/type_util.m
index 589525c0a..4537cb541 100644
--- a/compiler/type_util.m
+++ b/compiler/type_util.m
@@ -837,11 +837,29 @@ classify_type_ctor(ModuleInfo, TypeCtor) = TypeCategory :-
             TypeName = "character",
             TypeCategoryPrime = ctor_cat_builtin(cat_builtin_char)
         ;
+            TypeName = "int",
+            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int(int_type_int))
+        ;
             TypeName = "uint",
-            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_uint)
+            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int(int_type_uint))
         ;
-            TypeName = "int",
-            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int)
+            TypeName = "int8",
+            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int(int_type_int8))
+        ;
+            TypeName = "uint8",
+            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int(int_type_uint8))
+        ;
+            TypeName = "int16",
+            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int(int_type_int16))
+        ;
+            TypeName = "uint16",
+            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int(int_type_uint16))
+        ;
+            TypeName = "int32",
+            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int(int_type_int32))
+        ;
+            TypeName = "uint32",
+            TypeCategoryPrime = ctor_cat_builtin(cat_builtin_int(int_type_uint32))
         ;
             TypeName = "float",
             TypeCategoryPrime = ctor_cat_builtin(cat_builtin_float)
@@ -961,8 +979,7 @@ update_type_may_use_atomic_alloc(ModuleInfo, Type, !MayUseAtomic) :-
 type_may_use_atomic_alloc(ModuleInfo, Type) = TypeMayUseAtomic :-
     TypeCategory = classify_type(ModuleInfo, Type),
     (
-        ( TypeCategory = ctor_cat_builtin(cat_builtin_int)
-        ; TypeCategory = ctor_cat_builtin(cat_builtin_uint)
+        ( TypeCategory = ctor_cat_builtin(cat_builtin_int(_))
         ; TypeCategory = ctor_cat_builtin(cat_builtin_char)
         ; TypeCategory = ctor_cat_enum(_)
         ; TypeCategory = ctor_cat_builtin_dummy
diff --git a/compiler/typecheck.m b/compiler/typecheck.m
index 5ccd2fccb..07e679d7e 100644
--- a/compiler/typecheck.m
+++ b/compiler/typecheck.m
@@ -2234,11 +2234,35 @@ cons_id_must_be_builtin_type(ConsId, ConsType, BuiltinTypeName) :-
     (
         ConsId = int_const(_),
         BuiltinTypeName = "int",
-        BuiltinType = builtin_type_int
+        BuiltinType = builtin_type_int(int_type_int)
     ;
         ConsId = uint_const(_),
         BuiltinTypeName = "uint",
-        BuiltinType = builtin_type_uint
+        BuiltinType = builtin_type_int(int_type_uint)
+    ;
+        ConsId = int8_const(_),
+        BuiltinTypeName = "int8",
+        BuiltinType = builtin_type_int(int_type_int8)
+    ;
+        ConsId = uint8_const(_),
+        BuiltinTypeName = "uint8",
+        BuiltinType = builtin_type_int(int_type_uint8)
+    ;
+        ConsId = int16_const(_),
+        BuiltinTypeName = "int16",
+        BuiltinType = builtin_type_int(int_type_int16)
+    ;
+        ConsId = uint16_const(_),
+        BuiltinTypeName = "uint16",
+        BuiltinType = builtin_type_int(int_type_uint16)
+    ;
+        ConsId = int32_const(_),
+        BuiltinTypeName = "int32",
+        BuiltinType = builtin_type_int(int_type_int32)
+    ;
+        ConsId = uint32_const(_),
+        BuiltinTypeName = "uint32",
+        BuiltinType = builtin_type_int(int_type_uint32)
     ;
         ConsId = float_const(_),
         BuiltinTypeName = "float",
@@ -2774,6 +2798,12 @@ type_assign_unify_type(X, Y, TypeAssign0, TypeAssign) :-
 
 builtin_atomic_type(int_const(_), "int").
 builtin_atomic_type(uint_const(_), "uint").
+builtin_atomic_type(int8_const(_), "int8").
+builtin_atomic_type(uint8_const(_), "uint8").
+builtin_atomic_type(int16_const(_), "int16").
+builtin_atomic_type(uint16_const(_), "uint16").
+builtin_atomic_type(int32_const(_), "int32").
+builtin_atomic_type(uint32_const(_), "uint32").
 builtin_atomic_type(float_const(_), "float").
 builtin_atomic_type(char_const(_), "character").
 builtin_atomic_type(string_const(_), "string").
diff --git a/compiler/unify_gen.m b/compiler/unify_gen.m
index 6ec77d931..36de1c09a 100644
--- a/compiler/unify_gen.m
+++ b/compiler/unify_gen.m
@@ -288,7 +288,8 @@ generate_test(VarA, VarB, Code, !CI, !CLD) :-
         else if Type = builtin_type(builtin_type_float) then
             Op = float_eq
         else
-            Op = eq
+            % XXX FIXED SIZE AND UINTS??
+            Op = eq(int_type_int)
         ),
         fail_if_rval_is_false(binop(Op, ValA, ValB), FailCode, !CI, !CLD),
         Code = CodeA ++ CodeB ++ FailCode
@@ -418,16 +419,34 @@ raw_tag_test(Rval, ConsTag, TestRval) :-
         TestRval = binop(float_eq, Rval, const(llconst_float(Float)))
     ;
         ConsTag = int_tag(Int),
-        TestRval = binop(eq, Rval, const(llconst_int(Int)))
+        TestRval = binop(eq(int_type_int), Rval, const(llconst_int(Int)))
     ;
         ConsTag = uint_tag(UInt),
-        TestRval = binop(uint_eq, Rval, const(llconst_uint(UInt)))
+        TestRval = binop(eq(int_type_uint), Rval, const(llconst_uint(UInt)))
+    ;
+        ConsTag = int8_tag(Int8),
+        TestRval = binop(eq(int_type_int8), Rval, const(llconst_int8(Int8)))
+    ;
+        ConsTag = uint8_tag(UInt8),
+        TestRval = binop(eq(int_type_uint8), Rval, const(llconst_uint8(UInt8)))
+    ;
+        ConsTag = int16_tag(Int16),
+        TestRval = binop(eq(int_type_int16), Rval, const(llconst_int16(Int16)))
+    ;
+        ConsTag = uint16_tag(UInt16),
+        TestRval = binop(eq(int_type_uint16), Rval, const(llconst_uint16(UInt16)))
+    ;
+        ConsTag = int32_tag(Int32),
+        TestRval = binop(eq(int_type_int32), Rval, const(llconst_int32(Int32)))
+    ;
+        ConsTag = uint32_tag(UInt32),
+        TestRval = binop(eq(int_type_uint32), Rval, const(llconst_uint32(UInt32)))
     ;
         ConsTag = foreign_tag(ForeignLang, ForeignVal),
         expect(unify(ForeignLang, lang_c), $module, $pred,
             "foreign tag for language other than C"),
-        TestRval = binop(eq, Rval,
-            const(llconst_foreign(ForeignVal, lt_integer)))
+        TestRval = binop(eq(int_type_int), Rval,
+            const(llconst_foreign(ForeignVal, lt_int(int_type_int))))
     ;
         ConsTag = closure_tag(_, _, _),
         % This should never happen, since the error will be detected
@@ -472,23 +491,23 @@ raw_tag_test(Rval, ConsTag, TestRval) :-
         ),
         VarPtag = unop(tag, Rval),
         ConstPtag = unop(mktag, const(llconst_int(UnsharedTag))),
-        TestRval = binop(eq, VarPtag, ConstPtag)
+        TestRval = binop(eq(int_type_int), VarPtag, ConstPtag)
     ;
         ConsTag = shared_remote_tag(Bits, Num),
         VarPtag = unop(tag, Rval),
         ConstPtag = unop(mktag, const(llconst_int(Bits))),
-        PtagTestRval = binop(eq, VarPtag, ConstPtag),
+        PtagTestRval = binop(eq(int_type_int), VarPtag, ConstPtag),
         VarStag = lval(field(yes(Bits), Rval, const(llconst_int(0)))),
         ConstStag = const(llconst_int(Num)),
-        StagTestRval = binop(eq, VarStag, ConstStag),
+        StagTestRval = binop(eq(int_type_int), VarStag, ConstStag),
         TestRval = binop(logical_and, PtagTestRval, StagTestRval)
     ;
         ConsTag = shared_local_tag(Bits, Num),
         ConstStag = mkword(Bits, unop(mkbody, const(llconst_int(Num)))),
-        TestRval = binop(eq, Rval, ConstStag)
+        TestRval = binop(eq(int_type_int), Rval, ConstStag)
     ;
         ConsTag = reserved_address_tag(RA),
-        TestRval = binop(eq, Rval, generate_reserved_address(RA))
+        TestRval = binop(eq(int_type_int), Rval, generate_reserved_address(RA))
     ;
         ConsTag = shared_with_reserved_addresses_tag(ReservedAddrs, ThisTag),
         % We first check that the Rval doesn't match any of the ReservedAddrs,
@@ -558,10 +577,34 @@ generate_construction_2(ConsTag, LHSVar, RHSVars, ArgModes, ArgWidths,
         assign_const_to_var(LHSVar, const(llconst_uint(UInt)), !.CI, !CLD),
         Code = empty
     ;
+        ConsTag = int8_tag(Int8),
+        assign_const_to_var(LHSVar, const(llconst_int8(Int8)), !.CI, !CLD),
+        Code = empty
+    ;
+        ConsTag = uint8_tag(UInt8),
+        assign_const_to_var(LHSVar, const(llconst_uint8(UInt8)), !.CI, !CLD),
+        Code = empty
+    ;
+        ConsTag = int16_tag(Int16),
+        assign_const_to_var(LHSVar, const(llconst_int16(Int16)), !.CI, !CLD),
+        Code = empty
+    ;
+        ConsTag = uint16_tag(UInt16),
+        assign_const_to_var(LHSVar, const(llconst_uint16(UInt16)), !.CI, !CLD),
+        Code = empty
+    ;
+        ConsTag = int32_tag(Int32),
+        assign_const_to_var(LHSVar, const(llconst_int32(Int32)), !.CI, !CLD),
+        Code = empty
+    ;
+        ConsTag = uint32_tag(UInt32),
+        assign_const_to_var(LHSVar, const(llconst_uint32(UInt32)), !.CI, !CLD),
+        Code = empty
+    ;
         ConsTag = foreign_tag(Lang, Val),
         expect(unify(Lang, lang_c), $module, $pred,
             "foreign_tag for language other than C"),
-        ForeignConst = const(llconst_foreign(Val, lt_integer)),
+        ForeignConst = const(llconst_foreign(Val, lt_int(int_type_int))),
         assign_const_to_var(LHSVar, ForeignConst, !.CI, !CLD),
         Code = empty
     ;
@@ -828,7 +871,8 @@ generate_closure(PredId, ProcId, EvalMethod, Var, Args, GoalInfo, Code,
                     assign(NumOldArgs, lval(field(yes(0), OldClosure, Two))),
                     "get number of arguments"),
                 llds_instr(incr_hp(NewClosure, no, no,
-                    binop(int_add, lval(NumOldArgs), NumNewArgsPlusThree_Rval),
+                    binop(int_add(int_type_int), lval(NumOldArgs),
+                        NumNewArgsPlusThree_Rval),
                     MaybeAllocId, NewClosureMayUseAtomic, no, no_llds_reuse),
                     "allocate new closure"),
                 llds_instr(assign(field(yes(0), lval(NewClosure), Zero),
@@ -838,11 +882,12 @@ generate_closure(PredId, ProcId, EvalMethod, Var, Args, GoalInfo, Code,
                     lval(field(yes(0), OldClosure, One))),
                     "set closure code pointer"),
                 llds_instr(assign(field(yes(0), lval(NewClosure), Two),
-                    binop(int_add, lval(NumOldArgs), NumNewArgs_Rval)),
+                    binop(int_add(int_type_int), lval(NumOldArgs),
+                        NumNewArgs_Rval)),
                     "set new number of arguments"),
                 llds_instr(
                     assign(NumOldArgs,
-                        binop(int_add, lval(NumOldArgs), Three)),
+                        binop(int_add(int_type_int), lval(NumOldArgs), Three)),
                     "set up loop limit"),
                 llds_instr(assign(LoopCounter, Three),
                     "initialize loop counter"),
@@ -859,12 +904,13 @@ generate_closure(PredId, ProcId, EvalMethod, Var, Args, GoalInfo, Code,
                     "copy old hidden argument"),
                 llds_instr(
                     assign(LoopCounter,
-                        binop(int_add, lval(LoopCounter), One)),
+                        binop(int_add(int_type_int), lval(LoopCounter), One)),
                     "increment loop counter"),
                 llds_instr(label(LoopTest),
                     "do we have more old arguments to copy? nofulljump"),
                 llds_instr(
-                    if_val(binop(int_lt, lval(LoopCounter), lval(NumOldArgs)),
+                    if_val(binop(int_lt(int_type_int),
+                        lval(LoopCounter), lval(NumOldArgs)),
                         code_label(LoopStart)),
                     "repeat the loop?")
             ]),
@@ -955,7 +1001,8 @@ generate_extra_closure_args([Var | Vars], LoopCounter, NewClosure, Code,
     ),
     IncrCode = singleton(
         llds_instr(assign(LoopCounter,
-            binop(int_add, lval(LoopCounter), const(llconst_int(1)))),
+            binop(int_add(int_type_int), lval(LoopCounter),
+                const(llconst_int(1)))),
             "increment argument counter")
     ),
     generate_extra_closure_args(Vars, LoopCounter, NewClosure, VarsCode,
@@ -1304,6 +1351,12 @@ generate_det_deconstruction_2(Var, Cons, Args, Modes, ArgWidths, Tag,
         ( Tag = string_tag(_String)
         ; Tag = int_tag(_Int)
         ; Tag = uint_tag(_UInt)
+        ; Tag = int8_tag(_Int8)
+        ; Tag = uint8_tag(_UInt8)
+        ; Tag = int16_tag(_Int16)
+        ; Tag = uint16_tag(_UInt16)
+        ; Tag = int32_tag(_Int32)
+        ; Tag = uint32_tag(_UInt32)
         ; Tag = foreign_tag(_, _)
         ; Tag = float_tag(_Float)
         ; Tag = closure_tag(_, _, _)
@@ -1529,9 +1582,10 @@ generate_sub_assign(Left, Right, Code, CI, !CLD) :-
                 LeftWidth = partial_word_shifted(Shift, Mask)
             ),
             ComplementMask = const(llconst_int(\(Mask << Shift))),
-            MaskOld = binop(bitwise_and, lval(Lval), ComplementMask),
+            MaskOld = binop(bitwise_and(int_type_int), lval(Lval),
+                ComplementMask),
             ShiftNew = maybe_left_shift_rval(Source, Shift),
-            Combined = binop(bitwise_or, MaskOld, ShiftNew),
+            Combined = binop(bitwise_or(int_type_int), MaskOld, ShiftNew),
             AssignCode = singleton(llds_instr(assign(Lval, Combined),
                 "Update part of word"))
         ;
@@ -1566,7 +1620,8 @@ generate_sub_assign(Left, Right, Code, CI, !CLD) :-
                         RightWidth = partial_word_shifted(Shift, Mask),
                         Rval0 = right_shift_rval(lval(Lval), Shift)
                     ),
-                    Rval = binop(bitwise_and, Rval0, const(llconst_int(Mask))),
+                    Rval = binop(bitwise_and(int_type_int), Rval0,
+                        const(llconst_int(Mask))),
                     assign_field_lval_expr_to_var(Lvar, [Lval], Rval, Code,
                         !CLD)
                 ;
@@ -1796,7 +1851,8 @@ generate_const_struct_rval(ModuleInfo, UnboxedFloats, ConstStructMap,
         generate_const_struct_args(ModuleInfo, UnboxedFloats, ConstStructMap,
             ConstArgs, ConsArgWidths, ArgTypedRvals),
         pack_ground_term_args(ConsArgWidths, ArgTypedRvals, PackArgTypedRvals),
-        StagTypedRval = typed_rval(const(llconst_int(Stag)), lt_integer),
+        StagTypedRval = typed_rval(const(llconst_int(Stag)),
+            lt_int(int_type_int)),
         AllTypedRvals = [StagTypedRval | PackArgTypedRvals],
         add_scalar_static_cell(AllTypedRvals, DataAddr, !StaticCellInfo),
         MaybeOffset = no,
@@ -1807,6 +1863,12 @@ generate_const_struct_rval(ModuleInfo, UnboxedFloats, ConstStructMap,
         ( ConsTag = string_tag(_)
         ; ConsTag = int_tag(_)
         ; ConsTag = uint_tag(_)
+        ; ConsTag = int8_tag(_)
+        ; ConsTag = uint8_tag(_)
+        ; ConsTag = int16_tag(_)
+        ; ConsTag = uint16_tag(_)
+        ; ConsTag = int32_tag(_)
+        ; ConsTag = uint32_tag(_)
         ; ConsTag = foreign_tag(_, _)
         ; ConsTag = float_tag(_)
         ; ConsTag = shared_local_tag(_, _)
@@ -1863,17 +1925,41 @@ generate_const_struct_arg_tag(ModuleInfo, UnboxedFloats, ConstStructMap,
         ;
             ConsTag = int_tag(Int),
             Const = llconst_int(Int),
-            Type = lt_integer
+            Type = lt_int(int_type_int)
         ;
             ConsTag = uint_tag(UInt),
             Const = llconst_uint(UInt),
-            Type = lt_unsigned
+            Type = lt_int(int_type_uint)
+        ;
+            ConsTag = int8_tag(Int8),
+            Const = llconst_int8(Int8),
+            Type = lt_int(int_type_int8)
+        ;
+            ConsTag = uint8_tag(UInt8),
+            Const = llconst_uint8(UInt8),
+            Type = lt_int(int_type_uint8)
+        ;
+            ConsTag = int16_tag(Int16),
+            Const = llconst_int16(Int16),
+            Type = lt_int(int_type_int16)
+        ;
+            ConsTag = uint16_tag(UInt16),
+            Const = llconst_uint16(UInt16),
+            Type = lt_int(int_type_uint16)
+        ;
+            ConsTag = int32_tag(Int32),
+            Const = llconst_int32(Int32),
+            Type = lt_int(int_type_int32)
+        ;
+            ConsTag = uint32_tag(UInt32),
+            Const = llconst_uint32(UInt32),
+            Type = lt_int(int_type_uint32)
         ;
             ConsTag = foreign_tag(Lang, Val),
             expect(unify(Lang, lang_c), $module, $pred,
                 "foreign_tag for language other than C"),
-            Const = llconst_foreign(Val, lt_integer),
-            Type = lt_integer
+            Const = llconst_foreign(Val, lt_int(int_type_int)),
+            Type = lt_int(int_type_int)
         ;
             ConsTag = float_tag(Float),
             Const = llconst_float(Float),
@@ -2044,17 +2130,41 @@ generate_ground_term_conjunct_tag(Var, ConsTag, Args, ConsArgWidths,
         ;
             ConsTag = int_tag(Int),
             Const = llconst_int(Int),
-            Type = lt_integer
+            Type = lt_int(int_type_int)
         ;
             ConsTag = uint_tag(UInt),
             Const = llconst_uint(UInt),
-            Type = lt_unsigned
+            Type = lt_int(int_type_uint)
+        ;
+            ConsTag = int8_tag(Int8),
+            Const = llconst_int8(Int8),
+            Type = lt_int(int_type_int8)
+        ;
+            ConsTag = uint8_tag(UInt8),
+            Const = llconst_uint8(UInt8),
+            Type = lt_int(int_type_uint8)
+        ;
+            ConsTag = int16_tag(Int16),
+            Const = llconst_int16(Int16),
+            Type = lt_int(int_type_int16)
+        ;
+            ConsTag = uint16_tag(UInt16),
+            Const = llconst_uint16(UInt16),
+            Type = lt_int(int_type_uint16)
+        ;
+            ConsTag = int32_tag(Int32),
+            Const = llconst_int32(Int32),
+            Type = lt_int(int_type_int32)
+        ;
+            ConsTag = uint32_tag(UInt32),
+            Const = llconst_uint32(UInt32),
+            Type = lt_int(int_type_uint32)
         ;
             ConsTag = foreign_tag(Lang, Val),
             expect(unify(Lang, lang_c), $module, $pred,
                 "foreign_tag for language other than C"),
-            Const = llconst_foreign(Val, lt_integer),
-            Type = lt_integer
+            Const = llconst_foreign(Val, lt_int(int_type_int)),
+            Type = lt_int(int_type_int)
         ;
             ConsTag = float_tag(Float),
             Const = llconst_float(Float),
@@ -2131,7 +2241,8 @@ generate_ground_term_conjunct_tag(Var, ConsTag, Args, ConsArgWidths,
         generate_ground_term_args(Args, ConsArgWidths, ArgTypedRvals,
             !ActiveMap),
         pack_ground_term_args(ConsArgWidths, ArgTypedRvals, PackArgTypedRvals),
-        StagTypedRval = typed_rval(const(llconst_int(Stag)), lt_integer),
+        StagTypedRval = typed_rval(const(llconst_int(Stag)),
+            lt_int(int_type_int)),
         AllTypedRvals = [StagTypedRval | PackArgTypedRvals],
         add_scalar_static_cell(AllTypedRvals, DataAddr, !StaticCellInfo),
         MaybeOffset = no,
@@ -2259,7 +2370,7 @@ shift_combine_rval_type(ArgA, Shift, MaybeArgB, FinalArg, !Acc1, !Acc2) :-
     (
         MaybeArgB = yes(typed_rval(RvalB, TypeB)),
         ( if TypeA = TypeB then
-            FinalRval = binop(bitwise_or, ShiftRvalA, RvalB)
+            FinalRval = binop(bitwise_or(int_type_int), ShiftRvalA, RvalB)
         else
             unexpected($module, $pred, "mismatched llds_types")
         )
@@ -2275,7 +2386,8 @@ maybe_left_shift_rval(Rval, Shift) =
     ( if Shift = 0 then
         Rval
     else
-        binop(unchecked_left_shift, Rval, const(llconst_int(Shift)))
+        binop(unchecked_left_shift(int_type_int), Rval,
+            const(llconst_int(Shift)))
     ).
 
 :- func maybe_left_shift_int(int, int) = int.
@@ -2290,7 +2402,8 @@ maybe_left_shift_int(X, Shift) =
 :- func right_shift_rval(rval, int) = rval.
 
 right_shift_rval(Rval, Shift) =
-    binop(unchecked_right_shift, Rval, const(llconst_int(Shift))).
+    binop(unchecked_right_shift(int_type_int), Rval,
+        const(llconst_int(Shift))).
 
 :- func bitwise_or_cell_arg(cell_arg, cell_arg) = cell_arg.
 
@@ -2308,7 +2421,7 @@ bitwise_or_cell_arg(CellArgA, CellArgB, CellArg) :-
     (
         CellArgA = cell_arg_full_word(RvalA, CompletenessA),
         CellArgB = cell_arg_full_word(RvalB, CompletenessB),
-        Expr = binop(bitwise_or, RvalA, RvalB),
+        Expr = binop(bitwise_or(int_type_int), RvalA, RvalB),
         Completeness = combine_completeness(CompletenessA, CompletenessB),
         CellArg = cell_arg_full_word(Expr, Completeness)
     ;
diff --git a/compiler/unify_proc.m b/compiler/unify_proc.m
index 68ad8dd94..6d5a9c678 100644
--- a/compiler/unify_proc.m
+++ b/compiler/unify_proc.m
@@ -378,12 +378,30 @@ generate_builtin_unify(CtorCat, X, Y, Context, Clause, !Info) :-
     % can_generate_special_pred_clauses_for_type ensures the unexpected
     % cases can never occur.
     (
-        CtorCat = ctor_cat_builtin(cat_builtin_int),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int)),
         Name = "builtin_unify_int"
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_uint),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint)),
         Name = "builtin_unify_uint"
     ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int8)),
+        Name = "builtin_unify_int8"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint8)),
+        Name = "builtin_unify_uint8"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int16)),
+        Name = "builtin_unify_int16"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint16)),
+        Name = "builtin_unify_uint16"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int32)),
+        Name = "builtin_unify_int32"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint32)),
+        Name = "builtin_unify_uint32"
+    ;
         CtorCat = ctor_cat_builtin(cat_builtin_char),
         Name = "builtin_unify_character"
     ;
@@ -697,12 +715,30 @@ generate_builtin_compare(CtorCat, Res, X, Y, Context, Clause, !Info) :-
     % can_generate_special_pred_clauses_for_type ensures the unexpected
     % cases can never occur.
     (
-        CtorCat = ctor_cat_builtin(cat_builtin_int),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int)),
         Name = "builtin_compare_int"
     ;
-        CtorCat = ctor_cat_builtin(cat_builtin_uint),
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint)),
         Name = "builtin_compare_uint"
     ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int8)),
+        Name = "builtin_compare_int8"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint8)),
+        Name = "builtin_compare_uint8"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int16)),
+        Name = "builtin_compare_int16"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint16)),
+        Name = "builtin_compare_uint16"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_int32)),
+        Name = "builtin_compare_int32"
+    ;
+        CtorCat = ctor_cat_builtin(cat_builtin_int(int_type_uint32)),
+        Name = "builtin_compare_uint32"
+    ;
         CtorCat = ctor_cat_builtin(cat_builtin_char),
         Name = "builtin_compare_character"
     ;
diff --git a/compiler/unused_imports.m b/compiler/unused_imports.m
index 214e4e75d..ee8ed7109 100644
--- a/compiler/unused_imports.m
+++ b/compiler/unused_imports.m
@@ -803,6 +803,12 @@ cons_id_used_modules(Visibility, ConsId, !UsedModules) :-
         ; ConsId = closure_cons(_, _)
         ; ConsId = int_const(_)
         ; ConsId = uint_const(_)
+        ; ConsId = int8_const(_)
+        ; ConsId = uint8_const(_)
+        ; ConsId = int16_const(_)
+        ; ConsId = uint16_const(_)
+        ; ConsId = int32_const(_)
+        ; ConsId = uint32_const(_)
         ; ConsId = float_const(_)
         ; ConsId = char_const(_)
         ; ConsId = string_const(_)
@@ -833,8 +839,7 @@ mer_type_used_modules(Visibility, Type, !UsedModules) :-
     ;
         Type = builtin_type(BuiltinType),
         (
-            ( BuiltinType = builtin_type_int
-            ; BuiltinType = builtin_type_uint
+            ( BuiltinType = builtin_type_int(_)
             ; BuiltinType = builtin_type_float
             ; BuiltinType = builtin_type_string
             )
diff --git a/compiler/xml_documentation.m b/compiler/xml_documentation.m
index ae39f9ff8..3d33a02cd 100644
--- a/compiler/xml_documentation.m
+++ b/compiler/xml_documentation.m
@@ -469,8 +469,22 @@ mer_type_to_xml(TVarset, defined_type(TypeName, Args, _)) = Xml :-
     XmlName = name_to_xml(TypeName),
     XmlArgs = xml_list("type_args", mer_type_to_xml(TVarset), Args),
     Xml = elem("type", [Ref], [XmlName, XmlArgs]).
-mer_type_to_xml(_, builtin_type(builtin_type_int)) = elem("int", [], []).
-mer_type_to_xml(_, builtin_type(builtin_type_uint)) = elem("uint", [], []).
+mer_type_to_xml(_, builtin_type(builtin_type_int(int_type_int))) =
+    elem("int", [], []).
+mer_type_to_xml(_, builtin_type(builtin_type_int(int_type_uint))) =
+    elem("uint", [], []).
+mer_type_to_xml(_, builtin_type(builtin_type_int(int_type_int8))) =
+    elem("int8", [], []).
+mer_type_to_xml(_, builtin_type(builtin_type_int(int_type_uint8))) =
+    elem("uint8", [], []).
+mer_type_to_xml(_, builtin_type(builtin_type_int(int_type_int16))) =
+    elem("int16", [], []).
+mer_type_to_xml(_, builtin_type(builtin_type_int(int_type_uint16))) =
+    elem("uint16", [], []).
+mer_type_to_xml(_, builtin_type(builtin_type_int(int_type_int32))) =
+    elem("int32", [], []).
+mer_type_to_xml(_, builtin_type(builtin_type_int(int_type_uint32))) =
+    elem("uint32", [], []).
 mer_type_to_xml(_, builtin_type(builtin_type_float)) = elem("float", [], []).
 mer_type_to_xml(_, builtin_type(builtin_type_string)) = elem("string", [], []).
 mer_type_to_xml(_, builtin_type(builtin_type_char)) =
@@ -702,6 +716,18 @@ cons_id_to_xml(tuple_cons(Arity)) =
 cons_id_to_xml(int_const(I)) = tagged_int("int", I).
 cons_id_to_xml(uint_const(_)) = _ :-
     unexpected($file, $pred, "NYI uint").
+cons_id_to_xml(int8_const(_)) = _ :-
+    unexpected($file, $pred, "NYI int8").
+cons_id_to_xml(uint8_const(_)) = _ :-
+    unexpected($file, $pred, "NYI uint8").
+cons_id_to_xml(int16_const(_)) = _ :-
+    unexpected($file, $pred, "NYI int16").
+cons_id_to_xml(uint16_const(_)) = _ :-
+    unexpected($file, $pred, "NYI uint16").
+cons_id_to_xml(int32_const(_)) = _ :-
+    unexpected($file, $pred, "NYI int32").
+cons_id_to_xml(uint32_const(_)) = _ :-
+    unexpected($file, $pred, "NYI uint32").
 cons_id_to_xml(float_const(F)) = tagged_float("float", F).
 cons_id_to_xml(char_const(C)) = tagged_char("char", C).
 cons_id_to_xml(string_const(S)) = tagged_string("string", S).
diff --git a/configure.ac b/configure.ac
index ee854d1f0..f1915543e 100644
--- a/configure.ac
+++ b/configure.ac
@@ -1388,7 +1388,7 @@ MERCURY_CHECK_FOR_HEADERS( \
         sys/types.h sys/stat.h fcntl.h termios.h sys/ioctl.h \
         sys/resource.h sys/stropts.h windows.h dirent.h getopt.h malloc.h \
         semaphore.h pthread.h time.h spawn.h fenv.h sys/mman.h sys/sem.h \
-        sched.h utmpx.h dispatch/dispatch.h)
+        sched.h utmpx.h dispatch/dispatch.h stdint.h)
 
 if test "$MR_HAVE_GETOPT_H" = 1; then
     GETOPT_H_AVAILABLE=yes
diff --git a/deep_profiler/program_representation_utils.m b/deep_profiler/program_representation_utils.m
index 848431274..ec17e8816 100644
--- a/deep_profiler/program_representation_utils.m
+++ b/deep_profiler/program_representation_utils.m
@@ -304,6 +304,24 @@ type_rep_to_strings(TypeRep, Cord) :-
             BuiltinTypeRep = builtin_type_uint_rep,
             TypeNameStr = "uint"
         ;
+            BuiltinTypeRep = builtin_type_int8_rep,
+            TypeNameStr = "int8"
+        ;
+            BuiltinTypeRep = builtin_type_uint8_rep,
+            TypeNameStr = "uint8"
+        ;
+            BuiltinTypeRep = builtin_type_int16_rep,
+            TypeNameStr = "int16"
+        ;
+            BuiltinTypeRep = builtin_type_uint16_rep,
+            TypeNameStr = "uint16"
+        ;
+            BuiltinTypeRep = builtin_type_int32_rep,
+            TypeNameStr = "int32"
+        ;
+            BuiltinTypeRep = builtin_type_uint32_rep,
+            TypeNameStr = "uint32"
+        ;
             BuiltinTypeRep = builtin_type_float_rep,
             TypeNameStr = "float"
         ;
diff --git a/doc/reference_manual.texi b/doc/reference_manual.texi
index 751ba728f..e837e9ecd 100644
--- a/doc/reference_manual.texi
+++ b/doc/reference_manual.texi
@@ -2185,7 +2185,13 @@ that have meanings in Mercury.
 The list of reserved type names is
 @example
 int
+int8
+int16
+int32
 uint
+uint8
+uint16
+uint32
 float
 character
 string
@@ -7130,7 +7136,13 @@ The Mercury primitive types are mapped to the following C types:
 @multitable {Mercury_type} {MR_Unsigned}
 @headitem Mercury type @tab C type
   @item @code{int}    @tab @code{MR_Integer}
+ at c  @item @code{int8}   @tab @code{int8_t}
+ at c  @item @code{int16}  @tab @code{int16_t}
+ at c  @item @code{int32}  @tab @code{int32_t}
   @item @code{uint}   @tab @code{MR_Unsigned}
+ at c  @item @code{uint8}   @tab @code{uint8_t}
+ at c  @item @code{uint16}  @tab @code{uint16_t}
+ at c  @item @code{uint32}  @tab @code{uint32_t}
   @item @code{float}  @tab @code{MR_Float}
   @item @code{char}   @tab @code{MR_Char}
   @item @code{string} @tab @code{MR_String}
@@ -7221,7 +7233,13 @@ Infrastructure (CLI) and C# types:
 @multitable {Mercury_type} {System_String} {double}
   @headitem Mercury type @tab CLI type @tab C# type
   @item @code{int}    @tab @code{System.Int32}  @tab @code{int}
+ at c  @item @code{int8}   @tab @code{System.Int8}   @tab @code{sbyte}
+ at c  @item @code{int16}  @tab @code{System.Int16}  @tab @code{short}
+ at c  @item @code{int32}  @tab @code{System.Int32}  @tab @code{int}
   @item @code{uint}   @tab @code{System.UInt32} @tab @code{uint}
+ at c  @item @code{uint8}   @tab @code{System.UInt8}   @tab @code{byte}
+ at c  @item @code{uint16}  @tab @code{System.UInt16}  @tab @code{ushort}
+ at c  @item @code{uint32}  @tab @code{System.UInt32}  @tab @code{uint}
   @item @code{float}  @tab @code{System.Double} @tab @code{double}
   @item @code{char}   @tab @code{System.Int32}  @tab @code{int}
   @item @code{string} @tab @code{System.String} @tab @code{string}
@@ -7344,7 +7362,13 @@ The Mercury primitive types are mapped to the following Java types:
 @multitable {Mercury_type} {java_lang_String}
   @headitem Mercury type @tab Java type
   @item @code{int}    @tab @code{int}
+ at c  @item @code{int8}   @tab @code{byte}
+ at c  @item @code{int16}  @tab @code{short}
+ at c  @item @code{int32}  @tab @code{int}
   @item @code{uint}   @tab @code{int}
+ at c  @item @code{uint8}   @tab @code{byte}
+ at c  @item @code{uint16}  @tab @code{short}
+ at c  @item @code{uint32}  @tab @code{int}
   @item @code{float}  @tab @code{double}
   @item @code{char}   @tab @code{int}
   @item @code{string} @tab @code{java.lang.String}
diff --git a/library/MODULES_UNDOC b/library/MODULES_UNDOC
index b1cd56fbc..edc4b9847 100644
--- a/library/MODULES_UNDOC
+++ b/library/MODULES_UNDOC
@@ -1,6 +1,9 @@
 backjump.m
 erlang_builtin.m
 erlang_rtti_implementation.m
+int8.m
+int16.m
+int32.m
 mer_std.m
 mutvar.m
 par_builtin.m
@@ -17,3 +20,6 @@ string.to_string.m
 table_builtin.m
 term_size_prof_builtin.m
 test_bitset.m
+uint8.m
+uint16.m
+uint32.m
diff --git a/library/construct.m b/library/construct.m
index 17566e08a..815c15c56 100644
--- a/library/construct.m
+++ b/library/construct.m
@@ -459,6 +459,12 @@ get_functor_ordinal(TypeDesc, FunctorNumber, Ordinal) :-
         case MR_TYPECTOR_REP_PRED:
         case MR_TYPECTOR_REP_INT:
         case MR_TYPECTOR_REP_UINT:
+        case MR_TYPECTOR_REP_INT8:
+        case MR_TYPECTOR_REP_UINT8:
+        case MR_TYPECTOR_REP_INT16:
+        case MR_TYPECTOR_REP_UINT16:
+        case MR_TYPECTOR_REP_INT32:
+        case MR_TYPECTOR_REP_UINT32:
         case MR_TYPECTOR_REP_FLOAT:
         case MR_TYPECTOR_REP_CHAR:
         case MR_TYPECTOR_REP_STRING:
@@ -900,6 +906,42 @@ find_functor_2(TypeInfo, Functor, Arity, Num0, FunctorNumber, ArgTypes) :-
                 ""cannot construct uint with construct.construct"");
             break;
 
+        case MR_TYPECTOR_REP_INT8:
+            /* int8s don't have functor ordinals. */
+            MR_fatal_error(
+                ""cannot construct int8 with construct.construct"");
+            break;
+
+        case MR_TYPECTOR_REP_UINT8:
+            /* uint8s don't have functor ordinals. */
+            MR_fatal_error(
+                ""cannot construct uint8 with construct.construct"");
+            break;
+
+        case MR_TYPECTOR_REP_INT16:
+            /* int16s don't have functor ordinals. */
+            MR_fatal_error(
+                ""cannot construct int16 with construct.construct"");
+            break;
+
+        case MR_TYPECTOR_REP_UINT16:
+            /* uint16s don't have functor ordinals. */
+            MR_fatal_error(
+                ""cannot construct uint16 with construct.construct"");
+            break;
+
+        case MR_TYPECTOR_REP_INT32:
+            /* int32s don't have functor ordinals. */
+            MR_fatal_error(
+                ""cannot construct int32 with construct.construct"");
+            break;
+
+        case MR_TYPECTOR_REP_UINT32:
+            /* uint32s don't have functor ordinals. */
+            MR_fatal_error(
+                ""cannot construct uint32 with construct.construct"");
+            break;
+
         case MR_TYPECTOR_REP_FLOAT:
             /* floats don't have functor ordinals. */
             MR_fatal_error(
diff --git a/library/erlang_rtti_implementation.m b/library/erlang_rtti_implementation.m
index 156bd7a83..0910c8474 100644
--- a/library/erlang_rtti_implementation.m
+++ b/library/erlang_rtti_implementation.m
@@ -167,6 +167,12 @@
     ;       etcr_eqv
     ;       etcr_int
     ;       etcr_uint
+    ;       etcr_int8
+    ;       etcr_uint8
+    ;       etcr_int16
+    ;       etcr_uint16
+    ;       etcr_int32
+    ;       etcr_uint32
     ;       etcr_float
     ;       etcr_char
     ;       etcr_string
@@ -832,6 +838,42 @@ deconstruct_2(Term, TypeInfo, TypeCtorInfo, TypeCtorRep, NonCanon,
         Arity = 0,
         Arguments = []
     ;
+        TypeCtorRep = etcr_int8,
+        Functor = "<<int8>>",   % XXX FIXED SIZE INT
+        FunctorNumber = 0,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = etcr_uint8,
+        Functor = "<<uint8>>",  % XXX FIXED SIZE INT
+        FunctorNumber = 0,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = etcr_int16,
+        Functor = "<<int16>>",   % XXX FIXED SIZE INT
+        FunctorNumber = 0,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = etcr_uint16,
+        Functor = "<<uint16>>",  % XXX FIXED SIZE INT
+        FunctorNumber = 0,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = etcr_int32,
+        Functor = "<<int32>>",   % XXX FIXED SIZE INT
+        FunctorNumber = 0,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = etcr_uint32,
+        Functor = "<<uint32>>",  % XXX FIXED SIZE INT
+        FunctorNumber = 0,
+        Arity = 0,
+        Arguments = []
+    ;
         TypeCtorRep = etcr_float,
         det_dynamic_cast(Term, Float),
         Functor = float_to_string(Float),
@@ -1193,6 +1235,12 @@ num_functors(TypeInfo, MaybeNumFunctors) :-
         ( TypeCtorRep = etcr_array
         ; TypeCtorRep = etcr_int
         ; TypeCtorRep = etcr_uint
+        ; TypeCtorRep = etcr_int8
+        ; TypeCtorRep = etcr_uint8
+        ; TypeCtorRep = etcr_int16
+        ; TypeCtorRep = etcr_uint16
+        ; TypeCtorRep = etcr_int32
+        ; TypeCtorRep = etcr_uint32
         ; TypeCtorRep = etcr_float
         ; TypeCtorRep = etcr_char
         ; TypeCtorRep = etcr_string
@@ -1311,6 +1359,12 @@ get_functor_with_names(TypeInfo, NumFunctor) = Result :-
         ( TypeCtorRep = etcr_array
         ; TypeCtorRep = etcr_int
         ; TypeCtorRep = etcr_uint
+        ; TypeCtorRep = etcr_int8
+        ; TypeCtorRep = etcr_uint8
+        ; TypeCtorRep = etcr_int16
+        ; TypeCtorRep = etcr_uint16
+        ; TypeCtorRep = etcr_int32
+        ; TypeCtorRep = etcr_uint32
         ; TypeCtorRep = etcr_float
         ; TypeCtorRep = etcr_char
         ; TypeCtorRep = etcr_string
@@ -1464,6 +1518,12 @@ construct(TypeDesc, Index, Args) = Term :-
         ; TypeCtorRep = etcr_eqv
         ; TypeCtorRep = etcr_int
         ; TypeCtorRep = etcr_uint
+        ; TypeCtorRep = etcr_int8
+        ; TypeCtorRep = etcr_uint8
+        ; TypeCtorRep = etcr_int16
+        ; TypeCtorRep = etcr_uint16
+        ; TypeCtorRep = etcr_int32
+        ; TypeCtorRep = etcr_uint32
         ; TypeCtorRep = etcr_float
         ; TypeCtorRep = etcr_char
         ; TypeCtorRep = etcr_string
diff --git a/library/int16.m b/library/int16.m
new file mode 100644
index 000000000..a0e1499f8
--- /dev/null
+++ b/library/int16.m
@@ -0,0 +1,20 @@
+%---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
+%---------------------------------------------------------------------------%
+% Copyright (C) 2017 The Mercury team.
+% This file may only be copied under the terms of the GNU Library General
+% Public License - see the file COPYING.LIB in the Mercury distribution.
+%---------------------------------------------------------------------------%
+
+:- module int16.
+:- interface.
+
+    % int16s are NYI -- this module is just a placeholder for their
+    % library support.
+    %
+:- type placeholder_int16 ---> placeholder_int16.
+
+%---------------------------------------------------------------------------%
+:- end_module int16.
+%---------------------------------------------------------------------------%
+
diff --git a/library/int32.m b/library/int32.m
new file mode 100644
index 000000000..da40d0290
--- /dev/null
+++ b/library/int32.m
@@ -0,0 +1,20 @@
+%---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
+%---------------------------------------------------------------------------%
+% Copyright (C) 2017 The Mercury team.
+% This file may only be copied under the terms of the GNU Library General
+% Public License - see the file COPYING.LIB in the Mercury distribution.
+%---------------------------------------------------------------------------%
+
+:- module int32.
+:- interface.
+
+    % int32s are NYI -- this module is just a placeholder for their
+    % library support.
+    %
+:- type placeholder_int32 ---> placeholder_int32.
+
+%---------------------------------------------------------------------------%
+:- end_module int32.
+%---------------------------------------------------------------------------%
+
diff --git a/library/int8.m b/library/int8.m
new file mode 100644
index 000000000..4144652ca
--- /dev/null
+++ b/library/int8.m
@@ -0,0 +1,20 @@
+%---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
+%---------------------------------------------------------------------------%
+% Copyright (C) 2017 The Mercury team.
+% This file may only be copied under the terms of the GNU Library General
+% Public License - see the file COPYING.LIB in the Mercury distribution.
+%---------------------------------------------------------------------------%
+
+:- module int8.
+:- interface.
+
+    % int8s are NYI -- this module is just a placeholder for their
+    % library support.
+    %
+:- type placeholder_int8 ---> placeholder_int8.
+
+%---------------------------------------------------------------------------%
+:- end_module int8.
+%---------------------------------------------------------------------------%
+
diff --git a/library/library.m b/library/library.m
index 2c42f8e5b..0fa1ca353 100644
--- a/library/library.m
+++ b/library/library.m
@@ -95,6 +95,9 @@
 :- import_module hash_table.
 :- import_module injection.
 :- import_module int.
+:- import_module int8.
+:- import_module int16.
+:- import_module int32.
 :- import_module integer.
 :- import_module io.
 :- import_module lazy.
@@ -149,6 +152,9 @@
 :- import_module tree_bitset.
 :- import_module type_desc.
 :- import_module uint.
+:- import_module uint8.
+:- import_module uint16.
+:- import_module uint32.
 :- import_module unit.
 :- import_module univ.
 :- import_module varset.
@@ -266,6 +272,9 @@ mercury_std_library_module("getopt_io").
 mercury_std_library_module("hash_table").
 mercury_std_library_module("injection").
 mercury_std_library_module("int").
+mercury_std_library_module("int8").
+mercury_std_library_module("int16").
+mercury_std_library_module("int32").
 mercury_std_library_module("integer").
 mercury_std_library_module("io").
 mercury_std_library_module("lazy").
@@ -338,6 +347,9 @@ mercury_std_library_module("tree234").
 mercury_std_library_module("tree_bitset").
 mercury_std_library_module("type_desc").
 mercury_std_library_module("uint").
+mercury_std_library_module("uint8").
+mercury_std_library_module("uint16").
+mercury_std_library_module("uint32").
 mercury_std_library_module("unit").
 mercury_std_library_module("univ").
 mercury_std_library_module("varset").
diff --git a/library/private_builtin.m b/library/private_builtin.m
index d70f60b0e..e5b509626 100644
--- a/library/private_builtin.m
+++ b/library/private_builtin.m
@@ -51,6 +51,24 @@
 :- pred builtin_unify_uint(uint::in, uint::in) is semidet.
 :- pred builtin_compare_uint(comparison_result::uo, uint::in, uint::in) is det.
 
+:- pred builtin_unify_int8(T::in, T::in) is semidet.
+:- pred builtin_compare_int8(comparison_result::uo, T::in, T::in) is det.
+
+:- pred builtin_unify_uint8(T::in, T::in) is semidet.
+:- pred builtin_compare_uint8(comparison_result::uo, T::in, T::in) is det.
+
+:- pred builtin_unify_int16(T::in, T::in) is semidet.
+:- pred builtin_compare_int16(comparison_result::uo, T::in, T::in) is det.
+
+:- pred builtin_unify_uint16(T::in, T::in) is semidet.
+:- pred builtin_compare_uint16(comparison_result::uo, T::in, T::in) is det.
+
+:- pred builtin_unify_int32(T::in, T::in) is semidet.
+:- pred builtin_compare_int32(comparison_result::uo, T::in, T::in) is det.
+
+:- pred builtin_unify_uint32(T::in, T::in) is semidet.
+:- pred builtin_compare_uint32(comparison_result::uo, T::in, T::in) is det.
+
 :- pred builtin_unify_character(character::in, character::in) is semidet.
 :- pred builtin_compare_character(comparison_result::uo, character::in,
     character::in) is det.
@@ -180,6 +198,90 @@ builtin_compare_uint(R, X, Y) :-
         R = (>)
     ).
 
+builtin_unify_int8(_, _) :-
+    ( if semidet_succeed then
+        sorry("unify for int8")
+    else
+        semidet_succeed
+    ).
+
+builtin_compare_int8(R, _, _) :-
+    ( if semidet_succeed then
+        sorry("compare for int8")
+    else
+        R = (=)
+    ).
+
+builtin_unify_uint8(_, _) :-
+    ( if semidet_succeed then
+        sorry("unify for uint8")
+    else
+        semidet_succeed
+    ).
+
+builtin_compare_uint8(R, _, _) :-
+    ( if semidet_succeed then
+        sorry("compare for uint8")
+    else
+        R = (=)
+    ).
+
+builtin_unify_int16(_, _) :-
+    ( if semidet_succeed then
+        sorry("unify for int16")
+    else
+        semidet_succeed
+    ).
+
+builtin_compare_int16(R, _, _) :-
+    ( if semidet_succeed then
+        sorry("compare for int16")
+    else
+        R = (=)
+    ).
+
+builtin_unify_uint16(_, _) :-
+    ( if semidet_succeed then
+        sorry("unify for uint16")
+    else
+        semidet_succeed
+    ).
+
+builtin_compare_uint16(R, _, _) :-
+    ( if semidet_succeed then
+        sorry("compare for uint16")
+    else
+        R = (=)
+    ).
+
+builtin_unify_int32(_, _) :-
+    ( if semidet_succeed then
+        sorry("unify for int32")
+    else
+        semidet_succeed
+    ).
+
+builtin_compare_int32(R, _, _) :-
+    ( if semidet_succeed then
+        sorry("compare for int32")
+    else
+        R = (=)
+    ).
+
+builtin_unify_uint32(_, _) :-
+    ( if semidet_succeed then
+        sorry("unify for uint32")
+    else
+        semidet_succeed
+    ).
+
+builtin_compare_uint32(R, _, _) :-
+    ( if semidet_succeed then
+        sorry("compare for uint32")
+    else
+        R = (=)
+    ).
+
 builtin_unify_character(C, C).
 
 builtin_compare_character(R, X, Y) :-
@@ -1761,8 +1863,14 @@ const MR_FA_TypeInfo_Struct1 ML_type_info_for_list_of_pseudo_type_info = {
     public static final int MR_TYPECTOR_REP_BITMAP                  = 44;
     public static final int MR_TYPECTOR_REP_FOREIGN_ENUM            = 45;
     public static final int MR_TYPECTOR_REP_FOREIGN_ENUM_USEREQ     = 46;
-    public static final int MR_TYPECTOR_REP_UNKNOWN                 = 47;
-    public static final int MR_TYPECTOR_REP_MAX                     = 48;
+    public static final int MR_TYPECTOR_REP_INT8                    = 47;
+    public static final int MR_TYPECTOR_REP_UINT8                   = 48;
+    public static final int MR_TYPECTOR_REP_INT16                   = 49;
+    public static final int MR_TYPECTOR_REP_UINT16                  = 50;
+    public static final int MR_TYPECTOR_REP_INT32                   = 51;
+    public static final int MR_TYPECTOR_REP_UINT32                  = 52;
+    public static final int MR_TYPECTOR_REP_UNKNOWN                 = 53;
+    public static final int MR_TYPECTOR_REP_MAX                     = 54;
 
     public static final int MR_SECTAG_NONE              = 0;
     public static final int MR_SECTAG_NONE_DIRECT_ARG   = 1;
diff --git a/library/rtti_implementation.m b/library/rtti_implementation.m
index b85e3ff71..a3f4b9b4b 100644
--- a/library/rtti_implementation.m
+++ b/library/rtti_implementation.m
@@ -165,6 +165,12 @@
     ;       tcr_func
     ;       tcr_int
     ;       tcr_uint
+    ;       tcr_int8
+    ;       tcr_uint8
+    ;       tcr_int16
+    ;       tcr_uint16
+    ;       tcr_int32
+    ;       tcr_uint32
     ;       tcr_char
     ;       tcr_float
     ;       tcr_string
@@ -890,6 +896,12 @@ type_info_num_functors(TypeInfo, NumFunctors) :-
         ( TypeCtorRep = tcr_subgoal
         ; TypeCtorRep = tcr_int
         ; TypeCtorRep = tcr_uint
+        ; TypeCtorRep = tcr_int8
+        ; TypeCtorRep = tcr_uint8
+        ; TypeCtorRep = tcr_int16
+        ; TypeCtorRep = tcr_uint16
+        ; TypeCtorRep = tcr_int32
+        ; TypeCtorRep = tcr_uint32
         ; TypeCtorRep = tcr_char
         ; TypeCtorRep = tcr_float
         ; TypeCtorRep = tcr_string
@@ -995,6 +1007,12 @@ get_functor_impl(TypeInfo, FunctorNumber,
         ( TypeCtorRep = tcr_subgoal
         ; TypeCtorRep = tcr_int
         ; TypeCtorRep = tcr_uint
+        ; TypeCtorRep = tcr_int8
+        ; TypeCtorRep = tcr_uint8
+        ; TypeCtorRep = tcr_int16
+        ; TypeCtorRep = tcr_uint16
+        ; TypeCtorRep = tcr_int32
+        ; TypeCtorRep = tcr_uint32
         ; TypeCtorRep = tcr_char
         ; TypeCtorRep = tcr_float
         ; TypeCtorRep = tcr_string
@@ -1225,6 +1243,12 @@ type_info_get_functor_ordinal(TypeInfo, FunctorNum, Ordinal) :-
         ; TypeCtorRep = tcr_pred
         ; TypeCtorRep = tcr_int
         ; TypeCtorRep = tcr_uint
+        ; TypeCtorRep = tcr_int8
+        ; TypeCtorRep = tcr_uint8
+        ; TypeCtorRep = tcr_int16
+        ; TypeCtorRep = tcr_uint16
+        ; TypeCtorRep = tcr_int32
+        ; TypeCtorRep = tcr_uint32
         ; TypeCtorRep = tcr_float
         ; TypeCtorRep = tcr_char
         ; TypeCtorRep = tcr_string
@@ -2716,6 +2740,42 @@ deconstruct_2(Term, TypeInfo, TypeCtorInfo, TypeCtorRep, NonCanon,
         Arity = 0,
         Arguments = []
     ;
+        TypeCtorRep = tcr_int8,
+        Functor = "<<int8>>",
+        Ordinal = -1,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = tcr_uint8,
+        Functor = "<<uint8>>",
+        Ordinal = -1,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = tcr_int16,
+        Functor = "<<int16>>",
+        Ordinal = -1,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = tcr_uint16,
+        Functor = "<<uint16>>",
+        Ordinal = -1,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = tcr_int32,
+        Functor = "<<int32>>",
+        Ordinal = -1,
+        Arity = 0,
+        Arguments = []
+    ;
+        TypeCtorRep = tcr_uint32,
+        Functor = "<<uint32>>",
+        Ordinal = -1,
+        Arity = 0,
+        Arguments = []
+    ;
         TypeCtorRep = tcr_char,
         det_dynamic_cast(Term, Char),
         Functor = string.from_char_list(['\'', Char, '\'']),
@@ -2982,6 +3042,12 @@ univ_named_arg_2(Term, TypeInfo, TypeCtorInfo, TypeCtorRep, NonCanon, Name,
         ; TypeCtorRep = tcr_func
         ; TypeCtorRep = tcr_int
         ; TypeCtorRep = tcr_uint
+        ; TypeCtorRep = tcr_int8
+        ; TypeCtorRep = tcr_uint8
+        ; TypeCtorRep = tcr_int16
+        ; TypeCtorRep = tcr_uint16
+        ; TypeCtorRep = tcr_int32
+        ; TypeCtorRep = tcr_uint32
         ; TypeCtorRep = tcr_char
         ; TypeCtorRep = tcr_float
         ; TypeCtorRep = tcr_string
diff --git a/library/uint16.m b/library/uint16.m
new file mode 100644
index 000000000..703026221
--- /dev/null
+++ b/library/uint16.m
@@ -0,0 +1,20 @@
+%---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
+%---------------------------------------------------------------------------%
+% Copyright (C) 2017 The Mercury team.
+% This file may only be copied under the terms of the GNU Library General
+% Public License - see the file COPYING.LIB in the Mercury distribution.
+%---------------------------------------------------------------------------%
+
+:- module uint16.
+:- interface.
+
+    % uint16s are NYI -- this module is just a placeholder for their
+    % library support.
+    %
+:- type placeholder_uint16 ---> placeholder_uint16.
+
+%---------------------------------------------------------------------------%
+:- end_module uint16.
+%---------------------------------------------------------------------------%
+
diff --git a/library/uint32.m b/library/uint32.m
new file mode 100644
index 000000000..4409db83a
--- /dev/null
+++ b/library/uint32.m
@@ -0,0 +1,20 @@
+%---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
+%---------------------------------------------------------------------------%
+% Copyright (C) 2017 The Mercury team.
+% This file may only be copied under the terms of the GNU Library General
+% Public License - see the file COPYING.LIB in the Mercury distribution.
+%---------------------------------------------------------------------------%
+
+:- module uint32.
+:- interface.
+
+    % uint32s are NYI -- this module is just a placeholder for their
+    % library support.
+    %
+:- type placeholder_uint32 ---> placeholder_uint32.
+
+%---------------------------------------------------------------------------%
+:- end_module uint32.
+%---------------------------------------------------------------------------%
+
diff --git a/library/uint8.m b/library/uint8.m
new file mode 100644
index 000000000..d640fb587
--- /dev/null
+++ b/library/uint8.m
@@ -0,0 +1,20 @@
+%---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
+%---------------------------------------------------------------------------%
+% Copyright (C) 2017 The Mercury team.
+% This file may only be copied under the terms of the GNU Library General
+% Public License - see the file COPYING.LIB in the Mercury distribution.
+%---------------------------------------------------------------------------%
+
+:- module uint8.
+:- interface.
+
+    % uint8s are NYI -- this module is just a placeholder for their
+    % library support.
+    %
+:- type placeholder_uint8 ---> placeholder_uint8.
+
+%---------------------------------------------------------------------------%
+:- end_module uint8.
+%---------------------------------------------------------------------------%
+
diff --git a/mdbcomp/program_representation.m b/mdbcomp/program_representation.m
index 32a595757..434f814d3 100644
--- a/mdbcomp/program_representation.m
+++ b/mdbcomp/program_representation.m
@@ -98,6 +98,12 @@
 :- type builtin_type_rep
     --->    builtin_type_int_rep
     ;       builtin_type_uint_rep
+    ;       builtin_type_int8_rep
+    ;       builtin_type_uint8_rep
+    ;       builtin_type_int16_rep
+    ;       builtin_type_uint16_rep
+    ;       builtin_type_int32_rep
+    ;       builtin_type_uint32_rep
     ;       builtin_type_float_rep
     ;       builtin_type_string_rep
     ;       builtin_type_char_rep.
@@ -1383,6 +1389,29 @@ read_encoded_type(ByteCode, StringTable, TypeTable, TypeRep, !Pos) :-
         Selector = 13,
         read_num(ByteCode, VarNum, !Pos),
         TypeRep = type_var_rep(VarNum)
+    ;
+        % XXX in order to avoid bumping the deep profiler's binary compatibility
+        % version number when the fixed size integers were added, the newly
+        % added types were assigned unused Selector values.  The next time the
+        % format of the program representation file is changed for some
+        % unavoidable reason this should be tidied up.
+        Selector = 14,
+        TypeRep = builtin_type_rep(builtin_type_int8_rep)
+    ;
+        Selector = 15,
+        TypeRep = builtin_type_rep(builtin_type_uint8_rep)
+    ;
+        Selector = 16,
+        TypeRep = builtin_type_rep(builtin_type_int16_rep)
+    ;
+        Selector = 17,
+        TypeRep = builtin_type_rep(builtin_type_uint16_rep)
+    ;
+        Selector = 18,
+        TypeRep = builtin_type_rep(builtin_type_int32_rep)
+    ;
+        Selector = 19,
+        TypeRep = builtin_type_rep(builtin_type_uint32_rep)
     ).
 
 %---------------------%
diff --git a/runtime/mercury_builtin_types.c b/runtime/mercury_builtin_types.c
index d4fdb6d90..6cbf5eef2 100644
--- a/runtime/mercury_builtin_types.c
+++ b/runtime/mercury_builtin_types.c
@@ -40,6 +40,12 @@
 
 MR_DEFINE_TYPE_CTOR_INFO(builtin, int, 0, INT);
 MR_DEFINE_TYPE_CTOR_INFO(builtin, uint, 0, UINT);
+MR_DEFINE_TYPE_CTOR_INFO(builtin, int8, 0, INT8);
+MR_DEFINE_TYPE_CTOR_INFO(builtin, uint8, 0, UINT8);
+MR_DEFINE_TYPE_CTOR_INFO(builtin, int16, 0, INT16);
+MR_DEFINE_TYPE_CTOR_INFO(builtin, uint16, 0, UINT16);
+MR_DEFINE_TYPE_CTOR_INFO(builtin, int32, 0, INT32);
+MR_DEFINE_TYPE_CTOR_INFO(builtin, uint32, 0, UINT32);
 MR_DEFINE_TYPE_CTOR_INFO(builtin, character, 0, CHAR);
 MR_DEFINE_TYPE_CTOR_INFO(builtin, string, 0, STRING);
 MR_DEFINE_TYPE_CTOR_INFO(builtin, float, 0, FLOAT);
@@ -114,6 +120,42 @@ mercury__builtin____Unify____uint_0_0(MR_Unsigned x, MR_Unsigned y)
 }
 
 MR_bool MR_CALL
+mercury__builtin____Unify____int8_0_0(int8_t x, int8_t y)
+{
+    return x == y;
+}
+
+MR_bool MR_CALL
+mercury__builtin____Unify____uint8_0_0(uint8_t x, uint8_t y)
+{
+    return x == y;
+}
+
+MR_bool MR_CALL
+mercury__builtin____Unify____int16_0_0(int16_t x, int16_t y)
+{
+    return x == y;
+}
+
+MR_bool MR_CALL
+mercury__builtin____Unify____uint16_0_0(uint16_t x, uint16_t y)
+{
+    return x == y;
+}
+
+MR_bool MR_CALL
+mercury__builtin____Unify____int32_0_0(int32_t x, int32_t y)
+{
+    return x == y;
+}
+
+MR_bool MR_CALL
+mercury__builtin____Unify____uint32_0_0(uint32_t x, uint32_t y)
+{
+    return x == y;
+}
+
+MR_bool MR_CALL
 mercury__builtin____Unify____string_0_0(MR_String x, MR_String y)
 {
     return strcmp(x, y) == 0;
@@ -265,6 +307,60 @@ mercury__builtin____Compare____uint_0_0(
 }
 
 void MR_CALL
+mercury__builtin____Compare____int8_0_0(
+    MR_Comparison_Result *result, int8_t x, int8_t y)
+{
+    *result = (x > y ? MR_COMPARE_GREATER :
+          x == y ? MR_COMPARE_EQUAL :
+          MR_COMPARE_LESS);
+}
+
+void MR_CALL
+mercury__builtin____Compare____uint8_0_0(
+    MR_Comparison_Result *result, uint8_t x, uint8_t y)
+{
+    *result = (x > y ? MR_COMPARE_GREATER :
+          x == y ? MR_COMPARE_EQUAL :
+          MR_COMPARE_LESS);
+}
+
+void MR_CALL
+mercury__builtin____Compare____int16_0_0(
+    MR_Comparison_Result *result, int16_t x, int16_t y)
+{
+    *result = (x > y ? MR_COMPARE_GREATER :
+          x == y ? MR_COMPARE_EQUAL :
+          MR_COMPARE_LESS);
+}
+
+void MR_CALL
+mercury__builtin____Compare____uint16_0_0(
+    MR_Comparison_Result *result, uint16_t x, uint16_t y)
+{
+    *result = (x > y ? MR_COMPARE_GREATER :
+          x == y ? MR_COMPARE_EQUAL :
+          MR_COMPARE_LESS);
+}
+
+void MR_CALL
+mercury__builtin____Compare____int32_0_0(
+    MR_Comparison_Result *result, int32_t x, int32_t y)
+{
+    *result = (x > y ? MR_COMPARE_GREATER :
+          x == y ? MR_COMPARE_EQUAL :
+          MR_COMPARE_LESS);
+}
+
+void MR_CALL
+mercury__builtin____Compare____uint32_0_0(
+    MR_Comparison_Result *result, uint32_t x, uint32_t y)
+{
+    *result = (x > y ? MR_COMPARE_GREATER :
+          x == y ? MR_COMPARE_EQUAL :
+          MR_COMPARE_LESS);
+}
+
+void MR_CALL
 mercury__builtin____Compare____string_0_0(MR_Comparison_Result *result,
     MR_String x, MR_String y)
 {
@@ -427,6 +523,48 @@ mercury__builtin__do_unify__uint_0_0(MR_Box x, MR_Box y)
 }
 
 MR_bool MR_CALL
+mercury__builtin__do_unify__int8_0_0(MR_Box x, MR_Box y)
+{
+    return mercury__builtin____Unify____int8_0_0(
+        (int8_t) x, (int8_t) y);
+}
+
+MR_bool MR_CALL
+mercury__builtin__do_unify__uint8_0_0(MR_Box x, MR_Box y)
+{
+    return mercury__builtin____Unify____uint8_0_0(
+        (uint8_t) x, (uint8_t) y);
+}
+
+MR_bool MR_CALL
+mercury__builtin__do_unify__int16_0_0(MR_Box x, MR_Box y)
+{
+    return mercury__builtin____Unify____int16_0_0(
+        (int16_t) x, (int16_t) y);
+}
+
+MR_bool MR_CALL
+mercury__builtin__do_unify__uint16_0_0(MR_Box x, MR_Box y)
+{
+    return mercury__builtin____Unify____uint16_0_0(
+        (uint16_t) x, (uint16_t) y);
+}
+
+MR_bool MR_CALL
+mercury__builtin__do_unify__int32_0_0(MR_Box x, MR_Box y)
+{
+    return mercury__builtin____Unify____int32_0_0(
+        (int32_t) x, (int32_t) y);
+}
+
+MR_bool MR_CALL
+mercury__builtin__do_unify__uint32_0_0(MR_Box x, MR_Box y)
+{
+    return mercury__builtin____Unify____uint32_0_0(
+        (uint32_t) x, (uint32_t) y);
+}
+
+MR_bool MR_CALL
 mercury__builtin__do_unify__string_0_0(MR_Box x, MR_Box y)
 {
     return mercury__builtin____Unify____string_0_0(
@@ -576,6 +714,54 @@ mercury__builtin__do_compare__uint_0_0(
 }
 
 void MR_CALL
+mercury__builtin__do_compare__int8_0_0(
+    MR_Comparison_Result *result, MR_Box x, MR_Box y)
+{
+    mercury__builtin____Compare____int8_0_0(result,
+        (int8_t) x, (int8_t) y);
+}
+
+void MR_CALL
+mercury__builtin__do_compare__uint8_0_0(
+    MR_Comparison_Result *result, MR_Box x, MR_Box y)
+{
+    mercury__builtin____Compare____uint8_0_0(result,
+        (uint8_t) x, (uint8_t) y);
+}
+
+void MR_CALL
+mercury__builtin__do_compare__int16_0_0(
+    MR_Comparison_Result *result, MR_Box x, MR_Box y)
+{
+    mercury__builtin____Compare____int16_0_0(result,
+        (int16_t) x, (int16_t) y);
+}
+
+void MR_CALL
+mercury__builtin__do_compare__uint16_0_0(
+    MR_Comparison_Result *result, MR_Box x, MR_Box y)
+{
+    mercury__builtin____Compare____uint16_0_0(result,
+        (uint16_t) x, (uint16_t) y);
+}
+
+void MR_CALL
+mercury__builtin__do_compare__int32_0_0(
+    MR_Comparison_Result *result, MR_Box x, MR_Box y)
+{
+    mercury__builtin____Compare____int32_0_0(result,
+        (int32_t) x, (int32_t) y);
+}
+
+void MR_CALL
+mercury__builtin__do_compare__uint32_0_0(
+    MR_Comparison_Result *result, MR_Box x, MR_Box y)
+{
+    mercury__builtin____Compare____uint32_0_0(result,
+        (uint32_t) x, (uint32_t) y);
+}
+
+void MR_CALL
 mercury__builtin__do_compare__string_0_0(
     MR_Comparison_Result *result, MR_Box x, MR_Box y)
 {
@@ -761,6 +947,12 @@ MR_MODULE_STATIC_OR_EXTERN MR_ModuleFunc mercury_builtin_types;
 
 MR_UNIFY_COMPARE_REP_DECLS(builtin, int, 0)
 MR_UNIFY_COMPARE_REP_DECLS(builtin, uint, 0)
+MR_UNIFY_COMPARE_REP_DECLS(builtin, int8, 0)
+MR_UNIFY_COMPARE_REP_DECLS(builtin, uint8, 0)
+MR_UNIFY_COMPARE_REP_DECLS(builtin, int16, 0)
+MR_UNIFY_COMPARE_REP_DECLS(builtin, uint16, 0)
+MR_UNIFY_COMPARE_REP_DECLS(builtin, int32, 0)
+MR_UNIFY_COMPARE_REP_DECLS(builtin, uint32, 0)
 MR_UNIFY_COMPARE_REP_DECLS(builtin, string, 0)
 MR_UNIFY_COMPARE_REP_DECLS(builtin, float, 0)
 MR_UNIFY_COMPARE_REP_DECLS(builtin, character, 0)
@@ -791,6 +983,12 @@ MR_UNIFY_COMPARE_REP_DECLS(builtin, dummy, 0);
 
 MR_UNIFY_COMPARE_REP_DEFNS(builtin, int, 0)
 MR_UNIFY_COMPARE_REP_DEFNS(builtin, uint, 0)
+MR_UNIFY_COMPARE_REP_DEFNS(builtin, int8, 0)
+MR_UNIFY_COMPARE_REP_DEFNS(builtin, uint8, 0)
+MR_UNIFY_COMPARE_REP_DEFNS(builtin, int16, 0)
+MR_UNIFY_COMPARE_REP_DEFNS(builtin, uint16, 0)
+MR_UNIFY_COMPARE_REP_DEFNS(builtin, int32, 0)
+MR_UNIFY_COMPARE_REP_DEFNS(builtin, uint32, 0)
 MR_UNIFY_COMPARE_REP_DEFNS(builtin, string, 0)
 MR_UNIFY_COMPARE_REP_DEFNS(builtin, float, 0)
 MR_UNIFY_COMPARE_REP_DEFNS(builtin, character, 0)
@@ -864,6 +1062,12 @@ MR_UNIFY_COMPARE_REP_DEFNS(builtin, dummy, 0)
 
 MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, int, 0);
 MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, uint, 0);
+MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, int8, 0);
+MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, uint8, 0);
+MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, int16, 0);
+MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, uint16, 0);
+MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, int32, 0);
+MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, uint32, 0);
 MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, string, 0);
 MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, float, 0);
 MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, character, 0);
@@ -897,6 +1101,12 @@ MR_DEFINE_PROC_STATIC_LAYOUTS(builtin, dummy, 0);
 MR_BEGIN_MODULE(mercury_builtin_types)
     MR_UNIFY_COMPARE_REP_LABELS(builtin, int, 0)
     MR_UNIFY_COMPARE_REP_LABELS(builtin, uint, 0)
+    MR_UNIFY_COMPARE_REP_LABELS(builtin, int8, 0)
+    MR_UNIFY_COMPARE_REP_LABELS(builtin, uint8, 0)
+    MR_UNIFY_COMPARE_REP_LABELS(builtin, int16, 0)
+    MR_UNIFY_COMPARE_REP_LABELS(builtin, uint16, 0)
+    MR_UNIFY_COMPARE_REP_LABELS(builtin, int32, 0)
+    MR_UNIFY_COMPARE_REP_LABELS(builtin, uint32, 0)
     MR_UNIFY_COMPARE_REP_LABELS(builtin, string, 0)
     MR_UNIFY_COMPARE_REP_LABELS(builtin, float, 0)
     MR_UNIFY_COMPARE_REP_LABELS(builtin, character, 0)
@@ -971,6 +1181,132 @@ MR_BEGIN_CODE
 ////////////////////////////////////////////////////////////////////////////
 
 #define module          builtin
+#define type            int8
+#define arity           0
+#define unify_code      MR_r1 = ((int8_t) MR_r1 == (int8_t) MR_r2);
+#define compare_code    MR_r1 =                                         \
+                            ((int8_t) MR_r1 == (int8_t) MR_r2 ?         \
+                                MR_COMPARE_EQUAL :                      \
+                            (int8_t) MR_r1 < (int8_t) MR_r2 ?           \
+                                MR_COMPARE_LESS :                       \
+                            MR_COMPARE_GREATER);
+
+#include "mercury_hand_unify_compare_body.h"
+
+#undef  module
+#undef  type
+#undef  arity
+#undef  unify_code
+#undef  compare_code
+
+////////////////////////////////////////////////////////////////////////////
+
+#define module          builtin
+#define type            uint8
+#define arity           0
+#define unify_code      MR_r1 = ((uint8_t) MR_r1 == (uint8_t) MR_r2);
+#define compare_code    MR_r1 =                                         \
+                            ((uint8_t) MR_r1 == (uint8_t) MR_r2 ?       \
+                                MR_COMPARE_EQUAL :                      \
+                            (uint8_t) MR_r1 < (uint8_t) MR_r2 ?         \
+                                MR_COMPARE_LESS :                       \
+                            MR_COMPARE_GREATER);
+
+#include "mercury_hand_unify_compare_body.h"
+
+#undef  module
+#undef  type
+#undef  arity
+#undef  unify_code
+#undef  compare_code
+
+////////////////////////////////////////////////////////////////////////////
+
+#define module          builtin
+#define type            int16
+#define arity           0
+#define unify_code      MR_r1 = ((int16_t) MR_r1 == (int16_t) MR_r2);
+#define compare_code    MR_r1 =                                         \
+                            ((int16_t) MR_r1 == (int16_t) MR_r2 ?       \
+                                MR_COMPARE_EQUAL :                      \
+                            (int16_t) MR_r1 < (int16_t) MR_r2 ?         \
+                                MR_COMPARE_LESS :                       \
+                            MR_COMPARE_GREATER);
+
+#include "mercury_hand_unify_compare_body.h"
+
+#undef  module
+#undef  type
+#undef  arity
+#undef  unify_code
+#undef  compare_code
+
+////////////////////////////////////////////////////////////////////////////
+
+#define module          builtin
+#define type            uint16
+#define arity           0
+#define unify_code      MR_r1 = ((uint16_t) MR_r1 == (uint16_t) MR_r2);
+#define compare_code    MR_r1 =                                         \
+                            ((uint16_t) MR_r1 == (uint16_t) MR_r2 ?     \
+                                MR_COMPARE_EQUAL :                      \
+                            (uint16_t) MR_r1 < (uint16_t) MR_r2 ?       \
+                                MR_COMPARE_LESS :                       \
+                            MR_COMPARE_GREATER);
+
+#include "mercury_hand_unify_compare_body.h"
+
+#undef  module
+#undef  type
+#undef  arity
+#undef  unify_code
+#undef  compare_code
+
+////////////////////////////////////////////////////////////////////////////
+
+#define module          builtin
+#define type            int32
+#define arity           0
+#define unify_code      MR_r1 = ((int32_t) MR_r1 == (int32_t) MR_r2);
+#define compare_code    MR_r1 =                                         \
+                            ((int32_t) MR_r1 == (int32_t) MR_r2 ?       \
+                                MR_COMPARE_EQUAL :                      \
+                            (int32_t) MR_r1 < (int32_t) MR_r2 ?         \
+                                MR_COMPARE_LESS :                       \
+                            MR_COMPARE_GREATER);
+
+#include "mercury_hand_unify_compare_body.h"
+
+#undef  module
+#undef  type
+#undef  arity
+#undef  unify_code
+#undef  compare_code
+
+////////////////////////////////////////////////////////////////////////////
+
+#define module          builtin
+#define type            uint32
+#define arity           0
+#define unify_code      MR_r1 = ((uint32_t) MR_r1 == (uint32_t) MR_r2);
+#define compare_code    MR_r1 =                                         \
+                            ((uint32_t) MR_r1 == (uint32_t) MR_r2 ?     \
+                                MR_COMPARE_EQUAL :                      \
+                            (uint32_t) MR_r1 < (uint32_t) MR_r2 ?       \
+                                MR_COMPARE_LESS :                       \
+                            MR_COMPARE_GREATER);
+
+#include "mercury_hand_unify_compare_body.h"
+
+#undef  module
+#undef  type
+#undef  arity
+#undef  unify_code
+#undef  compare_code
+
+////////////////////////////////////////////////////////////////////////////
+
+#define module          builtin
 #define type            string
 #define arity           0
 #define unify_code      MR_r1 = strcmp((char *) MR_r1, (char *) MR_r2) == 0;
@@ -1603,6 +1939,12 @@ mercury_sys_init_mercury_builtin_types_init(void)
 
     MR_init_entry(mercury__builtin____Unify____int_0_0);
     MR_init_entry(mercury__builtin____Unify____uint_0_0);
+    MR_init_entry(mercury__builtin____Unify____int8_0_0);
+    MR_init_entry(mercury__builtin____Unify____uint8_0_0);
+    MR_init_entry(mercury__builtin____Unify____int16_0_0);
+    MR_init_entry(mercury__builtin____Unify____uint16_0_0);
+    MR_init_entry(mercury__builtin____Unify____int32_0_0);
+    MR_init_entry(mercury__builtin____Unify____uint32_0_0);
     MR_init_entry(mercury__builtin____Unify____string_0_0);
     MR_init_entry(mercury__builtin____Unify____float_0_0);
     MR_init_entry(mercury__builtin____Unify____character_0_0);
@@ -1613,6 +1955,12 @@ mercury_sys_init_mercury_builtin_types_init(void)
 
     MR_init_entry(mercury__builtin____Compare____int_0_0);
     MR_init_entry(mercury__builtin____Compare____uint_0_0);
+    MR_init_entry(mercury__builtin____Compare____int8_0_0);
+    MR_init_entry(mercury__builtin____Compare____uint8_0_0);
+    MR_init_entry(mercury__builtin____Compare____int16_0_0);
+    MR_init_entry(mercury__builtin____Compare____uint16_0_0);
+    MR_init_entry(mercury__builtin____Compare____int32_0_0);
+    MR_init_entry(mercury__builtin____Compare____uint32_0_0);
     MR_init_entry(mercury__builtin____Compare____float_0_0);
     MR_init_entry(mercury__builtin____Compare____string_0_0);
     MR_init_entry(mercury__builtin____Compare____character_0_0);
@@ -1629,6 +1977,12 @@ mercury_sys_init_mercury_builtin_types_init(void)
 
     MR_INIT_TYPE_CTOR_INFO_MNA(builtin, int, 0);
     MR_INIT_TYPE_CTOR_INFO_MNA(builtin, uint, 0);
+    MR_INIT_TYPE_CTOR_INFO_MNA(builtin, int8, 0);
+    MR_INIT_TYPE_CTOR_INFO_MNA(builtin, uint8, 0);
+    MR_INIT_TYPE_CTOR_INFO_MNA(builtin, int16, 0);
+    MR_INIT_TYPE_CTOR_INFO_MNA(builtin, uint16, 0);
+    MR_INIT_TYPE_CTOR_INFO_MNA(builtin, int32, 0);
+    MR_INIT_TYPE_CTOR_INFO_MNA(builtin, uint32, 0);
     MR_INIT_TYPE_CTOR_INFO_MNA(builtin, string, 0);
     MR_INIT_TYPE_CTOR_INFO_MNA(builtin, float, 0);
     MR_INIT_TYPE_CTOR_INFO_MNA(builtin, character, 0);
@@ -1663,6 +2017,12 @@ mercury_sys_init_mercury_builtin_types_init_type_tables(void)
 {
     MR_REGISTER_TYPE_CTOR_INFO(builtin, int, 0);
     MR_REGISTER_TYPE_CTOR_INFO(builtin, uint, 0);
+    MR_REGISTER_TYPE_CTOR_INFO(builtin, int8, 0);
+    MR_REGISTER_TYPE_CTOR_INFO(builtin, uint8, 0);
+    MR_REGISTER_TYPE_CTOR_INFO(builtin, int16, 0);
+    MR_REGISTER_TYPE_CTOR_INFO(builtin, uint16, 0);
+    MR_REGISTER_TYPE_CTOR_INFO(builtin, int32, 0);
+    MR_REGISTER_TYPE_CTOR_INFO(builtin, uint32, 0);
     MR_REGISTER_TYPE_CTOR_INFO(builtin, string, 0);
     MR_REGISTER_TYPE_CTOR_INFO(builtin, float, 0);
     MR_REGISTER_TYPE_CTOR_INFO(builtin, character, 0);
@@ -1699,6 +2059,12 @@ mercury_sys_init_mercury_builtin_types_write_out_proc_statics(FILE *deep_fp,
 {
     MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, int, 0);
     MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, uint, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, int8, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, uint8, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, int16, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, uint16, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, int32, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, uint32, 0);
     MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, string, 0);
     MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, float, 0);
     MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, character, 0);
diff --git a/runtime/mercury_builtin_types.h b/runtime/mercury_builtin_types.h
index 0d6e41e9c..6dfe0711f 100644
--- a/runtime/mercury_builtin_types.h
+++ b/runtime/mercury_builtin_types.h
@@ -26,6 +26,18 @@ MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
 MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
     MR_TYPE_CTOR_INFO_NAME(builtin, uint, 0));
 MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
+    MR_TYPE_CTOR_INFO_NAME(builtin, int8, 0));
+MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
+    MR_TYPE_CTOR_INFO_NAME(builtin, uint8, 0));
+MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
+    MR_TYPE_CTOR_INFO_NAME(builtin, int16, 0));
+MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
+    MR_TYPE_CTOR_INFO_NAME(builtin, uint16, 0));
+MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
+    MR_TYPE_CTOR_INFO_NAME(builtin, int32, 0));
+MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
+    MR_TYPE_CTOR_INFO_NAME(builtin, uint32, 0));
+MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
     MR_TYPE_CTOR_INFO_NAME(builtin, string, 0));
 MR_DECLARE_TYPE_CTOR_INFO_STRUCT(
     MR_TYPE_CTOR_INFO_NAME(builtin, float, 0));
@@ -71,6 +83,18 @@ MR_bool MR_CALL mercury__builtin____Unify____int_0_0(MR_Integer x,
                     MR_Integer y);
 MR_bool MR_CALL mercury__builtin____Unify____uint_0_0(MR_Unsigned x,
                     MR_Unsigned y);
+MR_bool MR_CALL mercury__builtin____Unify____int8_0_0(int8_t x,
+                    int8_t y);
+MR_bool MR_CALL mercury__builtin____Unify____uint8_0_0(uint8_t x,
+                    uint8_t y);
+MR_bool MR_CALL mercury__builtin____Unify____int16_0_0(int16_t x,
+                    int16_t y);
+MR_bool MR_CALL mercury__builtin____Unify____uint16_0_0(uint16_t x,
+                    uint16_t y);
+MR_bool MR_CALL mercury__builtin____Unify____int32_0_0(int32_t x,
+                    int32_t y);
+MR_bool MR_CALL mercury__builtin____Unify____uint32_0_0(uint32_t x,
+                    uint32_t y);
 MR_bool MR_CALL mercury__builtin____Unify____string_0_0(MR_String x,
                     MR_String y);
 MR_bool MR_CALL mercury__builtin____Unify____float_0_0(MR_Float x, MR_Float y);
@@ -106,6 +130,18 @@ void MR_CALL    mercury__builtin____Compare____int_0_0(
                     MR_Comparison_Result *result, MR_Integer x, MR_Integer y);
 void MR_CALL    mercury__builtin____Compare____uint_0_0(
                     MR_Comparison_Result *result, MR_Unsigned x, MR_Unsigned y);
+void MR_CALL    mercury__builtin____Compare____int8_0_0(
+                    MR_Comparison_Result *result, int8_t x, int8_t y);
+void MR_CALL    mercury__builtin____Compare____uint8_0_0(
+                    MR_Comparison_Result *result, uint8_t x, uint8_t y);
+void MR_CALL    mercury__builtin____Compare____int16_0_0(
+                    MR_Comparison_Result *result, int16_t x, int16_t y);
+void MR_CALL    mercury__builtin____Compare____uint16_0_0(
+                    MR_Comparison_Result *result, uint16_t x, uint16_t y);
+void MR_CALL    mercury__builtin____Compare____int32_0_0(
+                    MR_Comparison_Result *result, int32_t x, int32_t y);
+void MR_CALL    mercury__builtin____Compare____uint32_0_0(
+                    MR_Comparison_Result *result, uint32_t x, uint32_t y);
 void MR_CALL    mercury__builtin____Compare____string_0_0(
                     MR_Comparison_Result *result, MR_String x, MR_String y);
 void MR_CALL    mercury__builtin____Compare____float_0_0(
diff --git a/runtime/mercury_builtin_types_proc_layouts.h b/runtime/mercury_builtin_types_proc_layouts.h
index 772a16484..3b30bf7ac 100644
--- a/runtime/mercury_builtin_types_proc_layouts.h
+++ b/runtime/mercury_builtin_types_proc_layouts.h
@@ -38,6 +38,12 @@
 
 MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, int, 0);
 MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, uint, 0);
+MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, int8, 0);
+MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, uint8, 0);
+MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, int16, 0);
+MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, uint16, 0);
+MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, int32, 0);
+MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, uint32, 0);
 MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, string, 0);
 MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, float, 0);
 MR_DECLARE_UCI_PROC_STATIC_LAYOUTS(builtin, character, 0);
diff --git a/runtime/mercury_conf.h.in b/runtime/mercury_conf.h.in
index 317698749..b59cefc5e 100644
--- a/runtime/mercury_conf.h.in
+++ b/runtime/mercury_conf.h.in
@@ -139,6 +139,7 @@
 //  MR_HAVE_UTMPX_H         we have <utmpx.h>
 //  MR_HAVE_SYS_RESOURCE_H  we have <sys/resource.h>
 //  MR_HAVE_DISPATCH_DISPATCH_H we have <dispatch/dispatch.h>
+//  MR_HAVE_STDINT          we have <stdint.h>
 
 #undef  MR_HAVE_SYS_SIGINFO_H
 #undef  MR_HAVE_SYS_SIGNAL_H
@@ -172,6 +173,7 @@
 #undef  MR_HAVE_UTMPX_H
 #undef  MR_HAVE_SYS_RESOURCE_H
 #undef  MR_HAVE_DISPATCH_DISPATCH_H
+#undef  MR_HAVE_STDINT_H
 
 // MR_HAVE_POSIX_TIMES is defined if we have the POSIX
 // `struct tms' struct and times() function.
diff --git a/runtime/mercury_construct.c b/runtime/mercury_construct.c
index 2c62c79a9..b47187f4b 100644
--- a/runtime/mercury_construct.c
+++ b/runtime/mercury_construct.c
@@ -160,6 +160,12 @@ MR_get_functor_info(MR_TypeInfo type_info, int functor_number,
 
     case MR_TYPECTOR_REP_INT:
     case MR_TYPECTOR_REP_UINT:
+    case MR_TYPECTOR_REP_INT8:
+    case MR_TYPECTOR_REP_UINT8:
+    case MR_TYPECTOR_REP_INT16:
+    case MR_TYPECTOR_REP_UINT16:
+    case MR_TYPECTOR_REP_INT32:
+    case MR_TYPECTOR_REP_UINT32:
     case MR_TYPECTOR_REP_CHAR:
     case MR_TYPECTOR_REP_FLOAT:
     case MR_TYPECTOR_REP_STRING:
@@ -317,6 +323,12 @@ MR_get_num_functors(MR_TypeInfo type_info)
 
         case MR_TYPECTOR_REP_INT:
         case MR_TYPECTOR_REP_UINT:
+        case MR_TYPECTOR_REP_INT8:
+        case MR_TYPECTOR_REP_UINT8:
+        case MR_TYPECTOR_REP_INT16:
+        case MR_TYPECTOR_REP_UINT16:
+        case MR_TYPECTOR_REP_INT32:
+        case MR_TYPECTOR_REP_UINT32:
         case MR_TYPECTOR_REP_CHAR:
         case MR_TYPECTOR_REP_FLOAT:
         case MR_TYPECTOR_REP_STRING:
diff --git a/runtime/mercury_deconstruct.c b/runtime/mercury_deconstruct.c
index ed3698441..130aa2175 100644
--- a/runtime/mercury_deconstruct.c
+++ b/runtime/mercury_deconstruct.c
@@ -265,6 +265,12 @@ MR_named_arg_num(MR_TypeInfo type_info, MR_Word *term_ptr,
         case MR_TYPECTOR_REP_DUMMY:
         case MR_TYPECTOR_REP_INT:
         case MR_TYPECTOR_REP_UINT:
+        case MR_TYPECTOR_REP_INT8:
+        case MR_TYPECTOR_REP_UINT8:
+        case MR_TYPECTOR_REP_INT16:
+        case MR_TYPECTOR_REP_UINT16:
+        case MR_TYPECTOR_REP_INT32:
+        case MR_TYPECTOR_REP_UINT32:
         case MR_TYPECTOR_REP_FLOAT:
         case MR_TYPECTOR_REP_CHAR:
         case MR_TYPECTOR_REP_STRING:
diff --git a/runtime/mercury_deep_copy_body.h b/runtime/mercury_deep_copy_body.h
index df0aa33bd..1876a431b 100644
--- a/runtime/mercury_deep_copy_body.h
+++ b/runtime/mercury_deep_copy_body.h
@@ -408,6 +408,12 @@ try_again:
 
     case MR_TYPECTOR_REP_INT:  // fallthru
     case MR_TYPECTOR_REP_UINT: // fallthru
+    case MR_TYPECTOR_REP_INT8:  // fallthru
+    case MR_TYPECTOR_REP_UINT8: // fallthru
+    case MR_TYPECTOR_REP_INT16:  // fallthru
+    case MR_TYPECTOR_REP_UINT16: // fallthru
+    case MR_TYPECTOR_REP_INT32:  // fallthru
+    case MR_TYPECTOR_REP_UINT32: // fallthru
     case MR_TYPECTOR_REP_CHAR:
         return data;
 
diff --git a/runtime/mercury_dotnet.cs.in b/runtime/mercury_dotnet.cs.in
index 2e3cb1a7a..7721fe0ee 100644
--- a/runtime/mercury_dotnet.cs.in
+++ b/runtime/mercury_dotnet.cs.in
@@ -338,8 +338,14 @@ public enum TypeCtorRep {
     MR_TYPECTOR_REP_BITMAP                  = 44,
     MR_TYPECTOR_REP_FOREIGN_ENUM            = 45,
     MR_TYPECTOR_REP_FOREIGN_ENUM_USEREQ     = 46,
-    MR_TYPECTOR_REP_UNKNOWN                 = 47,
-    MR_TYPECTOR_REP_MAX                     = 48
+    MR_TYPECTOR_REP_INT8                    = 47,
+    MR_TYPECTOR_REP_UINT8                   = 48,
+    MR_TYPECTOR_REP_INT16                   = 49,
+    MR_TYPECTOR_REP_UINT16                  = 50,
+    MR_TYPECTOR_REP_INT32                   = 51,
+    MR_TYPECTOR_REP_UINT43                  = 52,
+    MR_TYPECTOR_REP_UNKNOWN                 = 53,
+    MR_TYPECTOR_REP_MAX                     = 54
 }
 
 public class PseudoTypeInfo {
diff --git a/runtime/mercury_ml_expand_body.h b/runtime/mercury_ml_expand_body.h
index e62639b34..0203ac200 100644
--- a/runtime/mercury_ml_expand_body.h
+++ b/runtime/mercury_ml_expand_body.h
@@ -793,6 +793,114 @@ EXPAND_FUNCTION_NAME(MR_TypeInfo type_info, MR_Word *data_word_ptr,
             handle_zero_arity_args();
             return;
 
+        case MR_TYPECTOR_REP_INT8:
+#ifdef  EXPAND_FUNCTOR_FIELD
+            {
+                MR_Word data_word;
+                char    buf[500];
+                char    *str;
+
+                data_word = *data_word_ptr;
+                sprintf(buf, "%" MR_INTEGER_LENGTH_MODIFIER "di8",
+                    (MR_Integer) data_word);
+                MR_make_aligned_string_copy_saved_hp(str, buf, NULL);
+                expand_info->EXPAND_FUNCTOR_FIELD = str;
+            }
+#endif  // EXPAND_FUNCTOR_FIELD
+
+            handle_zero_arity_args();
+            return;
+
+        case MR_TYPECTOR_REP_UINT8:
+#ifdef  EXPAND_FUNCTOR_FIELD
+            {
+                MR_Word data_word;
+                char    buf[500];
+                char    *str;
+
+                data_word = *data_word_ptr;
+                sprintf(buf, "%" MR_INTEGER_LENGTH_MODIFIER "uu8",
+                    (MR_Unsigned) data_word);
+                MR_make_aligned_string_copy_saved_hp(str, buf, NULL);
+                expand_info->EXPAND_FUNCTOR_FIELD = str;
+            }
+#endif  // EXPAND_FUNCTOR_FIELD
+
+            handle_zero_arity_args();
+            return;
+
+        case MR_TYPECTOR_REP_INT16:
+#ifdef  EXPAND_FUNCTOR_FIELD
+            {
+                MR_Word data_word;
+                char    buf[500];
+                char    *str;
+
+                data_word = *data_word_ptr;
+                sprintf(buf, "%" MR_INTEGER_LENGTH_MODIFIER "di16",
+                    (MR_Integer) data_word);
+                MR_make_aligned_string_copy_saved_hp(str, buf, NULL);
+                expand_info->EXPAND_FUNCTOR_FIELD = str;
+            }
+#endif  // EXPAND_FUNCTOR_FIELD
+
+            handle_zero_arity_args();
+            return;
+
+        case MR_TYPECTOR_REP_UINT16:
+#ifdef  EXPAND_FUNCTOR_FIELD
+            {
+                MR_Word data_word;
+                char    buf[500];
+                char    *str;
+
+                data_word = *data_word_ptr;
+                sprintf(buf, "%" MR_INTEGER_LENGTH_MODIFIER "uu16",
+                    (MR_Unsigned) data_word);
+                MR_make_aligned_string_copy_saved_hp(str, buf, NULL);
+                expand_info->EXPAND_FUNCTOR_FIELD = str;
+            }
+#endif  // EXPAND_FUNCTOR_FIELD
+
+            handle_zero_arity_args();
+            return;
+
+        case MR_TYPECTOR_REP_INT32:
+#ifdef  EXPAND_FUNCTOR_FIELD
+            {
+                MR_Word data_word;
+                char    buf[500];
+                char    *str;
+
+                data_word = *data_word_ptr;
+                sprintf(buf, "%" MR_INTEGER_LENGTH_MODIFIER "di32",
+                    (MR_Integer) data_word);
+                MR_make_aligned_string_copy_saved_hp(str, buf, NULL);
+                expand_info->EXPAND_FUNCTOR_FIELD = str;
+            }
+#endif  // EXPAND_FUNCTOR_FIELD
+
+            handle_zero_arity_args();
+            return;
+
+        case MR_TYPECTOR_REP_UINT32:
+#ifdef  EXPAND_FUNCTOR_FIELD
+            {
+                MR_Word data_word;
+                char    buf[500];
+                char    *str;
+
+                data_word = *data_word_ptr;
+                sprintf(buf, "%" MR_INTEGER_LENGTH_MODIFIER "uu32",
+                    (MR_Unsigned) data_word);
+                MR_make_aligned_string_copy_saved_hp(str, buf, NULL);
+                expand_info->EXPAND_FUNCTOR_FIELD = str;
+            }
+#endif  // EXPAND_FUNCTOR_FIELD
+
+            handle_zero_arity_args();
+            return;
+
         case MR_TYPECTOR_REP_CHAR:
 #ifdef  EXPAND_FUNCTOR_FIELD
             {
diff --git a/runtime/mercury_std.h b/runtime/mercury_std.h
index b19034ecf..c8bb661f8 100644
--- a/runtime/mercury_std.h
+++ b/runtime/mercury_std.h
@@ -16,6 +16,12 @@
 
 #include "mercury_regs.h"
 
+#if defined(MR_HAVE_STDINT_H)
+    #include <stdint.h>
+#else
+    #error "Mercury requires a system that provides stdint.h"
+#endif
+
 #include <stdlib.h> // for size_t
 #include <assert.h> // for assert()
 #include <errno.h>  // for EINTR
diff --git a/runtime/mercury_table_type_body.h b/runtime/mercury_table_type_body.h
index 1de1e392f..bf1883c24 100644
--- a/runtime/mercury_table_type_body.h
+++ b/runtime/mercury_table_type_body.h
@@ -307,6 +307,36 @@
             table = table_next;
             return table;
 
+        case MR_TYPECTOR_REP_INT8:
+            MR_TABLE_INT8(STATS, DEBUG, BACK, table_next, table, data);
+            table = table_next;
+            return table;
+
+        case MR_TYPECTOR_REP_UINT8:
+            MR_TABLE_UINT8(STATS, DEBUG, BACK, table_next, table, data);
+            table = table_next;
+            return table;
+
+        case MR_TYPECTOR_REP_INT16:
+            MR_TABLE_INT16(STATS, DEBUG, BACK, table_next, table, data);
+            table = table_next;
+            return table;
+
+        case MR_TYPECTOR_REP_UINT16:
+            MR_TABLE_UINT16(STATS, DEBUG, BACK, table_next, table, data);
+            table = table_next;
+            return table;
+
+        case MR_TYPECTOR_REP_INT32:
+            MR_TABLE_INT32(STATS, DEBUG, BACK, table_next, table, data);
+            table = table_next;
+            return table;
+
+        case MR_TYPECTOR_REP_UINT32:
+            MR_TABLE_UINT32(STATS, DEBUG, BACK, table_next, table, data);
+            table = table_next;
+            return table;
+
         case MR_TYPECTOR_REP_CHAR:
             MR_TABLE_CHAR(STATS, DEBUG, BACK, table_next, table, data);
             table = table_next;
diff --git a/runtime/mercury_tabling_macros.h b/runtime/mercury_tabling_macros.h
index 50ee970b3..2c773e973 100644
--- a/runtime/mercury_tabling_macros.h
+++ b/runtime/mercury_tabling_macros.h
@@ -71,10 +71,46 @@
 #define MR_RAW_TABLE_INT_STATS(stats, table, value)                         \
     MR_int_hash_lookup_or_add_stats((stats), (table), (value));
 
-#define MR_RAW_TABLE_UINT(table, value)                                      \
+#define MR_RAW_TABLE_UINT(table, value)                                     \
     MR_word_hash_lookup_or_add((table), (value));
 
-#define MR_RAW_TABLE_UINT_STATS(stats, table, value)                         \
+#define MR_RAW_TABLE_UINT_STATS(stats, table, value)                        \
+    MR_word_hash_lookup_or_add_stats((stats), (table), (value));
+
+#define MR_RAW_TABLE_INT8(table, value)                                     \
+    MR_int_hash_lookup_or_add((table), (value));
+
+#define MR_RAW_TABLE_INT8_STATS(stats, table, value)                        \
+    MR_int_hash_lookup_or_add_stats((stats), (table), (value));
+
+#define MR_RAW_TABLE_UINT8(table, value)                                    \
+    MR_word_hash_lookup_or_add((table), (value));
+
+#define MR_RAW_TABLE_UINT8_STATS(stats, table, value)                       \
+    MR_word_hash_lookup_or_add_stats((stats), (table), (value));
+
+#define MR_RAW_TABLE_INT16(table, value)                                    \
+    MR_int_hash_lookup_or_add((table), (value));
+
+#define MR_RAW_TABLE_INT16_STATS(stats, table, value)                       \
+    MR_int_hash_lookup_or_add_stats((stats), (table), (value));
+
+#define MR_RAW_TABLE_UINT16(table, value)                                   \
+    MR_word_hash_lookup_or_add((table), (value));
+
+#define MR_RAW_TABLE_UINT16_STATS(stats, table, value)                      \
+    MR_word_hash_lookup_or_add_stats((stats), (table), (value));
+
+#define MR_RAW_TABLE_INT32(table, value)                                    \
+    MR_int_hash_lookup_or_add((table), (value));
+
+#define MR_RAW_TABLE_INT32_STATS(stats, table, value)                       \
+    MR_int_hash_lookup_or_add_stats((stats), (table), (value));
+
+#define MR_RAW_TABLE_UINT32(table, value)                                   \
+    MR_word_hash_lookup_or_add((table), (value));
+
+#define MR_RAW_TABLE_UINT32_STATS(stats, table, value)                      \
     MR_word_hash_lookup_or_add_stats((stats), (table), (value));
 
 #define MR_RAW_TABLE_CHAR(table, value)                                     \
@@ -236,6 +272,85 @@
         }                                                                   \
     } while (0)
 
+#define MR_TABLE_INT8(stats, debug, back, t, t0, value)                     \
+    do {                                                                    \
+        if (stats != NULL) {                                                \
+            (t) = MR_RAW_TABLE_INT8_STATS((stats), (t0), (value));          \
+        } else {                                                            \
+            (t) = MR_RAW_TABLE_INT8((t0), (value));                         \
+        }                                                                   \
+        if (MR_tabledebug) {                                                \
+            printf("TABLE %p: int8 %ld => %p\n",                            \
+                (t0), (long) (value), (t));                                 \
+        }                                                                   \
+    } while (0)
+
+#define MR_TABLE_UINT8(stats, debug, back, t, t0, value)                    \
+    do {                                                                    \
+        if (stats != NULL) {                                                \
+            (t) = MR_RAW_TABLE_UINT8_STATS((stats), (t0), (value));         \
+        } else {                                                            \
+            (t) = MR_RAW_TABLE_UINT8((t0), (value));                        \
+        }                                                                   \
+        if (MR_tabledebug) {                                                \
+            printf("TABLE %p: uint8 %lu => %p\n",                           \
+                (t0), (unsigned long) (value), (t));                        \
+        }                                                                   \
+    } while (0)
+
+#define MR_TABLE_INT16(stats, debug, back, t, t0, value)                    \
+    do {                                                                    \
+        if (stats != NULL) {                                                \
+            (t) = MR_RAW_TABLE_INT16_STATS((stats), (t0), (value));         \
+        } else {                                                            \
+            (t) = MR_RAW_TABLE_INT16((t0), (value));                        \
+        }                                                                   \
+        if (MR_tabledebug) {                                                \
+            printf("TABLE %p: int16 %ld => %p\n",                           \
+                (t0), (long) (value), (t));                                 \
+        }                                                                   \
+    } while (0)
+
+#define MR_TABLE_UINT16(stats, debug, back, t, t0, value)                   \
+    do {                                                                    \
+        if (stats != NULL) {                                                \
+            (t) = MR_RAW_TABLE_UINT16_STATS((stats), (t0), (value));        \
+        } else {                                                            \
+            (t) = MR_RAW_TABLE_UINT16((t0), (value));                       \
+        }                                                                   \
+        if (MR_tabledebug) {                                                \
+            printf("TABLE %p: uint16 %lu => %p\n",                          \
+                (t0), (unsigned long) (value), (t));                        \
+        }                                                                   \
+    } while (0)
+
+#define MR_TABLE_INT32(stats, debug, back, t, t0, value)                    \
+    do {                                                                    \
+        if (stats != NULL) {                                                \
+            (t) = MR_RAW_TABLE_INT32_STATS((stats), (t0), (value));         \
+        } else {                                                            \
+            (t) = MR_RAW_TABLE_INT32((t0), (value));                        \
+        }                                                                   \
+        if (MR_tabledebug) {                                                \
+            printf("TABLE %p: int32 %ld => %p\n",                           \
+                (t0), (long) (value), (t));                                 \
+        }                                                                   \
+    } while (0)
+
+
+#define MR_TABLE_UINT32(stats, debug, back, t, t0, value)                   \
+    do {                                                                    \
+        if (stats != NULL) {                                                \
+            (t) = MR_RAW_TABLE_UINT32_STATS((stats), (t0), (value));        \
+        } else {                                                            \
+            (t) = MR_RAW_TABLE_UINT32((t0), (value));                       \
+        }                                                                   \
+        if (MR_tabledebug) {                                                \
+            printf("TABLE %p: uint32 %lu => %p\n",                          \
+                (t0), (unsigned long) (value), (t));                        \
+        }                                                                   \
+    } while (0)
+
 #define MR_TABLE_CHAR(stats, debug, back, t, t0, value)                     \
     do {                                                                    \
         if (stats != NULL) {                                                \
diff --git a/runtime/mercury_tabling_preds.h b/runtime/mercury_tabling_preds.h
index 5e8faea6a..e3b8749f2 100644
--- a/runtime/mercury_tabling_preds.h
+++ b/runtime/mercury_tabling_preds.h
@@ -20,6 +20,18 @@
         MR_tbl_lookup_insert_int(NULL, MR_FALSE, MR_FALSE, a, b, c)
 #define MR_table_lookup_insert_uint(a, b, c)                                \
         MR_tbl_lookup_insert_uint(NULL, MR_FALSE, MR_FALSE, a, b, c)
+#define MR_table_lookup_insert_int8(a, b, c)                                \
+        MR_tbl_lookup_insert_int8(NULL, MR_FALSE, MR_FALSE, a, b, c)
+#define MR_table_lookup_insert_uint8(a, b, c)                               \
+        MR_tbl_lookup_insert_uint8(NULL, MR_FALSE, MR_FALSE, a, b, c)
+#define MR_table_lookup_insert_int16(a, b, c)                               \
+        MR_tbl_lookup_insert_int16(NULL, MR_FALSE, MR_FALSE, a, b, c)
+#define MR_table_lookup_insert_uint16(a, b, c)                              \
+        MR_tbl_lookup_insert_uint16(NULL, MR_FALSE, MR_FALSE, a, b, c)
+#define MR_table_lookup_insert_int32(a, b, c)                               \
+        MR_tbl_lookup_insert_int32(NULL, MR_FALSE, MR_FALSE, a, b, c)
+#define MR_table_lookup_insert_uint32(a, b, c)                              \
+        MR_tbl_lookup_insert_uint32(NULL, MR_FALSE, MR_FALSE, a, b, c)
 #define MR_table_lookup_insert_start_int(a, b, c, d)                        \
         MR_tbl_lookup_insert_start_int(NULL, MR_FALSE, MR_FALSE, a, b, c, d)
 #define MR_table_lookup_insert_char(a, b, c)                                \
@@ -49,6 +61,18 @@
         MR_tbl_save_any_answer(MR_FALSE, a, b, c)
 #define MR_table_save_uint_answer(a, b, c)                                  \
         MR_tbl_save_any_answer(MR_FALSE, a, b, c)
+#define MR_table_save_int8_answer(a, b, c)                                  \
+        MR_tbl_save_any_answer(MR_FALSE, a, b, c)
+#define MR_table_save_uint8_answer(a, b, c)                                 \
+        MR_tbl_save_any_answer(MR_FALSE, a, b, c)
+#define MR_table_save_int16_answer(a, b, c)                                 \
+        MR_tbl_save_any_answer(MR_FALSE, a, b, c)
+#define MR_table_save_uint16_answer(a, b, c)                                \
+        MR_tbl_save_any_answer(MR_FALSE, a, b, c)
+#define MR_table_save_int32_answer(a, b, c)                                 \
+        MR_tbl_save_any_answer(MR_FALSE, a, b, c)
+#define MR_table_save_uint32_answer(a, b, c)                                \
+        MR_tbl_save_any_answer(MR_FALSE, a, b, c)
 #define MR_table_save_char_answer(a, b, c)                                  \
         MR_tbl_save_char_answer(MR_FALSE, a, b, c)
 #define MR_table_save_string_answer(a, b, c)                                \
@@ -64,6 +88,18 @@
         MR_tbl_restore_any_answer(MR_FALSE, a, b, c)
 #define MR_table_restore_uint_answer(a, b, c)                               \
         MR_tbl_restore_any_answer(MR_FALSE, a, b, c)
+#define MR_table_restore_int8_answer(a, b, c)                               \
+        MR_tbl_restore_any_answer(MR_FALSE, a, b, c)
+#define MR_table_restore_uint8_answer(a, b, c)                              \
+        MR_tbl_restore_any_answer(MR_FALSE, a, b, c)
+#define MR_table_restore_int16_answer(a, b, c)                              \
+        MR_tbl_restore_any_answer(MR_FALSE, a, b, c)
+#define MR_table_restore_uint16_answer(a, b, c)                             \
+        MR_tbl_restore_any_answer(MR_FALSE, a, b, c)
+#define MR_table_restore_int32_answer(a, b, c)                              \
+        MR_tbl_restore_any_answer(MR_FALSE, a, b, c)
+#define MR_table_restore_uint32_answer(a, b, c)                             \
+        MR_tbl_restore_any_answer(MR_FALSE, a, b, c)
 #define MR_table_restore_char_answer(a, b, c)                               \
         MR_tbl_restore_char_answer(MR_FALSE, a, b, c)
 #define MR_table_restore_string_answer(a, b, c)                             \
@@ -159,6 +195,36 @@
         MR_TABLE_UINT(stats, debug, back, T, T0, (MR_Unsigned) V);          \
     } while (0)
 
+#define MR_tbl_lookup_insert_int8(stats, debug, back, T0, V, T)             \
+    do {                                                                    \
+        MR_TABLE_INT8(stats, debug, back, T, T0, (MR_Integer) V);           \
+    } while (0)
+
+#define MR_tbl_lookup_insert_uint8(stats, debug, back, T0, V, T)            \
+    do {                                                                    \
+        MR_TABLE_UINT8(stats, debug, back, T, T0, (MR_Unsigned) V);         \
+    } while (0)
+
+#define MR_tbl_lookup_insert_int16(stats, debug, back, T0, V, T)            \
+    do {                                                                    \
+        MR_TABLE_INT16(stats, debug, back, T, T0, (MR_Integer) V);          \
+    } while (0)
+
+#define MR_tbl_lookup_insert_uint16(stats, debug, back, T0, V, T)           \
+    do {                                                                    \
+        MR_TABLE_UINT16(stats, debug, back, T, T0, (MR_Unsigned) V);        \
+    } while (0)
+
+#define MR_tbl_lookup_insert_int32(stats, debug, back, T0, V, T)            \
+    do {                                                                    \
+        MR_TABLE_INT32(stats, debug, back, T, T0, (MR_Integer) V);          \
+    } while (0)
+
+#define MR_tbl_lookup_insert_uint32(stats, debug, back, T0, V, T)           \
+    do {                                                                    \
+        MR_TABLE_UINT32(stats, debug, back, T, T0, (MR_Unsigned) V);        \
+    } while (0)
+
 #define MR_tbl_lookup_insert_start_int(stats, debug, back, T0, S, V, T)     \
     do {                                                                    \
         MR_TABLE_START_INT(stats, debug, back, T, T0,                       \
@@ -238,6 +304,42 @@
             &MR_TYPE_CTOR_INFO_NAME(builtin, uint, 0));                     \
     } while (0)
 
+#define MR_tbl_save_int8_answer(debug, AB, Offset, V)                       \
+    do {                                                                    \
+        MR_TABLE_SAVE_ANSWER(debug, AB, Offset, V,                          \
+            &MR_TYPE_CTOR_INFO_NAME(builtin, int8, 0));                     \
+    } while (0)
+
+#define MR_tbl_save_uint8_answer(debug, AB, Offset, V)                      \
+    do {                                                                    \
+        MR_TABLE_SAVE_ANSWER(debug, AB, Offset, V,                          \
+            &MR_TYPE_CTOR_INFO_NAME(builtin, uint8, 0));                    \
+    } while (0)
+
+#define MR_tbl_save_int16_answer(debug, AB, Offset, V)                      \
+    do {                                                                    \
+        MR_TABLE_SAVE_ANSWER(debug, AB, Offset, V,                          \
+            &MR_TYPE_CTOR_INFO_NAME(builtin, int16, 0));                    \
+    } while (0)
+
+#define MR_tbl_save_uint16_answer(debug, AB, Offset, V)                     \
+    do {                                                                    \
+        MR_TABLE_SAVE_ANSWER(debug, AB, Offset, V,                          \
+            &MR_TYPE_CTOR_INFO_NAME(builtin, uint16, 0));                   \
+    } while (0)
+
+#define MR_tbl_save_int32_answer(debug, AB, Offset, V)                      \
+    do {                                                                    \
+        MR_TABLE_SAVE_ANSWER(debug, AB, Offset, V,                          \
+            &MR_TYPE_CTOR_INFO_NAME(builtin, int32, 0));                    \
+    } while (0)
+
+#define MR_tbl_save_uint32_answer(debug, AB, Offset, V)                     \
+    do {                                                                    \
+        MR_TABLE_SAVE_ANSWER(debug, AB, Offset, V,                          \
+            &MR_TYPE_CTOR_INFO_NAME(builtin, uint32, 0));                   \
+    } while (0)
+
 #define MR_tbl_save_char_answer(debug, AB, Offset, V)                       \
     do {                                                                    \
         MR_TABLE_SAVE_ANSWER(debug, AB, Offset, V,                          \
@@ -279,6 +381,36 @@
         V = (MR_Unsigned) MR_TABLE_GET_ANSWER(debug, AB, Offset);           \
     } while (0)
 
+#define MR_tbl_restore_int8_answer(debug, AB, Offset, V)                    \
+    do {                                                                    \
+        V = (int8_t) MR_TABLE_GET_ANSWER(debug, AB, Offset);                \
+    } while (0)
+
+#define MR_tbl_restore_uint8_answer(debug, AB, Offset, V)                   \
+    do {                                                                    \
+        V = (uint8_t) MR_TABLE_GET_ANSWER(debug, AB, Offset);               \
+    } while (0)
+
+#define MR_tbl_restore_int16_answer(debug, AB, Offset, V)                   \
+    do {                                                                    \
+        V = (int16_t) MR_TABLE_GET_ANSWER(debug, AB, Offset);               \
+    } while (0)
+
+#define MR_tbl_restore_uint16_answer(debug, AB, Offset, V)                  \
+    do {                                                                    \
+        V = (uint16_t) MR_TABLE_GET_ANSWER(debug, AB, Offset);              \
+    } while (0)
+
+#define MR_tbl_restore_int32_answer(debug, AB, Offset, V)                   \
+    do {                                                                    \
+        V = (int32_t) MR_TABLE_GET_ANSWER(debug, AB, Offset);               \
+    } while (0)
+
+#define MR_tbl_restore_uint32_answer(debug, AB, Offset, V)                  \
+    do {                                                                    \
+        V = (uint32_t) MR_TABLE_GET_ANSWER(debug, AB, Offset);              \
+    } while (0)
+
 #define MR_tbl_restore_char_answer(debug, AB, Offset, V)                    \
     do {                                                                    \
         V = (MR_Char) MR_TABLE_GET_ANSWER(debug, AB, Offset);               \
diff --git a/runtime/mercury_term_size.c b/runtime/mercury_term_size.c
index 4a8783702..e2115e142 100644
--- a/runtime/mercury_term_size.c
+++ b/runtime/mercury_term_size.c
@@ -262,6 +262,66 @@ try_again:
 #endif
             return 0;
 
+        case MR_TYPECTOR_REP_INT8:
+#ifdef MR_DEBUG_TERM_SIZES
+            if (MR_heapdebug && MR_lld_print_enabled) {
+                printf(
+                    "MR_term_size: int8 %p %" MR_INTEGER_LENGTH_MODIFIER "d\n",
+                    (void *) term, (MR_Integer) term);
+            }
+#endif
+            return 0;
+
+        case MR_TYPECTOR_REP_UINT8:
+#ifdef MR_DEBUG_TERM_SIZES
+            if (MR_heapdebug && MR_lld_print_enabled) {
+                printf(
+                    "MR_term_size: uint8 %p %" MR_INTEGER_LENGTH_MODIFIER "u\n",
+                    (void *) term, (MR_Unsigned) term);
+            }
+#endif
+            return 0;
+
+        case MR_TYPECTOR_REP_INT16:
+#ifdef MR_DEBUG_TERM_SIZES
+            if (MR_heapdebug && MR_lld_print_enabled) {
+                printf(
+                    "MR_term_size: int16 %p %" MR_INTEGER_LENGTH_MODIFIER "d\n",
+                    (void *) term, (MR_Integer) term);
+            }
+#endif
+            return 0;
+
+        case MR_TYPECTOR_REP_UINT16:
+#ifdef MR_DEBUG_TERM_SIZES
+            if (MR_heapdebug && MR_lld_print_enabled) {
+                printf(
+                    "MR_term_size: uint16 %p %" MR_INTEGER_LENGTH_MODIFIER "u\n",
+                    (void *) term, (MR_Unsigned) term);
+            }
+#endif
+            return 0;
+
+        case MR_TYPECTOR_REP_INT32:
+#ifdef MR_DEBUG_TERM_SIZES
+            if (MR_heapdebug && MR_lld_print_enabled) {
+                printf(
+                    "MR_term_size: int32 %p %" MR_INTEGER_LENGTH_MODIFIER "d\n",
+                    (void *) term, (MR_Integer) term);
+            }
+#endif
+            return 0;
+
+        case MR_TYPECTOR_REP_UINT32:
+#ifdef MR_DEBUG_TERM_SIZES
+            if (MR_heapdebug && MR_lld_print_enabled) {
+                printf(
+                    "MR_term_size: uint32 %p %" MR_INTEGER_LENGTH_MODIFIER "u\n",
+                    (void *) term, (MR_Unsigned) term);
+            }
+#endif
+            return 0;
+
         case MR_TYPECTOR_REP_CHAR:
 #ifdef MR_DEBUG_TERM_SIZES
             if (MR_heapdebug && MR_lld_print_enabled) {
diff --git a/runtime/mercury_type_info.h b/runtime/mercury_type_info.h
index 9c4878af0..bb9517421 100644
--- a/runtime/mercury_type_info.h
+++ b/runtime/mercury_type_info.h
@@ -603,6 +603,12 @@ typedef enum {
     MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_BITMAP),
     MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_FOREIGN_ENUM),
     MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_FOREIGN_ENUM_USEREQ),
+    MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_INT8),
+    MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_UINT8),
+    MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_INT16),
+    MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_UINT16),
+    MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_INT32),
+    MR_DEFINE_BUILTIN_ENUM_CONST(MR_TYPECTOR_REP_UINT32),
     // MR_TYPECTOR_REP_UNKNOWN should remain the last alternative;
     // MR_TYPE_CTOR_STATS depends on this.
 
@@ -673,6 +679,12 @@ typedef MR_int_least16_t  MR_TypeCtorRepInt;
     "BITMAP",                                                           \
     "FOREIGN_ENUM",                                                     \
     "FOREIGN_ENUM_USEREQ",                                              \
+    "INT8",                                                             \
+    "UINT8",                                                            \
+    "INT16",                                                            \
+    "UINT16",                                                           \
+    "INT32",                                                            \
+    "UINT32",                                                           \
     "UNKNOWN"
 
 extern  MR_ConstString  MR_ctor_rep_name[];
@@ -1415,6 +1427,24 @@ typedef void MR_CALL MR_CompareFunc_5(MR_Mercury_Type_Info,
   #define MR_UINT_CTOR_ADDR                                               \
       (MR_Word *) &mercury__builtin__builtin__type_ctor_info_uint_0
       // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, uint, 0)
+  #define MR_INT8_CTOR_ADDR                                               \
+      (MR_Word *) &mercury__builtin__builtin__type_ctor_info_int8_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, int8, 0)
+  #define MR_UINT8_CTOR_ADDR                                              \
+      (MR_Word *) &mercury__builtin__builtin__type_ctor_info_uint8_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, uint8, 0)
+  #define MR_INT16_CTOR_ADDR                                              \
+      (MR_Word *) &mercury__builtin__builtin__type_ctor_info_int16_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, int16, 0)
+  #define MR_UINT16_CTOR_ADDR                                             \
+      (MR_Word *) &mercury__builtin__builtin__type_ctor_info_uint16_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, uint16, 0)
+  #define MR_INT32_CTOR_ADDR                                              \
+      (MR_Word *) &mercury__builtin__builtin__type_ctor_info_int32_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, int32, 0)
+  #define MR_UINT32_CTOR_ADDR                                             \
+      (MR_Word *) &mercury__builtin__builtin__type_ctor_info_uint32_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, uint32, 0)
   #define MR_FLOAT_CTOR_ADDR                                              \
       (MR_Word *) &mercury__builtin__builtin__type_ctor_info_float_0
       // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, float, 0)
@@ -1445,6 +1475,24 @@ typedef void MR_CALL MR_CompareFunc_5(MR_Mercury_Type_Info,
   #define MR_UINT_CTOR_ADDR                                               \
       (MR_Word *) &mercury_data_builtin__type_ctor_info_uint_0
       // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, uint, 0)
+  #define MR_INT8_CTOR_ADDR                                               \
+      (MR_Word *) &mercury_data_builtin__type_ctor_info_int8_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, int8, 0)
+  #define MR_UINT8_CTOR_ADDR                                              \
+      (MR_Word *) &mercury_data_builtin__type_ctor_info_uint8_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, uint8, 0)
+  #define MR_INT16_CTOR_ADDR                                              \
+      (MR_Word *) &mercury_data_builtin__type_ctor_info_int16_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, int16, 0)
+  #define MR_UINT16_CTOR_ADDR                                             \
+      (MR_Word *) &mercury_data_builtin__type_ctor_info_uint16_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, uint16, 0)
+  #define MR_INT32_CTOR_ADDR                                              \
+      (MR_Word *) &mercury_data_builtin__type_ctor_info_int32_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, int32, 0)
+  #define MR_UINT32_CTOR_ADDR                                             \
+      (MR_Word *) &mercury_data_builtin__type_ctor_info_uint32_0
+      // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, uint32, 0)
   #define MR_FLOAT_CTOR_ADDR                                              \
       (MR_Word *) &mercury_data_builtin__type_ctor_info_float_0
       // (MR_Word *) &MR_TYPE_CTOR_INFO_NAME(builtin, float, 0)
diff --git a/runtime/mercury_unify_compare_body.h b/runtime/mercury_unify_compare_body.h
index 1209e0f53..5e96b9443 100644
--- a/runtime/mercury_unify_compare_body.h
+++ b/runtime/mercury_unify_compare_body.h
@@ -616,6 +616,9 @@ start_label:
         case MR_TYPECTOR_REP_ENUM:
         case MR_TYPECTOR_REP_FOREIGN_ENUM:
         case MR_TYPECTOR_REP_INT:
+        case MR_TYPECTOR_REP_INT8:
+        case MR_TYPECTOR_REP_INT16:
+        case MR_TYPECTOR_REP_INT32:
         case MR_TYPECTOR_REP_CHAR:
 
 #ifdef  select_compare_code
@@ -631,6 +634,9 @@ start_label:
                 (MR_Integer) x == (MR_Integer) y);
 #endif
         case MR_TYPECTOR_REP_UINT:
+        case MR_TYPECTOR_REP_UINT8:
+        case MR_TYPECTOR_REP_UINT16:
+        case MR_TYPECTOR_REP_UINT32:
 
 #ifdef  select_compare_code
             if ((MR_Unsigned) x == (MR_Unsigned) y) {


More information about the reviews mailing list