[m-rev.] for review: better lookup switches

Zoltan Somogyi zs at cs.mu.OZ.AU
Wed Mar 29 14:33:07 AEDT 2006


Implement a more cache-friendly translation of lookup switches. Previously,
for a switch such as the one in

	:- pred p(foo::in, string::out, bar::out, float::out) is semidet.

	p(d, "four", f1, 4.4).
	p(e, "five", f2, 5.5).
	p(f, "six", f4("hex"), 6.6).
	p(g, "seven", f5(77.7), 7.7).

we generated three static cells, one for each argument, and then indexed
into each one in turn to get the values of HeadVar__2, HeadVar__3 and
HeadVar__4. The different static cells each represent a column here.
Each of the loads accessing the columns will access a different cache block,
so with this technique we expect to get as many cache misses as there are
output variables.

This diff changes the code we generate to use a vector of static cells
where each cell represents a row. The assignments to the output variables
will now access the different fields of a row, which will be next to each
other. We thus expect only one cache miss irrespective of the number of output
variables, at least up to the number of variables that actually fit into one
cache block.

compiler/global_data.m:
	Provide a mechanism for creating not just single (scalar) static cells,
	but arrays (vectors) of them.

compiler/lookup_switch.m:
	Use the new mechanism to generate code along the lines described above.

	Put the information passed between the two halves of the lookup switch
	implementation (detection and code generation) into an opaque data
	structure.

compiler/switch_gen.m:
	Conform to the new interface of lookup_switch.m.

compiler/ll_pseudo_type_info.m:
compiler/stack_layout.m:
compiler/string_switch.m:
compiler/unify_gen.m:
compiler/var_locn.m:
	Conform to the change to global_data.m.

compiler/llds.m:
	Define the data structures for holding vectors of static cells. Rename
	the function symbols we used to use to refer to static cells to make
	clear that they apply to scalar cells only. Provide similar mechanisms
	for representing static cell vectors and references to them.

	Generalize heap_ref heap references to allow the index to be computed
	at runtime, not compile time. For symmetry's sake, do likewise
	for stack references.

compiler/llds_out.m:
	Add the code required to write out static cell vectors.

	Rename decl_ids to increase clarity and avoid ambiguity.

compiler/code_util.m:
compiler/exprn_aux.m:
	Modify code that traverses rvals to now also traverse the new rvals
	inside memory references.

compiler/name_mangle.m:
	Provide the prefix for static cell vectors.

compiler/layout_out.m:
compiler/rtti_out.m:
compiler/opt_debug.m:
	Conform to the change to data_addrs and decl_ids.

compiler/code_info.m:
	Provide access to the new functionality in global_data.m, and conform
	to the change to llds.m.

	Provide a utility predicate needed by lookup_switch.m.

compiler/hlds_llds.m:
	Fix the formatting of some comments.

tests/hard_coded/dense_lookup_switch2.{m,exp}:
tests/hard_coded/dense_lookup_switch3.{m,exp}:
	New test cases to exercise the new algorithm.

tests/hard_coded/Mmakefile:
	Enable the new test cases, as well as an old one (from 1997!)
	that seems never to have been enabled.

Zoltan.

cvs diff: Diffing .
cvs diff: Diffing analysis
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/doc
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing boehm_gc/tests
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.316
diff -u -b -r1.316 code_info.m
--- compiler/code_info.m	27 Mar 2006 09:36:02 -0000	1.316
+++ compiler/code_info.m	28 Mar 2006 00:43:08 -0000
@@ -723,12 +723,16 @@
 :- pred add_closure_layout(comp_gen_c_data::in,
     code_info::in, code_info::out) is det.
 
-:- pred add_static_cell(assoc_list(rval, llds_type)::in,
+:- pred add_scalar_static_cell(assoc_list(rval, llds_type)::in,
     data_addr::out, code_info::in, code_info::out) is det.
 
-:- pred add_static_cell_natural_types(list(rval)::in,
+:- pred add_scalar_static_cell_natural_types(list(rval)::in,
     data_addr::out, code_info::in, code_info::out) is det.
 
+:- pred add_vector_static_cell(list(llds_type)::in,
+    list(maybe(list(rval)))::in, data_addr::out,
+    code_info::in, code_info::out) is det.
+
 %---------------------------------------------------------------------------%
 
 :- implementation.
@@ -972,15 +976,21 @@
     get_closure_layouts(!.CI, ClosureLayouts),
     set_closure_layouts([ClosureLayout | ClosureLayouts], !CI).
 
-add_static_cell(RvalsTypes, DataAddr, !CI) :-
+add_scalar_static_cell(RvalsTypes, DataAddr, !CI) :-
+    get_static_cell_info(!.CI, StaticCellInfo0),
+    global_data.add_scalar_static_cell(RvalsTypes, DataAddr,
+        StaticCellInfo0, StaticCellInfo),
+    set_static_cell_info(StaticCellInfo, !CI).
+
+add_scalar_static_cell_natural_types(Rvals, DataAddr, !CI) :-
     get_static_cell_info(!.CI, StaticCellInfo0),
-    add_static_cell(RvalsTypes, DataAddr,
+    global_data.add_scalar_static_cell_natural_types(Rvals, DataAddr,
         StaticCellInfo0, StaticCellInfo),
     set_static_cell_info(StaticCellInfo, !CI).
 
-add_static_cell_natural_types(Rvals, DataAddr, !CI) :-
+add_vector_static_cell(Types, Vector, DataAddr, !CI) :-
     get_static_cell_info(!.CI, StaticCellInfo0),
-    add_static_cell_natural_types(Rvals, DataAddr,
+    global_data.add_vector_static_cell(Types, Vector, DataAddr,
         StaticCellInfo0, StaticCellInfo),
     set_static_cell_info(StaticCellInfo, !CI).
 
@@ -3105,6 +3115,9 @@
 :- pred acquire_reg_for_var(prog_var::in, lval::out,
     code_info::in, code_info::out) is det.
 
+:- pred acquire_reg_not_in_storemap(abs_store_map::in, lval::out,
+    code_info::in, code_info::out) is det.
+
 :- pred acquire_reg(reg_type::in, lval::out,
     code_info::in, code_info::out) is det.
 
@@ -3317,6 +3330,32 @@
     ),
     set_var_locn_info(VarLocnInfo, !CI).
 
+acquire_reg_not_in_storemap(StoreMap, Lval, !CI) :-
+    map.foldl(record_highest_used_reg, StoreMap, 0, HighestUsedRegNum),
+    get_var_locn_info(!.CI, VarLocnInfo0),
+    var_locn.acquire_reg_start_at_given(HighestUsedRegNum + 1, Lval,
+        VarLocnInfo0, VarLocnInfo),
+    set_var_locn_info(VarLocnInfo, !CI).
+
+:- pred record_highest_used_reg(prog_var::in, abs_locn::in, int::in, int::out)
+    is det.
+
+record_highest_used_reg(_, AbsLocn, !HighestUsedRegNum) :-
+    (
+        AbsLocn = any_reg
+    ;
+        AbsLocn = abs_reg(N),
+        ( N > !.HighestUsedRegNum ->
+            !:HighestUsedRegNum = N
+        ;
+            true
+        )
+    ;
+        AbsLocn = abs_stackvar(_)
+    ;
+        AbsLocn = abs_framevar(_)
+    ).
+
 acquire_reg(Type, Lval, !CI) :-
     get_var_locn_info(!.CI, VarLocnInfo0),
     expect(unify(Type, r), this_file, "acquire_reg: unknown reg type"),
@@ -3771,9 +3810,9 @@
 
 stack_variable_reference(CI, Num, mem_addr(Ref)) :-
     ( get_proc_model(CI) = model_non ->
-        Ref = framevar_ref(Num)
+        Ref = framevar_ref(const(int_const(Num)))
     ;
-        Ref = stackvar_ref(Num)
+        Ref = stackvar_ref(const(int_const(Num)))
     ).
 
 %---------------------------------------------------------------------------%
Index: compiler/code_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_util.m,v
retrieving revision 1.167
diff -u -b -r1.167 code_util.m
--- compiler/code_util.m	27 Mar 2006 09:36:03 -0000	1.167
+++ compiler/code_util.m	29 Mar 2006 00:12:27 -0000
@@ -376,10 +376,9 @@
 %-----------------------------------------------------------------------------%
 
 lvals_in_lvals([], []).
-lvals_in_lvals([First | Rest], Lvals) :-
+lvals_in_lvals([First | Rest], FirstLvals ++ RestLvals) :-
     lvals_in_lval(First, FirstLvals),
-    lvals_in_lvals(Rest, RestLvals),
-    list.append(FirstLvals, RestLvals, Lvals).
+    lvals_in_lvals(Rest, RestLvals).
 
 lvals_in_rval(lval(Lval), [Lval | Lvals]) :-
     lvals_in_lval(Lval, Lvals).
@@ -389,10 +388,9 @@
 lvals_in_rval(const(_), []).
 lvals_in_rval(unop(_, Rval), Lvals) :-
     lvals_in_rval(Rval, Lvals).
-lvals_in_rval(binop(_, Rval1, Rval2), Lvals) :-
+lvals_in_rval(binop(_, Rval1, Rval2), Lvals1 ++ Lvals2) :-
     lvals_in_rval(Rval1, Lvals1),
-    lvals_in_rval(Rval2, Lvals2),
-    list.append(Lvals1, Lvals2, Lvals).
+    lvals_in_rval(Rval2, Lvals2).
 lvals_in_rval(mem_addr(MemRef), Lvals) :-
     lvals_in_mem_ref(MemRef, Lvals).
 
@@ -414,10 +412,9 @@
     lvals_in_rval(Rval, Lvals).
 lvals_in_lval(hp, []).
 lvals_in_lval(sp, []).
-lvals_in_lval(field(_, Rval1, Rval2), Lvals) :-
+lvals_in_lval(field(_, Rval1, Rval2), Lvals1 ++ Lvals2) :-
     lvals_in_rval(Rval1, Lvals1),
-    lvals_in_rval(Rval2, Lvals2),
-    list.append(Lvals1, Lvals2, Lvals).
+    lvals_in_rval(Rval2, Lvals2).
 lvals_in_lval(lvar(_), []).
 lvals_in_lval(temp(_, _), []).
 lvals_in_lval(mem_ref(Rval), Lvals) :-
@@ -425,10 +422,13 @@
 
 :- pred lvals_in_mem_ref(mem_ref::in, list(lval)::out) is det.
 
-lvals_in_mem_ref(stackvar_ref(_), []).
-lvals_in_mem_ref(framevar_ref(_), []).
-lvals_in_mem_ref(heap_ref(Rval, _, _), Lvals) :-
+lvals_in_mem_ref(stackvar_ref(Rval), Lvals) :-
     lvals_in_rval(Rval, Lvals).
+lvals_in_mem_ref(framevar_ref(Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+lvals_in_mem_ref(heap_ref(Rval1, _, Rval2), Lvals1 ++ Lvals2) :-
+    lvals_in_rval(Rval1, Lvals1),
+    lvals_in_rval(Rval2, Lvals2).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/exprn_aux.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/exprn_aux.m,v
retrieving revision 1.67
diff -u -b -r1.67 exprn_aux.m
--- compiler/exprn_aux.m	17 Mar 2006 01:40:17 -0000	1.67
+++ compiler/exprn_aux.m	29 Mar 2006 00:12:53 -0000
@@ -301,10 +301,13 @@
 
 :- pred vars_in_mem_ref(mem_ref::in, list(prog_var)::out) is det.
 
-vars_in_mem_ref(stackvar_ref(_SlotNum), []).
-vars_in_mem_ref(framevar_ref(_SlotNum), []).
-vars_in_mem_ref(heap_ref(Rval, _Tag, _FieldNum), Vars) :-
+vars_in_mem_ref(stackvar_ref(Rval), Vars) :-
     vars_in_rval(Rval, Vars).
+vars_in_mem_ref(framevar_ref(Rval), Vars) :-
+    vars_in_rval(Rval, Vars).
+vars_in_mem_ref(heap_ref(BaseRval, _Tag, FieldRval), BaseVars ++ FieldVars) :-
+    vars_in_rval(BaseRval, BaseVars),
+    vars_in_rval(FieldRval, FieldVars).
 
 %-----------------------------------------------------------------------------%
 
@@ -559,15 +562,20 @@
 
 substitute_lval_in_mem_ref(OldLval, NewLval, MemRef0, MemRef, !N) :-
     (
-        MemRef0 = stackvar_ref(_SlotNum),
-        MemRef = MemRef0
-    ;
-        MemRef0 = framevar_ref(_SlotNum),
-        MemRef = MemRef0
+        MemRef0 = stackvar_ref(Rval0),
+        substitute_lval_in_rval_count(OldLval, NewLval, Rval0, Rval, !N),
+        MemRef = stackvar_ref(Rval)
     ;
-        MemRef0 = heap_ref(Rval0, Tag, FieldNum),
+        MemRef0 = framevar_ref(Rval0),
         substitute_lval_in_rval_count(OldLval, NewLval, Rval0, Rval, !N),
-        MemRef = heap_ref(Rval, Tag, FieldNum)
+        MemRef = framevar_ref(Rval)
+    ;
+        MemRef0 = heap_ref(BaseRval0, Tag, FieldRval0),
+        substitute_lval_in_rval_count(OldLval, NewLval, BaseRval0, BaseRval,
+            !N),
+        substitute_lval_in_rval_count(OldLval, NewLval, FieldRval0, FieldRval,
+            !N),
+        MemRef = heap_ref(BaseRval, Tag, FieldRval)
     ).
 
 :- pred substitute_lval_in_lval_count(lval::in, lval::in,
Index: compiler/global_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/global_data.m,v
retrieving revision 1.15
diff -u -b -r1.15 global_data.m
--- compiler/global_data.m	21 Mar 2006 02:33:34 -0000	1.15
+++ compiler/global_data.m	27 Mar 2006 15:02:30 -0000
@@ -21,10 +21,12 @@
 :- import_module ll_backend.exprn_aux.
 :- import_module ll_backend.llds.
 :- import_module mdbcomp.prim_data. % for module_name
+:- import_module parse_tree.prog_data.
 
 :- import_module assoc_list.
 :- import_module bool.
 :- import_module list.
+:- import_module std_util.
 
 %-----------------------------------------------------------------------------%
 
@@ -69,22 +71,28 @@
 
 :- func init_static_cell_info(module_name, bool, bool) = static_cell_info.
 
-:- pred add_static_cell(assoc_list(rval, llds_type)::in, data_addr::out,
+:- pred add_scalar_static_cell(assoc_list(rval, llds_type)::in, data_addr::out,
+    static_cell_info::in, static_cell_info::out) is det.
+
+:- pred add_scalar_static_cell_natural_types(list(rval)::in, data_addr::out,
     static_cell_info::in, static_cell_info::out) is det.
 
-:- pred add_static_cell_natural_types(list(rval)::in, data_addr::out,
+:- pred find_general_llds_types(bool::in, list(mer_type)::in,
+    list(list(rval))::in, list(llds_type)::out) is semidet.
+
+:- pred add_vector_static_cell(list(llds_type)::in,
+    list(maybe(list(rval)))::in, data_addr::out,
     static_cell_info::in, static_cell_info::out) is det.
 
-:- pred search_static_cell_offset(static_cell_info::in, data_addr::in, int::in,
-    rval::out) is semidet.
+:- pred search_scalar_static_cell_offset(static_cell_info::in, data_addr::in,
+    int::in, rval::out) is semidet.
 
 :- func get_static_cells(static_cell_info) = list(comp_gen_c_data).
 
-    % Given an rval, figure out the type it would have as
-    % an argument.  Normally that's the same as its usual type;
-    % the exception is that for boxed floats, the type is data_ptr
-    % (i.e. the type of the boxed value) rather than float
-    % (the type of the unboxed value).
+    % Given an rval, figure out the type it would have as an argument.
+    % Normally that's the same as its usual type; the exception is that for
+    % boxed floats, the type is data_ptr (i.e. the type of the boxed value)
+    % rather than float (the type of the unboxed value).
     %
 :- pred rval_type_as_arg(rval::in, exprn_opts::in, llds_type::out) is det.
 
@@ -102,8 +110,8 @@
 :- import_module counter.
 :- import_module int.
 :- import_module map.
+:- import_module require.
 :- import_module set.
-:- import_module std_util.
 
 %-----------------------------------------------------------------------------%
 
@@ -194,18 +202,43 @@
 
 %-----------------------------------------------------------------------------%
 
-    % There is one cell_type_group for every group of cells that share
-    % the same sequence of argument types. We don't actually need the
-    % cell type here, since we can't get to a cell_type_group from
-    % the cell_group_map without knowing it.
+    % There is one scalar_cell_group for every group of scalar cells that
+    % share the same sequence of argument types. We don't actually need the
+    % cell type here, since we can't get to a scalar_cell_group from
+    % the scalar_cell_group_map field of the static_cell_sub_info
+    % without knowing it.
+    %
+:- type scalar_cell_group
+    --->    scalar_cell_group(
+                scalar_cell_counter         :: counter, % next cell number
+                scalar_cell_group_members   :: bimap(list(rval), data_name),
+                scalar_cell_rev_array       :: list(common_cell_value)
+            ).
+
+    % There is one vector_cell_group for every group of vector cells that
+    % share the same sequence of argument types. We don't actually need the
+    % cell type here, since we can't get to a vector_cell_group from
+    % the vector_cell_group_map field of the static_cell_sub_info
+    % without knowing it.
+    %
+    % Whereas in a scalar_cell_group, we try to find cells with the same
+    % content and represent them just once, we do not do so for vectors,
+    % because (a) the required lookup would be expensive due to the huge keys
+    % required, and (b) the probability of finding two vectors with identical
+    % contents is about zero.
     %
-:- type cell_type_group
-    --->    cell_type_group(
-                cell_counter        :: counter, % next cell number
-                cell_group_members  :: bimap(list(rval), data_name),
-                cell_rev_array      :: list(common_cell_value)
+    % The vector_cell_map field maps the cell num of a vector cell to its
+    % contents, the contents being a sequence of cells.
+    %
+:- type vector_cell_group
+    --->    vector_cell_group(
+                vector_cell_counter         :: counter, % next cell number
+                vector_cell_map             :: map(int, vector_contents)
             ).
 
+:- type vector_contents
+    --->    vector_contents(list(common_cell_value)).
+
 :- type static_cell_sub_info
     --->    static_cell_sub_info(
                 module_name         :: module_name, % base file name
@@ -218,26 +251,29 @@
                 sub_info            :: static_cell_sub_info,
                 type_counter        :: counter, % next type number
 
+                % Maps types to type numbers and vice versa.
                 cell_type_num_map   :: bimap(common_cell_type, int),
-                                    % Maps types to type numbers and vice
-                                    % versa.
 
-                cell_group_map      :: map(int, cell_type_group)
-                                    % Maps the cell type number to the
-                                    % information we have for all cells of that
-                                    % type.
+                % Maps the cell type number to the information we have
+                % for all scalar cells of that type.
+                scalar_cell_group_map       :: map(int, scalar_cell_group),
+
+                vector_cell_group_map       :: map(int, vector_cell_group)
             ).
 
 init_static_cell_info(BaseName, UnboxFloat, CommonData) = Info0 :-
     SubInfo0 = static_cell_sub_info(BaseName, UnboxFloat, CommonData),
-    Info0 = static_cell_info(SubInfo0, counter.init(0), bimap.init, map.init).
+    Info0 = static_cell_info(SubInfo0, counter.init(0), bimap.init,
+        map.init, map.init).
+
+%-----------------------------------------------------------------------------%
 
-add_static_cell_natural_types(Args, DataAddr, !Info) :-
+add_scalar_static_cell_natural_types(Args, DataAddr, !Info) :-
     list.map(associate_natural_type(!.Info ^ sub_info ^ unbox_float),
         Args, ArgsTypes),
-    add_static_cell(ArgsTypes, DataAddr, !Info).
+    add_scalar_static_cell(ArgsTypes, DataAddr, !Info).
 
-add_static_cell(ArgsTypes0, DataAddr, !Info) :-
+add_scalar_static_cell(ArgsTypes0, DataAddr, !Info) :-
     % If we have an empty cell, place a dummy field in it,
     % so that the generated C structure isn't empty.
     (
@@ -248,20 +284,25 @@
         ArgsTypes = ArgsTypes0
     ),
     compute_cell_type(ArgsTypes, CellType, CellTypeAndValue),
-    do_add_static_cell(ArgsTypes, CellType, CellTypeAndValue, DataAddr, !Info).
+    do_add_scalar_static_cell(ArgsTypes, CellType, CellTypeAndValue, DataAddr,
+        !Info).
 
-:- pred do_add_static_cell(assoc_list(rval, llds_type)::in,
+:- pred do_add_scalar_static_cell(assoc_list(rval, llds_type)::in,
     common_cell_type::in, common_cell_value::in, data_addr::out,
     static_cell_info::in, static_cell_info::out) is det.
 
-do_add_static_cell(ArgsTypes, CellType, CellValue, DataAddr, !Info) :-
+do_add_scalar_static_cell(ArgsTypes, CellType, CellValue, DataAddr, !Info) :-
     assoc_list.keys(ArgsTypes, Args),
     some [!CellGroup] (
         TypeNumMap0 = !.Info ^ cell_type_num_map,
-        CellGroupMap0 = !.Info ^ cell_group_map,
+        CellGroupMap0 = !.Info ^ scalar_cell_group_map,
         ( bimap.search(TypeNumMap0, CellType, TypeNumPrime) ->
             TypeNum = TypeNumPrime,
-            map.lookup(CellGroupMap0, TypeNum, !:CellGroup)
+            ( map.search(CellGroupMap0, TypeNum, !:CellGroup) ->
+                true
+            ;
+                !:CellGroup = init_scalar_cell_group
+            )
         ;
             TypeNumCounter0 = !.Info ^ type_counter,
             counter.allocate(TypeNum, TypeNumCounter0, TypeNumCounter),
@@ -270,24 +311,25 @@
             bimap.det_insert(TypeNumMap0, CellType, TypeNum, TypeNumMap),
             !:Info = !.Info ^ cell_type_num_map := TypeNumMap,
 
-            !:CellGroup = cell_type_group(counter.init(0), bimap.init, [])
+            !:CellGroup = init_scalar_cell_group
         ),
-        MembersMap0 = !.CellGroup ^ cell_group_members,
+        MembersMap0 = !.CellGroup ^ scalar_cell_group_members,
         ( bimap.search(MembersMap0, Args, DataNamePrime) ->
             DataName = DataNamePrime
         ;
-            CellNumCounter0 = !.CellGroup ^ cell_counter,
+            CellNumCounter0 = !.CellGroup ^ scalar_cell_counter,
             counter.allocate(CellNum, CellNumCounter0, CellNumCounter),
-            !:CellGroup = !.CellGroup ^ cell_counter := CellNumCounter,
-            DataName = common_ref(TypeNum, CellNum),
-            RevArray0 = !.CellGroup ^ cell_rev_array,
+            !:CellGroup = !.CellGroup ^ scalar_cell_counter := CellNumCounter,
+            DataName = scalar_common_ref(TypeNum, CellNum),
+            RevArray0 = !.CellGroup ^ scalar_cell_rev_array,
             RevArray = [CellValue | RevArray0],
-            !:CellGroup = !.CellGroup ^ cell_rev_array := RevArray,
+            !:CellGroup = !.CellGroup ^ scalar_cell_rev_array := RevArray,
             InsertCommonData = !.Info ^ sub_info ^ common_data,
             (
                 InsertCommonData = yes,
                 bimap.det_insert(MembersMap0, Args, DataName, MembersMap),
-                !:CellGroup = !.CellGroup ^ cell_group_members := MembersMap
+                !:CellGroup = !.CellGroup ^ scalar_cell_group_members
+                    := MembersMap
             ;
                 InsertCommonData = no
                 % With --no-common-data, we never insert any cell into
@@ -295,12 +337,210 @@
                 % be useful when comparing the LLDS and MLDS backends.
             ),
             map.set(CellGroupMap0, TypeNum, !.CellGroup, CellGroupMap),
-            !:Info = !.Info ^ cell_group_map := CellGroupMap
+            !:Info = !.Info ^ scalar_cell_group_map := CellGroupMap
         )
     ),
     ModuleName = !.Info ^ sub_info ^ module_name,
     DataAddr = data_addr(ModuleName, DataName).
 
+:- func init_scalar_cell_group = scalar_cell_group.
+
+init_scalar_cell_group = scalar_cell_group(counter.init(0), bimap.init, []).
+
+search_scalar_static_cell_offset(Info, DataAddr, Offset, Rval) :-
+    DataAddr = data_addr(Info ^ sub_info ^ module_name, DataName),
+    DataName = scalar_common_ref(TypeNum, _CellNum),
+    CellGroupMap = Info ^ scalar_cell_group_map,
+    map.lookup(CellGroupMap, TypeNum, CellGroup),
+    CellGroupMembers = CellGroup ^ scalar_cell_group_members,
+    bimap.reverse_lookup(CellGroupMembers, Rvals, DataName),
+    list.index0_det(Rvals, Offset, Rval).
+
+%-----------------------------------------------------------------------------%
+
+find_general_llds_types(UnboxFloat, Types, [Vector | Vectors], LLDSTypes) :-
+    list.map(natural_type(UnboxFloat), Vector, LLDSTypes0),
+    find_general_llds_types_2(UnboxFloat, Types, Vectors,
+        LLDSTypes0, LLDSTypes).
+
+:- pred find_general_llds_types_2(bool::in, list(mer_type)::in,
+    list(list(rval))::in, list(llds_type)::in, list(llds_type)::out)
+    is semidet.
+
+find_general_llds_types_2(_UnboxFloat, _Types, [], !LLDSTypes).
+find_general_llds_types_2(UnboxFloat, Types, [Vector | Vectors], !LLDSTypes) :-
+    find_general_llds_types_in_cell(UnboxFloat, Types, Vector, !LLDSTypes),
+    find_general_llds_types_2(UnboxFloat, Types, Vectors, !LLDSTypes).
+
+:- pred find_general_llds_types_in_cell(bool::in, list(mer_type)::in,
+    list(rval)::in, list(llds_type)::in, list(llds_type)::out) is semidet.
+
+find_general_llds_types_in_cell(_UnboxFloat, [], [], [], []).
+find_general_llds_types_in_cell(UnboxFloat, [_Type | Types], [Rval | Rvals],
+        [LLDSType0 | LLDSTypes0], [LLDSType | LLDSTypes]) :-
+    natural_type(UnboxFloat, Rval, NaturalType),
+    % For user-defined types, some function symbols may be constants
+    % (whose representations yield integer rvals) while others may be
+    % non-constants (whose representations yield data_ptr rvals).
+    % We need to be able to handle switches in which a variable of such a type
+    % has a value of one kind in one switch arm and a value of the other kind
+    % in another switch arm. We can mix the two because it is OK to initialize
+    % a field declared to be a data_ptr with an integer rval.
+    % 
+    % If there are any other similar cases, they should be added here.
+    % The value of Type may be useful in such code.
+    (
+        NaturalType = LLDSType0
+    ->
+        LLDSType = LLDSType0
+    ;
+        NaturalType = integer,
+        LLDSType0 = data_ptr
+    ->
+        LLDSType = data_ptr
+    ;
+        NaturalType = data_ptr,
+        LLDSType0 = integer
+    ->
+        LLDSType = data_ptr
+    ;
+        fail
+    ),
+    find_general_llds_types_in_cell(UnboxFloat, Types, Rvals,
+        LLDSTypes0, LLDSTypes).
+
+%-----------------------------------------------------------------------------%
+
+add_vector_static_cell(LLDSTypes, VectorData, DataAddr, !Info) :-
+    require(list.is_not_empty(LLDSTypes), "add_vector_static_cell: no types"),
+    require(list.is_not_empty(VectorData), "add_vector_static_cell: no data"),
+
+    % We don't to use grouped_args_type, since that would (a) make the code
+    % below significantly more complex, and (b) the type declaration can be
+    % expected to be only a small fraction of the size of the variable
+    % definition, so the saving in C code size wouldn't be significant.
+
+    CellType = plain_type(LLDSTypes),
+    VectorCells = list.map(pair_vector_element(LLDSTypes), VectorData),
+    some [!CellGroup] (
+        TypeNumMap0 = !.Info ^ cell_type_num_map,
+        CellGroupMap0 = !.Info ^ vector_cell_group_map,
+        ( bimap.search(TypeNumMap0, CellType, TypeNumPrime) ->
+            TypeNum = TypeNumPrime,
+            ( map.search(CellGroupMap0, TypeNum, !:CellGroup) ->
+                true
+            ;
+                !:CellGroup = init_vector_cell_group
+            )
+        ;
+            TypeNumCounter0 = !.Info ^ type_counter,
+            counter.allocate(TypeNum, TypeNumCounter0, TypeNumCounter),
+            !:Info = !.Info ^ type_counter := TypeNumCounter,
+
+            bimap.det_insert(TypeNumMap0, CellType, TypeNum, TypeNumMap),
+            !:Info = !.Info ^ cell_type_num_map := TypeNumMap,
+
+            !:CellGroup = init_vector_cell_group
+        ),
+        CellNumCounter0 = !.CellGroup ^ vector_cell_counter,
+        counter.allocate(CellNum, CellNumCounter0, CellNumCounter),
+        !:CellGroup = !.CellGroup ^ vector_cell_counter := CellNumCounter,
+        DataName = vector_common_ref(TypeNum, CellNum),
+        CellMap0 = !.CellGroup ^ vector_cell_map,
+        VectorContents = vector_contents(VectorCells),
+        map.det_insert(CellMap0, CellNum, VectorContents, CellMap),
+        !:CellGroup = !.CellGroup ^ vector_cell_map := CellMap,
+        map.set(CellGroupMap0, TypeNum, !.CellGroup, CellGroupMap),
+        !:Info = !.Info ^ vector_cell_group_map := CellGroupMap
+    ),
+    ModuleName = !.Info ^ sub_info ^ module_name,
+    DataAddr = data_addr(ModuleName, DataName).
+
+:- func init_vector_cell_group = vector_cell_group.
+
+init_vector_cell_group = vector_cell_group(counter.init(0), map.init).
+
+:- func pair_vector_element(list(llds_type), maybe(list(rval)))
+    = common_cell_value.
+
+pair_vector_element(Types, MaybeArgs) = plain_value(ArgsTypes) :-
+    (
+        MaybeArgs = no,
+        ArgsTypes = list.map(pair_with_default_value, Types)
+    ;
+        MaybeArgs = yes(Args),
+        assoc_list.from_corresponding_lists(Args, Types, ArgsTypes)
+    ).
+
+:- func pair_with_default_value(llds_type) = pair(rval, llds_type).
+
+pair_with_default_value(Type) = const(default_value_for_type(Type)) - Type.
+
+:- func default_value_for_type(llds_type) = rval_const.
+
+default_value_for_type(bool) = int_const(0).
+default_value_for_type(int_least8) = int_const(0).
+default_value_for_type(uint_least8) = int_const(0).
+default_value_for_type(int_least16) = int_const(0).
+default_value_for_type(uint_least16) = int_const(0).
+default_value_for_type(int_least32) = int_const(0).
+default_value_for_type(uint_least32) = int_const(0).
+default_value_for_type(integer) = int_const(0).
+default_value_for_type(unsigned) = int_const(0).
+default_value_for_type(float) = float_const(0.0).
+default_value_for_type(string) = string_const("").
+default_value_for_type(data_ptr) = int_const(0).
+default_value_for_type(code_ptr) = int_const(0).
+default_value_for_type(word) = int_const(0).
+
+%-----------------------------------------------------------------------------%
+
+get_static_cells(Info) = VectorDatas ++ ScalarDatas :-
+    ModuleName = Info ^ sub_info ^ module_name,
+    TypeNumMap = Info ^ cell_type_num_map,
+    map.foldl(add_scalar_static_cell_for_type(ModuleName, TypeNumMap),
+        Info ^ scalar_cell_group_map, [], RevScalarDatas),
+    list.reverse(RevScalarDatas, ScalarDatas),
+    map.foldl(add_all_vector_static_cells_for_type(ModuleName, TypeNumMap),
+        Info ^ vector_cell_group_map, [], RevVectorDatas),
+    list.reverse(RevVectorDatas, VectorDatas).
+
+:- pred add_scalar_static_cell_for_type(module_name::in,
+    bimap(common_cell_type, int)::in, int::in, scalar_cell_group::in,
+    list(comp_gen_c_data)::in, list(comp_gen_c_data)::out) is det.
+
+add_scalar_static_cell_for_type(ModuleName, TypeNumMap, TypeNum, CellGroup,
+        !Datas) :-
+    bimap.reverse_lookup(TypeNumMap, CellType, TypeNum),
+    list.reverse(CellGroup ^ scalar_cell_rev_array, ArrayContents),
+    Array = scalar_common_data_array(ModuleName, CellType, TypeNum,
+        ArrayContents),
+    Data = scalar_common_data(Array),
+    !:Datas = [Data | !.Datas].
+
+:- pred add_all_vector_static_cells_for_type(module_name::in,
+    bimap(common_cell_type, int)::in, int::in, vector_cell_group::in,
+    list(comp_gen_c_data)::in, list(comp_gen_c_data)::out) is det.
+
+add_all_vector_static_cells_for_type(ModuleName, TypeNumMap, TypeNum,
+        CellGroup, !Datas) :-
+    bimap.reverse_lookup(TypeNumMap, CellType, TypeNum),
+    map.foldl(add_one_vector_static_cell(ModuleName, TypeNum, CellType),
+        CellGroup ^ vector_cell_map, !Datas).
+
+:- pred add_one_vector_static_cell(module_name::in, int::in,
+    common_cell_type::in, int::in, vector_contents::in,
+    list(comp_gen_c_data)::in, list(comp_gen_c_data)::out) is det.
+
+add_one_vector_static_cell(ModuleName, TypeNum, CellType, CellNum,
+        vector_contents(VectorContents), !Datas) :-
+    Array = vector_common_data_array(ModuleName, CellType, TypeNum, CellNum,
+        VectorContents),
+    Data = vector_common_data(Array),
+    !:Datas = [Data | !.Datas].
+
+%-----------------------------------------------------------------------------%
+
 :- pred compute_cell_type(assoc_list(rval, llds_type)::in,
     common_cell_type::out, common_cell_value::out) is det.
 
@@ -358,35 +598,6 @@
         TypeGroup = Type - NumArgs,
         TypeAndArgGroup = common_cell_grouped_args(Type, NumArgs, Args)
     ).
-
-search_static_cell_offset(Info, DataAddr, Offset, Rval) :-
-    DataAddr = data_addr(Info ^ sub_info ^ module_name, DataName),
-    DataName = common_ref(TypeNum, _CellNum),
-    CellGroupMap = Info ^ cell_group_map,
-    map.lookup(CellGroupMap, TypeNum, CellGroup),
-    CellGroupMembers = CellGroup ^ cell_group_members,
-    bimap.reverse_lookup(CellGroupMembers, Rvals, DataName),
-    list.index0_det(Rvals, Offset, Rval).
-
-%-----------------------------------------------------------------------------%
-
-get_static_cells(Info) = Datas :-
-    ModuleName = Info ^ sub_info ^ module_name,
-    TypeNumMap = Info ^ cell_type_num_map,
-    map.foldl(add_static_cell_for_type(ModuleName, TypeNumMap),
-        Info ^ cell_group_map, [], RevDatas),
-    list.reverse(RevDatas, Datas).
-
-:- pred add_static_cell_for_type(module_name::in,
-    bimap(common_cell_type, int)::in, int::in, cell_type_group::in,
-    list(comp_gen_c_data)::in, list(comp_gen_c_data)::out) is det.
-
-add_static_cell_for_type(ModuleName, TypeNumMap, TypeNum, CellGroup, !Datas) :-
-    bimap.reverse_lookup(TypeNumMap, CellType, TypeNum),
-    list.reverse(CellGroup ^ cell_rev_array, ArrayContents),
-    Array = common_data_array(ModuleName, CellType, TypeNum, ArrayContents),
-    Data = common_data(Array),
-    !:Datas = [Data | !.Datas].
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/hlds_llds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_llds.m,v
retrieving revision 1.11
diff -u -b -r1.11 hlds_llds.m
--- compiler/hlds_llds.m	9 Mar 2006 04:56:32 -0000	1.11
+++ compiler/hlds_llds.m	28 Mar 2006 00:38:10 -0000
@@ -303,67 +303,59 @@
                 pre_deaths      :: set(prog_var),
                 post_deaths     :: set(prog_var),
 
-                % Initially set to `no' for all goals, which
-                % means the absence of the advisory
-                % information. Can be set to `yes' by the
-                % follow_vars pass, if it is invoked. Can be
-                % set to `yes' for any kind of goal.
+                % Initially set to `no' for all goals, which means the absence
+                % of the advisory information. Can be set to `yes' by the
+                % follow_vars pass, if it is invoked. Can be set to `yes'
+                % for any kind of goal.
                 %
                 % For the semantics of the value inside a `yes',
                 % see the documentation of the follow_vars type.
                 follow_vars     :: maybe(abs_follow_vars),
 
-                % This annotation is meaningful only after the
-                % store_alloc pass, and even then only if
-                % attached to a goal representing a branched
-                % control structure, i.e. an if_then_else,
-                % switch or disj goal. For those goals, the map
-                % will have an entry for every variable that is
-                % forward live after the goal, and will map
-                % each of those variables to the location where
-                % all the branches will leave the value of the
-                % variable. The code after the branched goal
-                % can therefore pick it up from there.
+                % This annotation is meaningful only after the store_alloc
+                % pass, and even then only if attached to a goal representing
+                % a branched control structure, i.e. an if_then_else, switch
+                % or disj goal. For those goals, the map will have an entry
+                % for every variable that is forward live after the goal,
+                % and will map each of those variables to the location where
+                % all the branches will leave the value of the variable.
+                % The code after the branched goal can therefore pick it
+                % up from there.
                 %
-                % This field should contain an empty map if its
-                % contents are not meaningful.
+                % This field should contain an empty map if its contents
+                % are not meaningful.
                 store_map       :: abs_store_map,
 
-                % If this goal establishes a resumption point,
-                % i.e. it is the second or later disjunct of a
-                % disjunction or if it is the condition of an
-                % if-then-else, this field will state what variables
-                % need to be saved for that resumption point, and
-                % which entry labels of the resumption point will be
+                % If this goal establishes a resumption point, i.e. it is
+                % the second or later disjunct of a disjunction or if it is
+                % the condition of an if-then-else, this field will state
+                % what variables need to be saved for that resumption point,
+                % and which entry labels of the resumption point will be
                 % needed. (See compiler/notes/allocation.html)
                 %
-                % This field is filled in during the liveness
-                % pass. Before then, and after then if the goal
-                % does not establish a resumption point, it
-                % should contain no_resume_point.
+                % This field is filled in during the liveness pass. Before
+                % then, and after then if the goal does not establish a
+                % resumption point, it should contain no_resume_point.
                 resume_point        :: resume_point,
 
                 % This field is filled in during the stackvars pass.
-                % It is not meaningful before then, and should
-                % contain `no_need'.
+                % It is not meaningful before then, and should contain
+                % `no_need'.
                 %
-                % For calls, generic calls, and for foreign_proc
-                % goals that may call back to Mercury, the stackvars
-                % pass will set this argument to need_call(NC), where
-                % NC specifies what variables need to be stored on the
-                % stack across the call.
-                %
-                % For disjunctions, if-then-elses and negations,
-                % the stackvars pass will set this argument to
-                % need_resume(NR), where NR specifies what variables
-                % need to be stored on the stack at the resumption
-                % point established by the goal.
-                %
-                % For parallel conjunctions, the stackvars pass will
-                % set this argument to need_par_conj(NPC), where NPC
-                % specifies what variables are required to be stored
-                % on the stack by the parallel conjunction execution
-                % mechanism.
+                % For calls, generic calls, and for foreign_proc goals
+                % that may call back to Mercury, the stackvars pass will set
+                % this argument to need_call(NC), where NC specifies what
+                % variables need to be stored on the stack across the call.
+                %
+                % For disjunctions, if-then-elses and negations, the stackvars
+                % pass will set this argument to need_resume(NR), where NR
+                % specifies what variables need to be stored on the stack
+                % at the resumption point established by the goal.
+                %
+                % For parallel conjunctions, the stackvars pass will set
+                % this argument to need_par_conj(NPC), where NPC specifies
+                % what variables are required to be stored on the stack
+                % by the parallel conjunction execution mechanism.
                 maybe_need      :: maybe_need
             ).
 
Index: compiler/layout_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout_out.m,v
retrieving revision 1.62
diff -u -b -r1.62 layout_out.m
--- compiler/layout_out.m	24 Mar 2006 03:03:50 -0000	1.62
+++ compiler/layout_out.m	27 Mar 2006 08:49:43 -0000
@@ -157,11 +157,11 @@
     io.write_string(";\n", !IO).
 
 output_maybe_layout_name_decl(LayoutName, !DeclSet, !IO) :-
-    ( decl_set_is_member(data_addr(layout_addr(LayoutName)), !.DeclSet) ->
+    ( decl_set_is_member(decl_data_addr(layout_addr(LayoutName)), !.DeclSet) ->
         true
     ;
         output_layout_name_decl(LayoutName, !IO),
-        decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet)
+        decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet)
     ).
 
 output_maybe_layout_data_decl(LayoutData, !DeclSet, !IO) :-
@@ -198,12 +198,12 @@
     io::di, io::uo) is det.
 
 output_layout_decl(LayoutName, !DeclSet, !IO) :-
-    ( decl_set_is_member(data_addr(layout_addr(LayoutName)), !.DeclSet) ->
+    ( decl_set_is_member(decl_data_addr(layout_addr(LayoutName)), !.DeclSet) ->
         true
     ;
         output_layout_name_storage_type_name(LayoutName, no, !IO),
         io.write_string(";\n", !IO),
-        decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet)
+        decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet)
     ).
 
     % This code should be kept in sync with output_layout_name/3 below.
@@ -552,13 +552,14 @@
         LabelVars = label_has_var_info,
         (
             LocnsTypes0 = const(data_addr_const(LTDataAddr, no)),
-            LTDataAddr = data_addr(_, common_ref(LTTypeNum, LTCellNum)),
+            LTDataAddr = data_addr(_, scalar_common_ref(LTTypeNum, LTCellNum)),
             VarNums0 = const(data_addr_const(VNDataAddr, no)),
-            VNDataAddr = data_addr(_, common_ref(VNTypeNum, VNCellNum))
+            VNDataAddr = data_addr(_, scalar_common_ref(VNTypeNum, VNCellNum))
         ->
             (
                 TypeParams0 = const(data_addr_const(TPDataAddr, no)),
-                TPDataAddr = data_addr(_, common_ref(TPTypeNum, TPCellNum))
+                TPDataAddr = data_addr(_,
+                    scalar_common_ref(TPTypeNum, TPCellNum))
             ->
                 CommonChars = "XCCC",
                 LocnsTypes1 = num_pair(LTTypeNum, LTCellNum),
@@ -629,7 +630,7 @@
         MaybeVarInfoTuple = no
     ),
     io.write_string(");\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
     % Output the rval in a context in which it is immediately cast to an
     % address.
@@ -640,7 +641,7 @@
     ( Rval = const(int_const(0)) ->
         io.write_string(" 0", !IO)
     ; Rval = const(data_addr_const(DataAddr, no)) ->
-        ( DataAddr = data_addr(_Module, common_ref(_TypeNum, _CellNum)) ->
+        ( DataAddr = data_addr(_, scalar_common_ref(_TypeNum, _CellNum)) ->
             output_data_addr(DataAddr, !IO)
         ;
             io.write_string(" &", !IO),
@@ -735,8 +736,8 @@
         ),
         output_proc_layout_data_defn_end(!IO)
     ),
-    decl_set_insert(data_addr(layout_addr(proc_layout(RttiProcLabel, Kind))),
-        !DeclSet).
+    DeclId = decl_data_addr(layout_addr(proc_layout(RttiProcLabel, Kind))),
+    decl_set_insert(DeclId, !DeclSet).
 
 :- func maybe_proc_layout_and_more_kind(maybe_proc_id_and_more,
     proc_label) = proc_layout_kind.
@@ -1050,8 +1051,8 @@
         list.foldl(output_number_in_vector, HeadVarNums, !IO)
     ),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(
-        layout_addr(proc_layout_head_var_nums(ProcLabel))), !DeclSet).
+    DeclId = decl_data_addr(layout_addr(proc_layout_head_var_nums(ProcLabel))),
+    decl_set_insert(DeclId, !DeclSet).
 
 :- pred output_proc_layout_var_names(rtti_proc_label::in, list(int)::in,
     int::in, decl_set::in, decl_set::out, io::di, io::uo) is det.
@@ -1074,8 +1075,8 @@
         list.foldl(output_number_in_vector, VarNames, !IO)
     ),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(proc_layout_var_names(ProcLabel))),
-        !DeclSet).
+    DeclId = decl_data_addr(layout_addr(proc_layout_var_names(ProcLabel))),
+    decl_set_insert(DeclId, !DeclSet).
 
 %-----------------------------------------------------------------------------%
 
@@ -1101,7 +1102,7 @@
     io.write_string(",\n", !IO),
     quote_and_write_string(GoalPath, !IO),
     io.write_string("\n};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred output_proc_id(proc_label::in, pred_origin::in, io::di, io::uo) is det.
 
@@ -1266,7 +1267,7 @@
         NumLabels),
     output_layout_name_storage_type_name(LabelExecCountName, yes, !IO),
     io.write_string(";\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LabelExecCountName)), !DeclSet),
+    decl_set_insert(decl_data_addr(layout_addr(LabelExecCountName)), !DeclSet),
 
     ModuleLayoutName = module_layout(ModuleName),
     io.write_string("\n", !IO),
@@ -1298,7 +1299,7 @@
     io.write_string(",\n", !IO),
     output_layout_name(LabelExecCountName, !IO),
     io.write_string("\n};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(ModuleLayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(ModuleLayoutName)), !DeclSet).
 
 :- pred output_module_layout_proc_vector_defn(module_name::in,
     list(layout_name)::in, layout_name::out, decl_set::in, decl_set::out,
@@ -1321,7 +1322,7 @@
         list.foldl(output_proc_layout_name_in_vector, ProcLayoutNames, !IO)
     ),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(VectorName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(VectorName)), !DeclSet).
 
 :- pred output_proc_layout_name_in_vector(layout_name::in, io::di, io::uo)
     is det.
@@ -1355,7 +1356,7 @@
     output_module_string_table_chars_driver(0, StringTableSize - 1,
         StringTable, !IO),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(TableName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(TableName)), !DeclSet).
 
     % The job of this predicate is to minimize stack space consumption in
     % grades that do not allow output_module_string_table_chars to be tail
@@ -1423,7 +1424,7 @@
         list.foldl(output_layout_name_in_vector("&"), FileLayoutNames, !IO)
     ),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(VectorName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(VectorName)), !DeclSet).
 
 :- pred output_file_layout_data_defns(module_name::in, int::in,
     list(file_layout_data)::in, list(layout_name)::out,
@@ -1466,7 +1467,7 @@
     io.write_string(",\n", !IO),
     output_layout_name(LabelVectorName, !IO),
     io.write_string("\n};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(FileLayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(FileLayoutName)), !DeclSet).
 
 :- pred output_file_layout_line_number_vector_defn(module_name::in, int::in,
     list(int)::in, layout_name::out, decl_set::in, decl_set::out,
@@ -1488,7 +1489,7 @@
         list.foldl(output_number_in_vector, LineNumbers, !IO)
     ),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred output_file_layout_label_layout_vector_defn(module_name::in, int::in,
     list(data_addr)::in, layout_name::out, decl_set::in, decl_set::out,
@@ -1511,7 +1512,7 @@
         output_label_layout_addrs_in_vector(Labels, !IO)
     ),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred project_label_layout(data_addr::in, label::out) is det.
 
@@ -1655,7 +1656,7 @@
     io.write_string(",\n\t", !IO),
     io.write_int(OldOutermostSlot, !IO),
     io.write_string("\n};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred output_call_site_static_array(rtti_proc_label::in,
     list(call_site_static_data)::in, decl_set::in, decl_set::out,
@@ -1668,7 +1669,7 @@
     io.write_string(" = {\n", !IO),
     list.foldl2(output_call_site_static, CallSites, 0, _, !IO),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred output_call_site_static(call_site_static_data::in, int::in, int::out,
     io::di, io::uo) is det.
@@ -1758,7 +1759,7 @@
     io.write_string(",\n(const MR_Type_Param_Locns *) ", !IO),
     output_rval(TypeParamsRval, !IO),
     io.write_string("\n};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred output_table_gen(rtti_proc_label::in, int::in, int::in,
     list(table_trie_step)::in, rval::in, rval::in,
@@ -1787,7 +1788,7 @@
     io.write_string(",\n(const MR_Type_Param_Locns *)\n", !IO),
     output_rval(TypeParamsRval, !IO),
     io.write_string("\n};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred output_table_gen_steps_table(rtti_proc_label::in,
     list(table_trie_step)::in, list(maybe(int))::out,
@@ -1801,7 +1802,7 @@
     io.write_string(" = {\n", !IO),
     output_table_gen_steps(Steps, MaybeEnumParams, !IO),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred output_table_gen_steps(list(table_trie_step)::in,
     list(maybe(int))::out, io::di, io::uo) is det.
@@ -1878,7 +1879,7 @@
     io.write_string(" = {\n", !IO),
     output_table_gen_enum_params(MaybeEnumParams, !IO),
     io.write_string("};\n", !IO),
-    decl_set_insert(data_addr(layout_addr(LayoutName)), !DeclSet).
+    decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
 :- pred output_table_gen_enum_params(list(maybe(int))::in,
     io::di, io::uo) is det.
Index: compiler/ll_pseudo_type_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ll_pseudo_type_info.m,v
retrieving revision 1.17
diff -u -b -r1.17 ll_pseudo_type_info.m
--- compiler/ll_pseudo_type_info.m	17 Mar 2006 01:40:24 -0000	1.17
+++ compiler/ll_pseudo_type_info.m	27 Mar 2006 07:57:38 -0000
@@ -153,8 +153,8 @@
         )
     ), Args, ArgRvals1, !StaticCellInfo),
     list.append(ArgRvals0, ArgRvals1, ArgRvals),
-    add_static_cell_natural_types([TypeCtorInfoRval | ArgRvals], DataAddr,
-        !StaticCellInfo),
+    add_scalar_static_cell_natural_types([TypeCtorInfoRval | ArgRvals],
+        DataAddr, !StaticCellInfo),
     Rval = const(data_addr_const(DataAddr, no)).
 
 :- pred convert_compound_type_info(rtti_type_ctor::in, list(rval)::in,
@@ -172,8 +172,8 @@
         convert_plain_type_info(A, SCI0, SCI, AR, _LldsType)
     ), Args, ArgRvals1, !StaticCellInfo),
     list.append(ArgRvals0, ArgRvals1, ArgRvals),
-    add_static_cell_natural_types([TypeCtorInfoRval | ArgRvals], DataAddr,
-        !StaticCellInfo),
+    add_scalar_static_cell_natural_types([TypeCtorInfoRval | ArgRvals],
+        DataAddr, !StaticCellInfo),
     Rval = const(data_addr_const(DataAddr, no)).
 
 %-----------------------------------------------------------------------------%
Index: compiler/llds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds.m,v
retrieving revision 1.327
diff -u -b -r1.327 llds.m
--- compiler/llds.m	21 Mar 2006 02:33:35 -0000	1.327
+++ compiler/llds.m	27 Mar 2006 09:12:04 -0000
@@ -117,16 +117,35 @@
     % exception: data containing code addresses must be initialized.
     %
 :- type comp_gen_c_data
-    --->    common_data(common_data_array)
+    --->    scalar_common_data(scalar_common_data_array)
+    ;       vector_common_data(vector_common_data_array)
     ;       rtti_data(rtti_data)
     ;       layout_data(layout_data).
 
-:- type common_data_array
-    --->    common_data_array(
-                module_name,        % The basename of this C file.
-                common_cell_type,   % The type of the elements of the array.
-                int,                % The type number.
-                list(common_cell_value)
+:- type scalar_common_data_array
+    --->    scalar_common_data_array(
+                scda_module     :: module_name,
+                                % The basename of this C file.
+                scda_rval_types :: common_cell_type,
+                                % The type of the elements of the array.
+                scda_type_num   :: int,
+                                % The type number.
+                scda_values     :: list(common_cell_value)
+                                % The array elements, starting at offset 0.
+            ).
+
+:- type vector_common_data_array
+    --->    vector_common_data_array(
+                vcda_module     :: module_name,
+                                % The basename of this C file.
+                vcda_rval_types :: common_cell_type,
+                                % The type of the elements of the array.
+                vcda_type_num   :: int,
+                                % The type number.
+                vcda_vector_num :: int,
+                                % The number of this vector, among all the
+                                % vector cells with this type for the elements.
+                vcda_values     :: list(common_cell_value)
                                     % The array elements, starting at offset 0.
             ).
 
@@ -827,9 +846,9 @@
             % stack.
 
 :- type mem_ref
-    --->    stackvar_ref(int)           % Stack slot number.
-    ;       framevar_ref(int)           % Stack slot number.
-    ;       heap_ref(rval, int, int).   % The cell pointer, the tag to
+    --->    stackvar_ref(rval)          % Stack slot number.
+    ;       framevar_ref(rval)          % Stack slot number.
+    ;       heap_ref(rval, int, rval).  % The cell pointer, the tag to
                                         % subtract, and the field number.
 
 :- type rval_const
@@ -853,9 +872,18 @@
     ;       layout_addr(layout_name).
 
 :- type data_name
-    --->    common_ref(int, int)
-            % The first int is the type and thus array number, the second
-            % is the offset in the array.
+    --->    scalar_common_ref(int, int)
+            % We store all standalone (scalar) common cells of the same type
+            % in an array. A reference to one of these cells contains the
+            % the type number (which becomes the distinguishing part of the
+            % name of the global variable containing all these scalar cells)
+            % which is stored in the first integer, and the offset within
+            % this array, which is stored in the second integer.
+
+    ;       vector_common_ref(int, int)
+            % We store each vector of common cells in its own global variable,
+            % identified by a sequence number. The first integer is this
+            % sequence number; the second is the offset in the array.
 
     ;       tabling_pointer(proc_label).
             % A variable that contains a pointer that points to the table
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.274
diff -u -b -r1.274 llds_out.m
--- compiler/llds_out.m	27 Mar 2006 01:01:04 -0000	1.274
+++ compiler/llds_out.m	27 Mar 2006 09:15:03 -0000
@@ -132,14 +132,14 @@
     % to put these in a new module (maybe llds_out_util).
 
 :- type decl_id
-    --->    common_type(int)
-    ;       common_array(int)
-    ;       float_label(string)
-    ;       code_addr(code_addr)
-    ;       data_addr(data_addr)
-    ;       pragma_c_struct(string)
-    ;       type_info_like_struct(int)
-    ;       typeclass_constraint_struct(int).
+    --->    decl_common_type(int)
+    ;       decl_scalar_common_array(int)
+    ;       decl_float_label(string)
+    ;       decl_code_addr(code_addr)
+    ;       decl_data_addr(data_addr)
+    ;       decl_pragma_c_struct(string)
+    ;       decl_type_info_like_struct(int)
+    ;       decl_typeclass_constraint_struct(int).
 
 :- type decl_set.
 
@@ -302,15 +302,23 @@
 
     gather_c_file_labels(Modules, Labels),
     classify_comp_gen_c_data(Datas,
-        [], CommonDatas0, [], RttiDatas, [], LayoutDatas0),
-    list.reverse(CommonDatas0, CommonDatas),
+        [], ScalarCommonDatas0, [], VectorCommonDatas0,
+        [], RttiDatas, [], LayoutDatas0),
+    list.reverse(ScalarCommonDatas0, ScalarCommonDatas),
+    list.reverse(VectorCommonDatas0, VectorCommonDatas),
     order_layout_datas(LayoutDatas0, LayoutDatas),
 
-    list.foldl2(output_common_data_decl, CommonDatas, !DeclSet, !IO),
+    list.foldl2(output_scalar_common_data_decl, ScalarCommonDatas,
+        !DeclSet, !IO),
+    list.foldl2(output_vector_common_data_decl, VectorCommonDatas,
+        !DeclSet, !IO),
     output_rtti_data_decl_list(RttiDatas, !DeclSet, !IO),
     output_c_label_decls(StackLayoutLabels, Labels, !DeclSet, !IO),
     list.foldl2(output_comp_gen_c_var, Vars, !DeclSet, !IO),
-    list.foldl2(output_common_data_defn, CommonDatas, !DeclSet, !IO),
+    list.foldl2(output_scalar_common_data_defn, ScalarCommonDatas,
+        !DeclSet, !IO),
+    list.foldl2(output_vector_common_data_defn, VectorCommonDatas,
+        !DeclSet, !IO),
     list.foldl2(output_rtti_data_defn, RttiDatas, !DeclSet, !IO),
     list.foldl2(output_layout_data_defn, LayoutDatas, !DeclSet, !IO),
 
@@ -795,16 +803,21 @@
     io.write_int(Number, !IO).
 
 :- pred classify_comp_gen_c_data(list(comp_gen_c_data)::in,
-    list(common_data_array)::in, list(common_data_array)::out,
+    list(scalar_common_data_array)::in, list(scalar_common_data_array)::out,
+    list(vector_common_data_array)::in, list(vector_common_data_array)::out,
     list(rtti_data)::in, list(rtti_data)::out,
     list(layout_data)::in, list(layout_data)::out) is det.
 
-classify_comp_gen_c_data([], !CommonList, !RttiList, !LayoutList).
-classify_comp_gen_c_data([Data | Datas], !CommonList, !RttiList,
-        !LayoutList) :-
+classify_comp_gen_c_data([], !ScalarCommonList, !VectorCommonList,
+        !RttiList, !LayoutList).
+classify_comp_gen_c_data([Data | Datas], !ScalarCommonList, !VectorCommonList,
+        !RttiList, !LayoutList) :-
     (
-        Data = common_data(CommonData),
-        !:CommonList = [CommonData | !.CommonList]
+        Data = scalar_common_data(ScalarCommonData),
+        !:ScalarCommonList = [ScalarCommonData | !.ScalarCommonList]
+    ;
+        Data = vector_common_data(VectorCommonData),
+        !:VectorCommonList = [VectorCommonData | !.VectorCommonList]
     ;
         Data = rtti_data(Rtti),
         !:RttiList = [Rtti | !.RttiList]
@@ -812,7 +825,8 @@
         Data = layout_data(Layout),
         !:LayoutList = [Layout | !.LayoutList]
     ),
-    classify_comp_gen_c_data(Datas, !CommonList, !RttiList, !LayoutList).
+    classify_comp_gen_c_data(Datas, !ScalarCommonList, !VectorCommonList,
+        !RttiList, !LayoutList).
 
     % output_c_data_type_def outputs the given the type definition.
     % This is needed because some compilers need the type definition
@@ -822,22 +836,53 @@
 :- pred output_c_data_type_def(comp_gen_c_data::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_c_data_type_def(common_data(CommonData), !DeclSet, !IO) :-
-    output_common_data_decl(CommonData, !DeclSet, !IO).
+output_c_data_type_def(scalar_common_data(ScalarCommonData), !DeclSet, !IO) :-
+    output_scalar_common_data_decl(ScalarCommonData, !DeclSet, !IO).
+output_c_data_type_def(vector_common_data(VectorCommonData), !DeclSet, !IO) :-
+    output_vector_common_data_decl(VectorCommonData, !DeclSet, !IO).
 output_c_data_type_def(rtti_data(RttiData), !DeclSet, !IO) :-
     output_rtti_data_decl(RttiData, !DeclSet, !IO).
 output_c_data_type_def(layout_data(LayoutData), !DeclSet, !IO) :-
     output_maybe_layout_data_decl(LayoutData, !DeclSet, !IO).
 
-:- pred output_common_data_decl(common_data_array::in,
+:- pred output_scalar_common_data_decl(scalar_common_data_array::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_common_data_decl(CommonDataArray, !DeclSet, !IO) :-
-    CommonDataArray = common_data_array(_ModuleName, CellType, TypeNum,
-        _Values),
+output_scalar_common_data_decl(ScalarCommonDataArray, !DeclSet, !IO) :-
+    ScalarCommonDataArray = scalar_common_data_array(_ModuleName, CellType,
+        TypeNum, _Values),
     io.write_string("\n", !IO),
+    output_common_type_defn(TypeNum, CellType, !DeclSet, !IO),
+    VarDeclId = decl_scalar_common_array(TypeNum),
+    io.write_string("static const struct ", !IO),
+    output_common_cell_type_name(TypeNum, !IO),
+    io.write_string(" ", !IO),
+    output_common_scalar_cell_array_name(TypeNum, !IO),
+    io.write_string("[];\n", !IO),
+    decl_set_insert(VarDeclId, !DeclSet).
+
+:- pred output_vector_common_data_decl(vector_common_data_array::in,
+    decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-    TypeDeclId = common_type(TypeNum),
+output_vector_common_data_decl(VectorCommonDataArray, !DeclSet, !IO) :-
+    VectorCommonDataArray = vector_common_data_array(ModuleName, CellType,
+        TypeNum, CellNum, _Values),
+    io.write_string("\n", !IO),
+    output_common_type_defn(TypeNum, CellType, !DeclSet, !IO),
+    VarDeclId = decl_data_addr(data_addr(ModuleName,
+        vector_common_ref(TypeNum, CellNum))),
+    io.write_string("static const struct ", !IO),
+    output_common_cell_type_name(TypeNum, !IO),
+    io.write_string(" ", !IO),
+    output_common_vector_cell_array_name(TypeNum, CellNum, !IO),
+    io.write_string("[];\n", !IO),
+    decl_set_insert(VarDeclId, !DeclSet).
+
+:- pred output_common_type_defn(int::in, common_cell_type::in,
+    decl_set::in, decl_set::out, io::di, io::uo) is det.
+
+output_common_type_defn(TypeNum, CellType, !DeclSet, !IO) :-
+    TypeDeclId = decl_common_type(TypeNum),
     ( decl_set_is_member(TypeDeclId, !.DeclSet) ->
         true
     ;
@@ -853,14 +898,7 @@
         ),
         io.write_string("};\n", !IO),
         decl_set_insert(TypeDeclId, !DeclSet)
-    ),
-    VarDeclId = common_array(TypeNum),
-    io.write_string("static const struct ", !IO),
-    output_common_cell_type_name(TypeNum, !IO),
-    io.write_string(" ", !IO),
-    output_common_cell_array_name(TypeNum, !IO),
-    io.write_string("[];\n", !IO),
-    decl_set_insert(VarDeclId, !DeclSet).
+    ).
 
 :- pred output_comp_gen_c_module(map(label, data_addr)::in,
     comp_gen_c_module::in, decl_set::in, decl_set::out, io::di, io::uo)
@@ -893,23 +931,52 @@
     output_tabling_pointer_var_name(ProcLabel, !IO),
     io.write_string(" = { 0 };\n", !IO),
     DataAddr = data_addr(ModuleName, tabling_pointer(ProcLabel)),
-    decl_set_insert(data_addr(DataAddr), !DeclSet).
+    decl_set_insert(decl_data_addr(DataAddr), !DeclSet).
 
 :- pred output_comp_gen_c_data(comp_gen_c_data::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_comp_gen_c_data(common_data(CommonData), !DeclSet, !IO) :-
-    output_common_data_defn(CommonData, !DeclSet, !IO).
+output_comp_gen_c_data(scalar_common_data(ScalarCommonData), !DeclSet, !IO) :-
+    output_scalar_common_data_defn(ScalarCommonData, !DeclSet, !IO).
+output_comp_gen_c_data(vector_common_data(VectorCommonData), !DeclSet, !IO) :-
+    output_vector_common_data_defn(VectorCommonData, !DeclSet, !IO).
 output_comp_gen_c_data(rtti_data(RttiData), !DeclSet, !IO) :-
     output_rtti_data_defn(RttiData, !DeclSet, !IO).
 output_comp_gen_c_data(layout_data(LayoutData), !DeclSet, !IO) :-
     output_layout_data_defn(LayoutData, !DeclSet, !IO).
 
-:- pred output_common_data_defn(common_data_array::in,
+:- pred output_scalar_common_data_defn(scalar_common_data_array::in,
+    decl_set::in, decl_set::out, io::di, io::uo) is det.
+
+output_scalar_common_data_defn(ScalarCommonDataArray, !DeclSet, !IO) :-
+    ScalarCommonDataArray = scalar_common_data_array(_ModuleName, _CellType,
+        TypeNum, Values),
+    io.write_string("\n", !IO),
+    ArgLists = list.map(common_cell_get_rvals, Values),
+    list.condense(ArgLists, Args),
+    output_rvals_decls(Args, !DeclSet, !IO),
+
+    % Although the array should have ben declared by now, it is OK if it
+    % hasn't.
+    VarDeclId = decl_scalar_common_array(TypeNum),
+    decl_set_insert(VarDeclId, !DeclSet),
+
+    io.write_string("static const struct ", !IO),
+    output_common_cell_type_name(TypeNum, !IO),
+    io.write_string(" ", !IO),
+    output_common_scalar_cell_array_name(TypeNum, !IO),
+    io.write_string("[", !IO),
+    io.write_int(list.length(Values), !IO),
+    io.write_string("] =\n{\n", !IO),
+    list.foldl(output_common_cell_value, Values, !IO),
+    io.write_string("};\n", !IO).
+
+:- pred output_vector_common_data_defn(vector_common_data_array::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_common_data_defn(CommonData, !DeclSet, !IO) :-
-    CommonData = common_data_array(_ModuleName, _CellType, TypeNum, Values),
+output_vector_common_data_defn(VectorCommonDataArray, !DeclSet, !IO) :-
+    VectorCommonDataArray = vector_common_data_array(ModuleName, _CellType,
+        TypeNum, CellNum, Values),
     io.write_string("\n", !IO),
     ArgLists = list.map(common_cell_get_rvals, Values),
     list.condense(ArgLists, Args),
@@ -917,13 +984,14 @@
 
     % Although the array should have ben declared by now, it is OK if it
     % hasn't.
-    VarDeclId = common_array(TypeNum),
+    VarDeclId = decl_data_addr(data_addr(ModuleName,
+        vector_common_ref(TypeNum, CellNum))),
     decl_set_insert(VarDeclId, !DeclSet),
 
     io.write_string("static const struct ", !IO),
     output_common_cell_type_name(TypeNum, !IO),
     io.write_string(" ", !IO),
-    output_common_cell_array_name(TypeNum, !IO),
+    output_common_vector_cell_array_name(TypeNum, CellNum, !IO),
     io.write_string("[", !IO),
     io.write_int(list.length(Values), !IO),
     io.write_string("] =\n{\n", !IO),
@@ -1116,14 +1184,14 @@
 insert_var_info_label_layout_decl(ProcLabel, LabelNum, !DeclSet) :-
     LayoutName = label_layout(ProcLabel, LabelNum, label_has_var_info),
     DataAddr = layout_addr(LayoutName),
-    DeclId = data_addr(DataAddr),
+    DeclId = decl_data_addr(DataAddr),
     decl_set_insert(DeclId, !DeclSet).
 
 :- pred insert_code_addr_decl(proc_label::in, int::in,
     decl_set::in, decl_set::out) is det.
 
 insert_code_addr_decl(ProcLabel, LabelNum, !DeclSet) :-
-    DeclId = code_addr(label(internal(LabelNum, ProcLabel))),
+    DeclId = decl_code_addr(label(internal(LabelNum, ProcLabel))),
     decl_set_insert(DeclId, !DeclSet).
 
 :- pred output_c_label_decl(map(label, data_addr)::in, label::in,
@@ -1188,7 +1256,7 @@
     ;
         AlreadyDeclaredLabel = yes
     ),
-    decl_set_insert(code_addr(label(Label)), !DeclSet).
+    decl_set_insert(decl_code_addr(label(Label)), !DeclSet).
 
 :- pred output_stack_layout_decl(data_addr::in, decl_set::in, decl_set::out,
     io::di, io::uo) is det.
@@ -1516,7 +1584,7 @@
         Struct = pragma_c_struct(StructName, StructFields,
             MaybeStructFieldsContext)
     ->
-        ( decl_set_is_member(pragma_c_struct(StructName), !.DeclSet) ->
+        ( decl_set_is_member(decl_pragma_c_struct(StructName), !.DeclSet) ->
             Msg = "struct " ++ StructName ++ " has been declared already",
             unexpected(this_file, Msg)
         ;
@@ -1535,7 +1603,7 @@
             io.write_string(StructFields, !IO)
         ),
         io.write_string("\n};\n", !IO),
-        decl_set_insert(pragma_c_struct(StructName), !DeclSet)
+        decl_set_insert(decl_pragma_c_struct(StructName), !DeclSet)
     ;
         true
     ),
@@ -2560,7 +2628,7 @@
             StaticGroundTerms = yes
         ->
             float_literal_name(FloatVal, FloatName),
-            FloatLabel = float_label(FloatName),
+            FloatLabel = decl_float_label(FloatName),
             ( decl_set_is_member(FloatLabel, !.DeclSet) ->
                 true
             ;
@@ -2602,7 +2670,7 @@
             StaticGroundTerms = yes,
             float_const_binop_expr_name(Op, Rval1, Rval2, FloatName)
         ->
-            FloatLabel = float_label(FloatName),
+            FloatLabel = decl_float_label(FloatName),
             ( decl_set_is_member(FloatLabel, !.DeclSet) ->
                 true
             ;
@@ -2656,11 +2724,20 @@
 :- pred output_mem_ref_decls_format(mem_ref::in, string::in, string::in,
     int::in, int::out, decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_mem_ref_decls_format(stackvar_ref(_), _, _, !N, !DeclSet, !IO).
-output_mem_ref_decls_format(framevar_ref(_), _, _, !N, !DeclSet, !IO).
-output_mem_ref_decls_format(heap_ref(Rval, _, _), FirstIndent, LaterIndent,
+output_mem_ref_decls_format(stackvar_ref(Rval), FirstIndent, LaterIndent,
         !N, !DeclSet, !IO) :-
-    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent,
+        !N, !DeclSet, !IO).
+output_mem_ref_decls_format(framevar_ref(Rval), FirstIndent, LaterIndent,
+        !N, !DeclSet, !IO) :-
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N,
+        !DeclSet, !IO).
+output_mem_ref_decls_format(heap_ref(BaseRval, _, OffsetRval),
+        FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
+    output_rval_decls_format(BaseRval, FirstIndent, LaterIndent, !N,
+        !DeclSet, !IO),
+    output_rval_decls_format(OffsetRval, FirstIndent, LaterIndent, !N,
+        !DeclSet, !IO).
 
 %-----------------------------------------------------------------------------%
 %
@@ -2744,26 +2821,27 @@
 
 % Common structures can include code addresses, but only in grades with
 % static code addresses.
-data_name_may_include_non_static_code_address(common_ref(_, _)) = no.
+data_name_may_include_non_static_code_address(scalar_common_ref(_, _)) = no.
+data_name_may_include_non_static_code_address(vector_common_ref(_, _)) = no.
 data_name_may_include_non_static_code_address(tabling_pointer(_)) = no.
 
 :- pred output_decl_id(decl_id::in, io::di, io::uo) is det.
 
-output_decl_id(common_type(TypeNum), !IO) :-
+output_decl_id(decl_common_type(TypeNum), !IO) :-
     output_common_cell_type_name(TypeNum, !IO).
-output_decl_id(common_array(TypeNum), !IO) :-
-    output_common_cell_array_name(TypeNum, !IO).
-output_decl_id(data_addr(DataAddr), !IO) :-
+output_decl_id(decl_scalar_common_array(TypeNum), !IO) :-
+    output_common_scalar_cell_array_name(TypeNum, !IO).
+output_decl_id(decl_data_addr(DataAddr), !IO) :-
     output_data_addr(DataAddr, !IO).
-output_decl_id(code_addr(_CodeAddress), !IO) :-
+output_decl_id(decl_code_addr(_CodeAddress), !IO) :-
     unexpected(this_file, "output_decl_id: code_addr unexpected").
-output_decl_id(float_label(_Label), !IO) :-
+output_decl_id(decl_float_label(_Label), !IO) :-
     unexpected(this_file, "output_decl_id: float_label unexpected").
-output_decl_id(pragma_c_struct(_Name), !IO) :-
+output_decl_id(decl_pragma_c_struct(_Name), !IO) :-
     unexpected(this_file, "output_decl_id: pragma_c_struct unexpected").
-output_decl_id(type_info_like_struct(_Name), !IO) :-
+output_decl_id(decl_type_info_like_struct(_Name), !IO) :-
     unexpected(this_file, "output_decl_id: type_info_like_struct unexpected").
-output_decl_id(typeclass_constraint_struct(_Name), !IO) :-
+output_decl_id(decl_typeclass_constraint_struct(_Name), !IO) :-
     unexpected(this_file,
         "output_decl_id: class_constraint_struct unexpected").
 
@@ -3106,10 +3184,10 @@
 
 output_code_addr_decls_format(CodeAddress, FirstIndent, LaterIndent, !N,
         !DeclSet, !IO) :-
-    ( decl_set_is_member(code_addr(CodeAddress), !.DeclSet) ->
+    ( decl_set_is_member(decl_code_addr(CodeAddress), !.DeclSet) ->
         true
     ;
-        decl_set_insert(code_addr(CodeAddress), !DeclSet),
+        decl_set_insert(decl_code_addr(CodeAddress), !DeclSet),
         need_code_addr_decls(CodeAddress, NeedDecl, !IO),
         (
             NeedDecl = yes,
@@ -3225,8 +3303,8 @@
 
 output_data_addr_decls_format(DataAddr, FirstIndent, LaterIndent, !N, !DeclSet,
         !IO) :-
-    ( DataAddr = data_addr(_, common_ref(TypeNum, _CellNum)) ->
-        DeclId = common_array(TypeNum),
+    ( DataAddr = data_addr(_, scalar_common_ref(TypeNum, _CellNum)) ->
+        DeclId = decl_scalar_common_array(TypeNum),
         ( decl_set_is_member(DeclId, !.DeclSet) ->
             true
         ;
@@ -3236,11 +3314,11 @@
             io.write_string("static ", !IO),
             output_common_cell_type_name(TypeNum, !IO),
             io.write_string(" ", !IO),
-            output_common_cell_array_name(TypeNum, !IO),
+            output_common_scalar_cell_array_name(TypeNum, !IO),
             io.write_string("[];\n", !IO)
         )
     ;
-        DeclId = data_addr(DataAddr),
+        DeclId = decl_data_addr(DataAddr),
         ( decl_set_is_member(DeclId, !.DeclSet) ->
             true
         ;
@@ -3334,7 +3412,8 @@
 
 :- pred data_name_linkage(data_name::in, linkage::out) is det.
 
-data_name_linkage(common_ref(_, _),   static).
+data_name_linkage(scalar_common_ref(_, _),   static).
+data_name_linkage(vector_common_ref(_, _),   static).
 data_name_linkage(tabling_pointer(_), static).
 
 %-----------------------------------------------------------------------------%
@@ -3793,13 +3872,16 @@
 
 output_data_addr_2(_ModuleName, VarName, !IO) :-
     (
-        VarName = common_ref(TypeNum, CellNum),
+        VarName = scalar_common_ref(TypeNum, CellNum),
         io.write_string("&", !IO),
-        output_common_cell_array_name(TypeNum, !IO),
+        output_common_scalar_cell_array_name(TypeNum, !IO),
         io.write_string("[", !IO),
         io.write_int(CellNum, !IO),
         io.write_string("]", !IO)
     ;
+        VarName = vector_common_ref(TypeNum, CellNum),
+        output_common_vector_cell_array_name(TypeNum, CellNum, !IO)
+    ;
         VarName = tabling_pointer(ProcLabel),
         output_tabling_pointer_var_name(ProcLabel, !IO)
     ).
@@ -3807,29 +3889,23 @@
 :- pred output_common_cell_type_name(int::in, io::di, io::uo) is det.
 
 output_common_cell_type_name(TypeNum, !IO) :-
-    output_common_prefix(common_prefix_type, !IO),
+    io.write_string(mercury_common_type_prefix, !IO),
     io.write_int(TypeNum, !IO).
 
-:- pred output_common_cell_array_name(int::in, io::di, io::uo) is det.
+:- pred output_common_scalar_cell_array_name(int::in, io::di, io::uo) is det.
 
-output_common_cell_array_name(TypeNum, !IO) :-
-    output_common_prefix(common_prefix_var, !IO),
+output_common_scalar_cell_array_name(TypeNum, !IO) :-
+    io.write_string(mercury_scalar_common_array_prefix, !IO),
     io.write_int(TypeNum, !IO).
 
-:- type common_prefix
-    --->    common_prefix_var
-    ;       common_prefix_type.
-
-:- pred output_common_prefix(common_prefix::in, io::di, io::uo) is det.
+:- pred output_common_vector_cell_array_name(int::in, int::in, io::di, io::uo)
+    is det.
 
-output_common_prefix(Prefix, !IO) :-
-    (
-        Prefix = common_prefix_var,
-        io.write_string(mercury_common_prefix, !IO)
-    ;
-        Prefix = common_prefix_type,
-        io.write_string(mercury_common_type_prefix, !IO)
-    ).
+output_common_vector_cell_array_name(TypeNum, CellNum, !IO) :-
+    io.write_string(mercury_vector_common_array_prefix, !IO),
+    io.write_int(TypeNum, !IO),
+    io.write_string("_", !IO),
+    io.write_int(CellNum, !IO).
 
 :- pred output_label_as_code_addr(label::in, io::di, io::uo) is det.
 
@@ -4357,7 +4433,7 @@
     (
         Exprn = const(data_addr_const(DataAddr, no)),
         DataAddr = data_addr(_, DataName),
-        DataName = common_ref(TypeNum, CellNum)
+        DataName = scalar_common_ref(TypeNum, CellNum)
     ->
         io.write_string("MR_TAG_XCOMMON(", !IO),
         io.write_int(Tag, !IO),
@@ -4411,26 +4487,26 @@
     unexpected(this_file, "Cannot output a var(_) expression in code").
 output_rval(mem_addr(MemRef), !IO) :-
     (
-        MemRef = stackvar_ref(N),
+        MemRef = stackvar_ref(Rval),
         output_llds_type_cast(data_ptr, !IO),
         io.write_string("&MR_sv(", !IO),
-        io.write_int(N, !IO),
+        output_rval(Rval, !IO),
         io.write_string(")", !IO)
     ;
-        MemRef = framevar_ref(N),
+        MemRef = framevar_ref(Rval),
         output_llds_type_cast(data_ptr, !IO),
         io.write_string("&MR_fv(", !IO),
-        io.write_int(N, !IO),
+        output_rval(Rval, !IO),
         io.write_string(")", !IO)
     ;
-        MemRef = heap_ref(Rval, Tag, FieldNum),
+        MemRef = heap_ref(BaseRval, Tag, FieldNumRval),
         output_llds_type_cast(data_ptr, !IO),
         io.write_string("&MR_tfield(", !IO),
         io.write_int(Tag, !IO),
         io.write_string(", ", !IO),
-        output_rval(Rval, !IO),
+        output_rval(BaseRval, !IO),
         io.write_string(", ", !IO),
-        io.write_int(FieldNum, !IO),
+        output_rval(FieldNumRval, !IO),
         io.write_string(")", !IO)
     ).
 
@@ -4483,7 +4559,7 @@
         % file size difference can be very substantial.
         (
             DataAddr = data_addr(_, DataName),
-            DataName = common_ref(TypeNum, CellNum)
+            DataName = scalar_common_ref(TypeNum, CellNum)
         ->
             io.write_string("MR_XCOMMON(", !IO),
             io.write_int(TypeNum, !IO),
Index: compiler/lookup_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lookup_switch.m,v
retrieving revision 1.63
diff -u -b -r1.63 lookup_switch.m
--- compiler/lookup_switch.m	24 Mar 2006 04:40:44 -0000	1.63
+++ compiler/lookup_switch.m	28 Mar 2006 02:55:26 -0000
@@ -50,29 +50,22 @@
 :- import_module ll_backend.llds.
 :- import_module parse_tree.prog_data.
 
-:- import_module list.
-:- import_module map.
-:- import_module set.
-:- import_module std_util.
-
 %-----------------------------------------------------------------------------%
 
-:- type case_consts == list(pair(int, list(rval))).
-
-:- type rval_map == map(prog_var, list(pair(int, rval))).
+:- type lookup_switch_info.
 
+    % Decide whether we can generate code for this switch using a lookup table.
+    %
 :- pred is_lookup_switch(prog_var::in, cases_list::in,
     hlds_goal_info::in, can_fail::in, int::in, abs_store_map::in,
-    branch_end::in, branch_end::out, code_model::in, int::out, int::out,
-    can_fail::out, can_fail::out, list(prog_var)::out, case_consts::out,
-    maybe(set(prog_var))::out, code_info::in, code_info::out) is semidet.
-
-    % Generate code for a switch using a lookup table.
-    %
-:- pred generate_lookup_switch(prog_var::in, list(prog_var)::in,
-    case_consts::in, int::in, int::in, can_fail::in, can_fail::in,
-    maybe(set(prog_var))::in, abs_store_map::in, branch_end::in,
-    code_tree::out, code_info::in, code_info::out) is det.
+    branch_end::in, branch_end::out, code_model::in, lookup_switch_info::out,
+    code_info::in, code_info::out) is semidet.
+
+    % Generate code for the switch that the lookup_switch_info came from.
+    %
+:- pred generate_lookup_switch(prog_var::in, abs_store_map::in, branch_end::in,
+    lookup_switch_info::in, code_tree::out, code_info::in, code_info::out)
+    is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -97,16 +90,43 @@
 :- import_module assoc_list.
 :- import_module bool.
 :- import_module int.
+:- import_module list.
+:- import_module map.
+:- import_module set.
 :- import_module solutions.
+:- import_module std_util.
+
+:- type case_consts == assoc_list(int, list(rval)).
+
+:- type lookup_switch_info
+    --->    lookup_switch_info(
+                lsi_first               :: int,
+                lsi_last                :: int,
+                                        % The first and last values of the
+                                        % switched-on rval covered by the
+                                        % switch.
+                lsi_cases               :: case_consts,
+                                        % The map from the switched-on value
+                                        % to the the values of the variables.
+                lsi_variables           :: list(prog_var),
+                                        % The output variables.
+                lsi_field_types         :: list(llds_type),
+                                        % The types of the fields in the C
+                                        % structure we generate for each case.
+                lsi_need_range_check    :: can_fail,
+                lsi_need_bit_vec_check  :: can_fail,
+                                        % Do we need a range check and/or a
+                                        % bit vector check on the switched-on
+                                        % variable?
+                lsi_liveness            :: maybe(set(prog_var))
+            ).
 
 %-----------------------------------------------------------------------------%
 
     % Most of this predicate is taken from dense_switch.m.
     %
-is_lookup_switch(CaseVar, TaggedCases, GoalInfo, SwitchCanFail,
-        ReqDensity, StoreMap, !MaybeEnd, CodeModel,
-        FirstVal, LastVal, NeedRangeCheck, NeedBitVecTest, OutVars,
-        CaseValues, MLiveness, !CI) :-
+is_lookup_switch(CaseVar, TaggedCases, GoalInfo, SwitchCanFail, ReqDensity,
+        StoreMap, !MaybeEnd, CodeModel, LookupSwitchInfo, !CI) :-
     % We need the code_info structure to generate code for the cases to
     % get the constants (if they exist). We can't throw it away at the
     % end because we may have allocated some new static ground term labels.
@@ -136,9 +156,9 @@
     % If there are going to be no gaps in the lookup table then we won't need
     % a bitvector test to see if this switch has a value for this case.
     ( NumCases = Range ->
-        NeedBitVecTest0 = cannot_fail
+        NeedBitVecCheck0 = cannot_fail
     ;
-        NeedBitVecTest0 = can_fail
+        NeedBitVecCheck0 = can_fail
     ),
     (
         SwitchCanFail = can_fail,
@@ -156,25 +176,33 @@
             DetDensity > ReqDensity
         ->
             NeedRangeCheck = cannot_fail,
-            NeedBitVecTest = can_fail,
+            NeedBitVecCheck = can_fail,
             FirstVal = 0,
             LastVal = TypeRange - 1
         ;
             NeedRangeCheck = SwitchCanFail,
-            NeedBitVecTest = NeedBitVecTest0,
+            NeedBitVecCheck = NeedBitVecCheck0,
             FirstVal = FirstCaseVal,
             LastVal = LastCaseVal
         )
     ;
         SwitchCanFail = cannot_fail,
         NeedRangeCheck = cannot_fail,
-        NeedBitVecTest = NeedBitVecTest0,
+        NeedBitVecCheck = NeedBitVecCheck0,
         FirstVal = FirstCaseVal,
         LastVal = LastCaseVal
     ),
     figure_out_output_vars(!.CI, GoalInfo, OutVars),
     generate_constants(TaggedCases, OutVars, StoreMap, !MaybeEnd, CodeModel,
-        CaseValues, MLiveness, !CI).
+        CaseValuePairs, MaybeLiveness, !CI),
+    VarTypes = get_var_types(!.CI),
+    list.map(map.lookup(VarTypes), OutVars, OutTypes),
+    assoc_list.values(CaseValuePairs, CaseValues),
+    code_info.get_globals(!.CI, Globals),
+    globals.lookup_bool_option(Globals, unboxed_float, UnboxFloat),
+    find_general_llds_types(UnboxFloat, OutTypes, CaseValues, LLDSTypes),
+    LookupSwitchInfo = lookup_switch_info(FirstVal, LastVal, CaseValuePairs,
+        OutVars, LLDSTypes, NeedRangeCheck, NeedBitVecCheck, MaybeLiveness).
 
 %---------------------------------------------------------------------------%
 
@@ -279,9 +307,10 @@
 
 %---------------------------------------------------------------------------%
 
-generate_lookup_switch(Var, OutVars, CaseValues, StartVal, EndVal,
-        NeedRangeCheck, NeedBitVecCheck, MLiveness, StoreMap, MaybeEnd0,
-        Code, !CI) :-
+generate_lookup_switch(Var, StoreMap, MaybeEnd0, LookupSwitchInfo, Code,
+        !CI) :-
+    LookupSwitchInfo = lookup_switch_info(StartVal, EndVal, CaseValues,
+        OutVars, LLDSTypes, NeedRangeCheck, NeedBitVecCheck, MaybeLiveness),
 
     % Evaluate the variable which we are going to be switching on.
     code_info.produce_variable(Var, VarCode, Rval, !CI),
@@ -289,9 +318,9 @@
     % If the case values start at some number other than 0,
     % then subtract that number to give us a zero-based index.
     ( StartVal = 0 ->
-        Index = Rval
+        IndexRval = Rval
     ;
-        Index = binop(int_sub, Rval, const(int_const(StartVal)))
+        IndexRval = binop(int_sub, Rval, const(int_const(StartVal)))
     ),
 
     % If the switch is not locally deterministic, we need to check that
@@ -299,39 +328,62 @@
     (
         NeedRangeCheck = can_fail,
         Difference = EndVal - StartVal,
-        code_info.fail_if_rval_is_false(
-            binop(unsigned_le, Index,
-                const(int_const(Difference))), RangeCheck, !CI)
+        CmpRval = binop(unsigned_le, IndexRval, const(int_const(Difference))),
+        code_info.fail_if_rval_is_false(CmpRval, RangeCheckCode, !CI)
     ;
         NeedRangeCheck = cannot_fail,
-        RangeCheck = empty
+        RangeCheckCode = empty
     ),
     (
         NeedBitVecCheck = can_fail,
-        generate_bitvec_test(Index, CaseValues, StartVal, EndVal, CheckBitVec,
-            !CI)
+        generate_bitvec_test(IndexRval, CaseValues, StartVal, EndVal,
+            CheckBitVecCode, !CI)
     ;
         NeedBitVecCheck = cannot_fail,
-        CheckBitVec = empty
+        CheckBitVecCode = empty
     ),
 
-    % Now generate the terms into which we do the lookups.
-    generate_terms(Index, OutVars, CaseValues, StartVal, !CI),
+    % Now generate the terms into which we do the lookups of the values of
+    % the output variables, if there are any.
+    % 
+    % Note that invoking generate_terms when OutVars = [] would lead to
+    % a compiler abort, since we cannot create C structures with zero fields.
+    (
+        OutVars = [],
+        BaseRegCode = empty,
+        MaybeBaseReg = no
+    ;
+        OutVars = [_ | _],
+        % Since we release BaseReg only after the call to generate_branch_end,
+        % we must make sure that generate_branch_end won't want to overwrite
+        % BaseReg.
+        code_info.acquire_reg_not_in_storemap(StoreMap, BaseReg, !CI),
+        MaybeBaseReg = yes(BaseReg),
+        generate_terms(IndexRval, OutVars, LLDSTypes, CaseValues, StartVal,
+            BaseRegCode, BaseReg, !CI)
+    ),
 
     % We keep track of what variables are supposed to be live at the end
     % of cases. We have to do this explicitly because generating a `fail' slot
     % last would yield the wrong liveness.
     (
-        MLiveness = yes(Liveness),
+        MaybeLiveness = yes(Liveness),
         code_info.set_forward_live_vars(Liveness, !CI)
     ;
-        MLiveness = no,
+        MaybeLiveness = no,
         unexpected(this_file, "generate_lookup_switch: no liveness!")
     ),
-    code_info.generate_branch_end(StoreMap, MaybeEnd0, _MaybeEnd, LookupCode,
-        !CI),
+    code_info.generate_branch_end(StoreMap, MaybeEnd0, _MaybeEnd,
+        BranchEndCode, !CI),
+    (
+        MaybeBaseReg = no
+    ;
+        MaybeBaseReg = yes(FinalBaseReg),
+        code_info.release_reg(FinalBaseReg, !CI)
+    ),
     Comment = node([comment("lookup switch") - ""]),
-    Code = tree_list([Comment, VarCode, RangeCheck, CheckBitVec, LookupCode]).
+    Code = tree_list([Comment, VarCode, RangeCheckCode, CheckBitVecCode,
+        BaseRegCode, BranchEndCode]).
 
 %-----------------------------------------------------------------------------%
 
@@ -343,7 +395,7 @@
 :- pred generate_bitvec_test(rval::in, case_consts::in, int::in, int::in,
     code_tree::out, code_info::in, code_info::out) is det.
 
-generate_bitvec_test(Index, CaseVals, Start, _End, CheckCode, !CI) :-
+generate_bitvec_test(IndexRval, CaseVals, Start, _End, CheckCode, !CI) :-
     get_word_bits(!.CI, WordBits, Log2WordBits),
     generate_bit_vec(CaseVals, Start, WordBits, BitVecArgs, BitVecRval, !CI),
 
@@ -353,20 +405,20 @@
     % and the low bits specify which bit.
     ( BitVecArgs = [SingleWord] ->
         Word = SingleWord,
-        BitNum = Index
+        BitNum = IndexRval
     ;
         % This is the same as
-        % WordNum = binop(int_div, Index, const(int_const(WordBits)))
+        % WordNum = binop(int_div, IndexRval, const(int_const(WordBits)))
         % except that it can generate more efficient code.
-        WordNum = binop(unchecked_right_shift, Index,
+        WordNum = binop(unchecked_right_shift, IndexRval,
             const(int_const(Log2WordBits))),
 
         Word = lval(field(yes(0), BitVecRval, WordNum)),
 
         % This is the same as
-        % BitNum = binop(int_mod, Index, const(int_const(WordBits)))
+        % BitNum = binop(int_mod, IndexRval, const(int_const(WordBits)))
         % except that it can generate more efficient code.
-        BitNum = binop(bitwise_and, Index, const(int_const(WordBits - 1)))
+        BitNum = binop(bitwise_and, IndexRval, const(int_const(WordBits - 1)))
     ),
     HasBit = binop(bitwise_and,
         binop(unchecked_left_shift, const(int_const(1)), BitNum), Word),
@@ -407,7 +459,7 @@
     generate_bit_vec_2(CaseVals, Start, WordBits, Empty, BitMap),
     map.to_assoc_list(BitMap, WordVals),
     generate_bit_vec_args(WordVals, 0, Args),
-    add_static_cell_natural_types(Args, DataAddr, !CI),
+    add_scalar_static_cell_natural_types(Args, DataAddr, !CI),
     BitVec = const(data_addr_const(DataAddr, no)).
 
 :- pred generate_bit_vec_2(case_consts::in, int::in, int::in,
@@ -447,76 +499,57 @@
     % Add an expression to the expression cache in the code_info structure
     % for each of the output variables of the lookup switch. This is done by
     % creating a `create' term for the array, and caching an expression
-    % for the variable to get the Index'th field of that term.
+    % for the variable to get the IndexRval'th field of that term.
     %
-:- pred generate_terms(rval::in, list(prog_var)::in, case_consts::in, int::in,
+:- pred generate_terms(rval::in, list(prog_var)::in, list(llds_type)::in,
+    case_consts::in, int::in, code_tree::out, lval::in,
     code_info::in, code_info::out) is det.
 
-generate_terms(Index, OutVars, CaseVals, Start, !CI) :-
-    map.init(Empty),
-    rearrange_vals(OutVars, CaseVals, Start, Empty, ValMap),
-    generate_terms_2(Index, OutVars, ValMap, !CI).
-
-:- pred generate_terms_2(rval::in, list(prog_var)::in,
-    rval_map::in, code_info::in, code_info::out) is det.
-
-generate_terms_2(_Index, [], _Map, !CI).
-generate_terms_2(Index, [Var | Vars], Map, !CI) :-
-    map.lookup(Map, Var, Vals0),
-    list.sort(Vals0, Vals),
-    construct_args(Vals, 0, Args),
-    code_info.add_static_cell_natural_types(Args, DataAddr, !CI),
-    ArrayTerm = const(data_addr_const(DataAddr, no)),
-    LookupLval = field(yes(0), ArrayTerm, Index),
-    code_info.assign_lval_to_var(Var, LookupLval, Code, !CI),
-    expect(tree.is_empty(Code), this_file, "generate_terms_2: nonempty code"),
-    generate_terms_2(Index, Vars, Map, !CI).
-
-:- pred construct_args(list(pair(int, rval))::in, int::in, list(rval)::out)
-    is det.
-
-construct_args([], _, []).
-construct_args([Index - Rval | Rest], Count0, [Arg | Args]) :-
-    ( Count0 < Index ->
+generate_terms(IndexRval, OutVars, OutTypes, CaseVals, Start, Code, BaseReg,
+        !CI) :-
+    list.length(OutVars, NumOutVars),
+    construct_vector(Start, CaseVals, VectorRvals),
+    code_info.add_vector_static_cell(OutTypes, VectorRvals, VectorAddr, !CI),
+
+    VectorAddrRval = const(data_addr_const(VectorAddr, no)),
+    % IndexRval has already had Start subtracted from it.
+    ( NumOutVars = 1 ->
+        BaseRval = IndexRval
+    ;
+        BaseRval = binop(int_mul, IndexRval, const(int_const(NumOutVars)))
+    ),
+    Code = node([
+        assign(BaseReg, mem_addr(heap_ref(VectorAddrRval, 0, BaseRval)))
+            - "Compute base address for this case"
+    ]),
+    generate_offset_assigns(OutVars, 0, BaseReg, !CI).
+
+:- pred construct_vector(int::in, case_consts::in,
+    list(maybe(list(rval)))::out) is det.
+
+construct_vector(_, [], []).
+construct_vector(CurIndex, [Index - Rvals | Rest], [MaybeRow | MaybeRows]) :-
+    ( CurIndex < Index ->
         % If this argument (array element) is a place-holder and
-        % will never be referenced, just fill it in with a `0'.
-        Arg = const(int_const(0)),
-        Remainder = [Index - Rval | Rest]
+        % will never be referenced, just fill it in with a dummy entry.
+        MaybeRow = no,
+        Remainder = [Index - Rvals | Rest]
     ;
-        Arg = Rval,
+        MaybeRow = yes(Rvals),
         Remainder = Rest
     ),
-    Count1 = Count0 + 1,
-    construct_args(Remainder, Count1, Args).
+    construct_vector(CurIndex + 1, Remainder, MaybeRows).
 
-%-----------------------------------------------------------------------------%
+:- pred generate_offset_assigns(list(prog_var)::in, int::in, lval::in,
+    code_info::in, code_info::out) is det.
 
-    % For the purpose of constructing the terms, the case_consts structure
-    % is a bit inconvenient, so we rearrange the data into a map from var
-    % to list of tag-value pairs.
-    %
-:- pred rearrange_vals(list(prog_var)::in, case_consts::in, int::in,
-    rval_map::in, rval_map::out) is det.
-
-rearrange_vals(_Vars, [], _Start, Map, Map).
-rearrange_vals(Vars, [Tag - Rvals | Rest], Start, Map0, Map) :-
-    assoc_list.from_corresponding_lists(Vars, Rvals, Pairs),
-    Index = Tag - Start,
-    rearrange_vals_2(Pairs, Index, Map0, Map1),
-    rearrange_vals(Vars, Rest, Start, Map1, Map).
-
-:- pred rearrange_vals_2(list(pair(prog_var, rval))::in, int::in,
-    rval_map::in, rval_map::out) is det.
-
-rearrange_vals_2([], _, Map, Map).
-rearrange_vals_2([Var - Rval | Rest], Tag, Map0, Map) :-
-    ( map.search(Map0, Var, Vals0) ->
-        Vals = [Tag - Rval | Vals0]
-    ;
-        Vals = [Tag - Rval]
-    ),
-    map.set(Map0, Var, Vals, Map1),
-    rearrange_vals_2(Rest, Tag, Map1, Map).
+generate_offset_assigns([], _, _, !CI).
+generate_offset_assigns([Var | Vars], Offset, BaseReg, !CI) :-
+    LookupLval = field(yes(0), lval(BaseReg), const(int_const(Offset))),
+    code_info.assign_lval_to_var(Var, LookupLval, Code, !CI),
+    expect(tree.is_empty(Code), this_file,
+        "generate_offset_assigns: nonempty code"),
+    generate_offset_assigns(Vars, Offset + 1, BaseReg, !CI).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/name_mangle.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/name_mangle.m,v
retrieving revision 1.16
diff -u -b -r1.16 name_mangle.m
--- compiler/name_mangle.m	17 Mar 2006 01:40:33 -0000	1.16
+++ compiler/name_mangle.m	27 Mar 2006 08:12:00 -0000
@@ -80,11 +80,12 @@
 :- func mercury_label_prefix = string.
 
     % All the C data structures we generate which are either fully static
-    % or static after initialization should have one of these two prefixes,
+    % or static after initialization should have one of these yrefixes,
     % to ensure that Mercury global variables don't clash with C symbols.
     %
 :- func mercury_data_prefix = string.
-:- func mercury_common_prefix = string.
+:- func mercury_scalar_common_array_prefix = string.
+:- func mercury_vector_common_array_prefix = string.
 
     % All the C types we generate should have this prefix to ensure
     % that they don't clash with C symbols.
@@ -278,8 +279,8 @@
 mercury_label_prefix = "mercury__".
 
 mercury_data_prefix = "mercury_data_".
-
-mercury_common_prefix = "mercury_common_".
+mercury_scalar_common_array_prefix = "mercury_common_".
+mercury_vector_common_array_prefix = "mercury_vector_common_".
 
 mercury_common_type_prefix = "mercury_type_".
 
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.164
diff -u -b -r1.164 opt_debug.m
--- compiler/opt_debug.m	24 Mar 2006 03:03:56 -0000	1.164
+++ compiler/opt_debug.m	27 Mar 2006 09:15:38 -0000
@@ -301,12 +301,12 @@
     dump_rval(Rval) ++ ", " ++ dump_rvals(Rvals).
 
 dump_mem_ref(stackvar_ref(N)) =
-    "stackvar_ref(" ++ int_to_string(N) ++ ")".
+    "stackvar_ref(" ++ dump_rval(N) ++ ")".
 dump_mem_ref(framevar_ref(N)) =
-    "framevar_ref(" ++ int_to_string(N) ++ ")".
+    "framevar_ref(" ++ dump_rval(N) ++ ")".
 dump_mem_ref(heap_ref(R, T, N)) =
     "heap_ref(" ++ dump_rval(R) ++ ", " ++ int_to_string(T) ++ ", "
-        ++ int_to_string(N) ++ ")".
+        ++ dump_rval(N) ++ ")".
 
 dump_const(true) = "true".
 dump_const(false) = "false".
@@ -343,8 +343,11 @@
 dump_data_addr(layout_addr(LayoutName)) =
     "layout_addr(" ++ dump_layout_name(LayoutName) ++ ")".
 
-dump_data_name(common_ref(TypeNum, Offset)) =
-    "common_ref(" ++ int_to_string(TypeNum) ++ ", "
+dump_data_name(scalar_common_ref(TypeNum, Offset)) =
+    "scalar_common_ref(" ++ int_to_string(TypeNum) ++ ", "
+        ++ int_to_string(Offset) ++ ")".
+dump_data_name(vector_common_ref(TypeNum, Offset)) =
+    "vector_common_ref(" ++ int_to_string(TypeNum) ++ ", "
         ++ int_to_string(Offset) ++ ")".
 dump_data_name(tabling_pointer(ProcLabel)) =
     "tabling_pointer(" ++ dump_proclabel(ProcLabel) ++ ")".
Index: compiler/rtti_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rtti_out.m,v
retrieving revision 1.64
diff -u -b -r1.64 rtti_out.m
--- compiler/rtti_out.m	24 Mar 2006 03:04:01 -0000	1.64
+++ compiler/rtti_out.m	27 Mar 2006 08:54:45 -0000
@@ -440,7 +440,7 @@
     (
         rtti_data_to_id(type_info(TypeInfo), RttiId),
         DataAddr = rtti_addr(RttiId),
-        decl_set_is_member(data_addr(DataAddr), !.DeclSet)
+        decl_set_is_member(decl_data_addr(DataAddr), !.DeclSet)
     ->
         true
     ;
@@ -496,7 +496,7 @@
     ;
         rtti_data_to_id(pseudo_type_info(PseudoTypeInfo), RttiId),
         DataAddr = rtti_addr(RttiId),
-        decl_set_is_member(data_addr(DataAddr), !.DeclSet)
+        decl_set_is_member(decl_data_addr(DataAddr), !.DeclSet)
     ->
         true
     ;
@@ -1301,7 +1301,7 @@
 output_rtti_data_decl_chunk_entries(IsArray, [RttiId | RttiIds],
         !DeclSet, !IO) :-
     DataAddr = rtti_addr(RttiId),
-    decl_set_insert(data_addr(DataAddr), !DeclSet),
+    decl_set_insert(decl_data_addr(DataAddr), !DeclSet),
     io.write_string("\t", !IO),
     output_rtti_id(RttiId, !IO),
     (
@@ -1340,7 +1340,7 @@
     output_rtti_id_storage_type_name(RttiId, no, !DeclSet, !IO),
     io.write_string(";\n", !IO),
     DataAddr = rtti_addr(RttiId),
-    decl_set_insert(data_addr(DataAddr), !DeclSet).
+    decl_set_insert(decl_data_addr(DataAddr), !DeclSet).
 
 :- pred output_generic_rtti_data_defn_start(rtti_id::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
@@ -1349,7 +1349,7 @@
     io.write_string("\n", !IO),
     output_rtti_id_storage_type_name(RttiId, yes, !DeclSet, !IO),
     DataAddr = rtti_addr(RttiId),
-    decl_set_insert(data_addr(DataAddr), !DeclSet).
+    decl_set_insert(decl_data_addr(DataAddr), !DeclSet).
 
 output_rtti_id_storage_type_name_no_decl(RttiId, BeingDefined, !IO) :-
     decl_set_init(DeclSet0),
@@ -1389,7 +1389,7 @@
         rtti_type_ctor_template_arity(RttiName, Arity),
         Arity > max_always_declared_arity_type_ctor
     ->
-        DeclId = type_info_like_struct(Arity),
+        DeclId = decl_type_info_like_struct(Arity),
         ( decl_set_is_member(DeclId, !.DeclSet) ->
             true
         ;
@@ -1407,7 +1407,7 @@
         rtti_type_class_constraint_template_arity(TCRttiName, Arity),
         Arity > max_always_declared_arity_type_class_constraint
     ->
-        DeclId = typeclass_constraint_struct(Arity),
+        DeclId = decl_typeclass_constraint_struct(Arity),
         ( decl_set_is_member(DeclId, !.DeclSet) ->
             true
         ;
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.113
diff -u -b -r1.113 stack_layout.m
--- compiler/stack_layout.m	24 Mar 2006 03:04:02 -0000	1.113
+++ compiler/stack_layout.m	27 Mar 2006 08:03:42 -0000
@@ -951,7 +951,7 @@
         TypeParamRval = const(int_const(0))
     ;
         construct_tvar_rvals(TVarLocnMap, Vector),
-        add_static_cell(Vector, DataAddr, !StaticCellInfo),
+        add_scalar_static_cell(Vector, DataAddr, !StaticCellInfo),
         TypeParamRval = const(data_addr_const(DataAddr, no))
     ).
 
@@ -1124,7 +1124,7 @@
     list.append(IntLocnsTypes, ByteLocnsTypes, AllLocnsTypes),
     list.append(AllTypeRvalsTypes, AllLocnsTypes, TypeLocnVectorRvalsTypes),
     get_static_cell_info(!.Info, StaticCellInfo0),
-    add_static_cell(TypeLocnVectorRvalsTypes, TypeLocnVectorAddr,
+    add_scalar_static_cell(TypeLocnVectorRvalsTypes, TypeLocnVectorAddr,
         StaticCellInfo0, StaticCellInfo1),
     TypeLocnVector = const(data_addr_const(TypeLocnVectorAddr, no)),
     set_static_cell_info(StaticCellInfo1, !Info),
@@ -1136,7 +1136,7 @@
         list.reverse(RevVarNumRvals, VarNumRvals),
         list.map(associate_type(uint_least16), VarNumRvals, VarNumRvalsTypes),
         get_static_cell_info(!.Info, StaticCellInfo2),
-        add_static_cell(VarNumRvalsTypes, NumVectorAddr,
+        add_scalar_static_cell(VarNumRvalsTypes, NumVectorAddr,
             StaticCellInfo2, StaticCellInfo),
         set_static_cell_info(StaticCellInfo, !Info),
         NumVector = const(data_addr_const(NumVectorAddr, no))
@@ -1301,7 +1301,7 @@
     list.length(Args, NumPTIs),
     list.map_foldl(construct_table_arg_pti_rval, Args, PTIRvalsTypes,
         !StaticCellInfo),
-    add_static_cell(PTIRvalsTypes, PTIVectorAddr, !StaticCellInfo),
+    add_scalar_static_cell(PTIRvalsTypes, PTIVectorAddr, !StaticCellInfo),
     PTIVectorRval = const(data_addr_const(PTIVectorAddr, no)),
     map.map_values(convert_slot_to_locn_map, TVarSlotMap, TVarLocnMap),
     construct_tvar_vector(TVarLocnMap, TVarVectorRval, !StaticCellInfo).
Index: compiler/string_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/string_switch.m,v
retrieving revision 1.53
diff -u -b -r1.53 string_switch.m
--- compiler/string_switch.m	17 Mar 2006 01:40:41 -0000	1.53
+++ compiler/string_switch.m	27 Mar 2006 08:03:54 -0000
@@ -96,9 +96,10 @@
 
     % Generate code which does the hash table lookup
     (
-        add_static_cell_natural_types(NextSlots, NextSlotsTableAddr, !CI),
+        add_scalar_static_cell_natural_types(NextSlots, NextSlotsTableAddr,
+            !CI),
         NextSlotsTable = const(data_addr_const(NextSlotsTableAddr, no)),
-        add_static_cell_natural_types(Strings, StringTableAddr, !CI),
+        add_scalar_static_cell_natural_types(Strings, StringTableAddr, !CI),
         StringTable = const(data_addr_const(StringTableAddr, no)),
         HashLookupCode = node([
             comment("hashed string switch") - "",
Index: compiler/switch_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/switch_gen.m,v
retrieving revision 1.93
diff -u -b -r1.93 switch_gen.m
--- compiler/switch_gen.m	17 Mar 2006 01:40:41 -0000	1.93
+++ compiler/switch_gen.m	27 Mar 2006 14:04:15 -0000
@@ -122,13 +122,11 @@
         globals.lookup_int_option(Globals, lookup_switch_req_density,
             ReqDensity),
         is_lookup_switch(CaseVar, TaggedCases, GoalInfo, CanFail, ReqDensity,
-            StoreMap, no, MaybeEndPrime, CodeModel, FirstVal, LastVal,
-            NeedRangeCheck, NeedBitVecCheck, OutVars, CaseVals, MLiveness, !CI)
+            StoreMap, no, MaybeEndPrime, CodeModel, LookupSwitchInfo, !CI)
     ->
         MaybeEnd = MaybeEndPrime,
-        generate_lookup_switch(CaseVar, OutVars, CaseVals, FirstVal, LastVal,
-            NeedRangeCheck, NeedBitVecCheck, MLiveness, StoreMap, no,
-            Code, !CI)
+        generate_lookup_switch(CaseVar, StoreMap, no, LookupSwitchInfo, Code,
+            !CI)
     ;
         Indexing = yes,
         SwitchCategory = atomic_switch,
Index: compiler/unify_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/unify_gen.m,v
retrieving revision 1.163
diff -u -b -r1.163 unify_gen.m
--- compiler/unify_gen.m	27 Mar 2006 09:36:33 -0000	1.163
+++ compiler/unify_gen.m	27 Mar 2006 09:36:07 -0000
@@ -667,8 +667,8 @@
         code_info.add_closure_layout(Data, !CI),
         % For now, closures always have zero size, and the size slot
         % is never looked at.
-        code_info.add_static_cell(ClosureLayoutRvalsTypes, ClosureDataAddr,
-            !CI),
+        code_info.add_scalar_static_cell(ClosureLayoutRvalsTypes,
+            ClosureDataAddr, !CI),
         ClosureLayoutRval = const(data_addr_const(ClosureDataAddr, no)),
         list.length(Args, NumArgs),
         proc_info_arg_info(ProcInfo, ArgInfo),
@@ -812,7 +812,8 @@
 generate_field_take_address_assigns([], _, _, empty, !CI).
 generate_field_take_address_assigns([FieldNum - Var | FieldAddrs],
         CellVar, CellPtag, tree(ThisCode, RestCode), !CI) :-
-    Addr = mem_addr(heap_ref(var(CellVar), CellPtag, FieldNum)),
+    FieldNumRval = const(int_const(FieldNum)),
+    Addr = mem_addr(heap_ref(var(CellVar), CellPtag, FieldNumRval)),
     assign_expr_to_var(Var, Addr, ThisCode, !CI),
     generate_field_take_address_assigns(FieldAddrs, CellVar, CellPtag,
         RestCode, !CI).
Index: compiler/var_locn.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/var_locn.m,v
retrieving revision 1.34
diff -u -b -r1.34 var_locn.m
--- compiler/var_locn.m	17 Mar 2006 01:40:46 -0000	1.34
+++ compiler/var_locn.m	27 Mar 2006 08:55:12 -0000
@@ -706,7 +706,7 @@
             % XXX We could drop the MaybeBaseOffset = no condition,
             % but this would require more complex code below.
             MaybeBaseOffset = no,
-            search_static_cell_offset(StaticCellInfo, DataAddr, Offset,
+            search_scalar_static_cell_offset(StaticCellInfo, DataAddr, Offset,
                 SelectedArgRval)
         ->
             MaybeConstRval = yes(SelectedArgRval),
@@ -819,7 +819,7 @@
     get_var_state_map(!.VLI, VarStateMap),
     get_exprn_opts(!.VLI, ExprnOpts),
     ( cell_is_constant(VarStateMap, ExprnOpts, MaybeRvals, RvalsTypes) ->
-        add_static_cell(RvalsTypes, DataAddr, !StaticCellInfo),
+        add_scalar_static_cell(RvalsTypes, DataAddr, !StaticCellInfo),
         CellPtrConst = const(data_addr_const(DataAddr, MaybeOffset)),
         CellPtrRval = mkword(Ptag, CellPtrConst),
         assign_const_to_var(Var, CellPtrRval, !VLI),
cvs diff: Diffing compiler/notes
cvs diff: Diffing debian
cvs diff: Diffing debian/patches
cvs diff: Diffing deep_profiler
cvs diff: Diffing deep_profiler/notes
cvs diff: Diffing doc
cvs diff: Diffing extras
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/concurrency
cvs diff: Diffing extras/curs
cvs diff: Diffing extras/curs/samples
cvs diff: Diffing extras/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
cvs diff: Diffing extras/error
cvs diff: Diffing extras/gator
cvs diff: Diffing extras/gator/generations
cvs diff: Diffing extras/gator/generations/1
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/easyx
cvs diff: Diffing extras/graphics/easyx/samples
cvs diff: Diffing extras/graphics/mercury_glut
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/gears
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/lex
cvs diff: Diffing extras/lex/samples
cvs diff: Diffing extras/lex/tests
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/moose/tests
cvs diff: Diffing extras/morphine
cvs diff: Diffing extras/morphine/non-regression-tests
cvs diff: Diffing extras/morphine/scripts
cvs diff: Diffing extras/morphine/source
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/quickcheck
cvs diff: Diffing extras/quickcheck/tutes
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/solver_types
cvs diff: Diffing extras/solver_types/library
cvs diff: Diffing extras/stream
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/windows_installer_generator
cvs diff: Diffing extras/windows_installer_generator/sample
cvs diff: Diffing extras/windows_installer_generator/sample/images
cvs diff: Diffing extras/xml
cvs diff: Diffing extras/xml/samples
cvs diff: Diffing extras/xml_stylesheets
cvs diff: Diffing java
cvs diff: Diffing java/runtime
cvs diff: Diffing library
cvs diff: Diffing mdbcomp
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing slice
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
Index: tests/debugger/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/Mmakefile,v
retrieving revision 1.120
diff -u -b -r1.120 Mmakefile
--- tests/debugger/Mmakefile	1 Mar 2006 22:58:47 -0000	1.120
+++ tests/debugger/Mmakefile	27 Mar 2006 02:01:16 -0000
@@ -280,7 +280,7 @@
 	$(MDB_STD) ./poly_io_retry2 < poly_io_retry2.inp \
 		> poly_io_retry2.out 2>&1
 
-# The exception_cmd, exception_vars, polymorphic_output and loopcheck tests
+# The exception_cmd, exception_vars and loopcheck tests
 # are supposed to return a non-zero exit status, since they exit by throwing
 # an exception. We strip the goal paths from their exception events, since
 # the exact goal paths are dependent on optimization level. The stripping
@@ -426,19 +426,8 @@
 		sed 's/io.m:[0-9]*/io.m:NNNN/g' > output_term_dep.out 2>&1
 
 polymorphic_output.out: polymorphic_output polymorphic_output.inp
-	if $(MDB_STD) ./polymorphic_output < polymorphic_output.inp	\
-		> polymorphic_output.tmp 2>&1;			\
-	then							\
-		sed -e '/EXCP/s/).*/)/' < polymorphic_output.tmp\
-			> polymorphic_output.out 2>&1;		\
-		rm polymorphic_output.tmp;			\
-		false;						\
-	else							\
-		sed -e '/EXCP/s/).*/)/' < polymorphic_output.tmp\
-			> polymorphic_output.out 2>&1;		\
-		rm polymorphic_output.tmp;			\
-		true;						\
-	fi
+	$(MDB_STD) ./polymorphic_output < polymorphic_output.inp \
+		> polymorphic_output.out 2>&1;
 
 print_goal.out: print_goal print_goal.inp
 	$(MDB_STD) ./print_goal < print_goal.inp > print_goal.out 2>&1
cvs diff: Diffing tests/debugger/declarative
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: Diffing tests/general/string_format
cvs diff: Diffing tests/general/structure_reuse
cvs diff: Diffing tests/grade_subdirs
cvs diff: Diffing tests/hard_coded
Index: tests/hard_coded/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/hard_coded/Mmakefile,v
retrieving revision 1.281
diff -u -b -r1.281 Mmakefile
--- tests/hard_coded/Mmakefile	21 Mar 2006 22:25:36 -0000	1.281
+++ tests/hard_coded/Mmakefile	28 Mar 2006 03:01:51 -0000
@@ -42,6 +42,9 @@
 	deep_copy_bug \
 	deep_copy_exist \
 	deforest_cc_bug \
+	dense_lookup_switch \
+	dense_lookup_switch2 \
+	dense_lookup_switch3 \
 	det_in_semidet_cntxt \
 	division_test \
 	dos \
Index: tests/hard_coded/dense_lookup_switch2.exp
===================================================================
RCS file: tests/hard_coded/dense_lookup_switch2.exp
diff -N tests/hard_coded/dense_lookup_switch2.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/dense_lookup_switch2.exp	27 Mar 2006 14:55:03 -0000
@@ -0,0 +1,8 @@
+a -> failed
+b -> failed
+c -> failed
+d -> four f1 4.40000000000000
+e -> five f2 5.50000000000000
+f -> six f4("hex") 6.60000000000000
+g -> seven f5(77.7000000000000) 7.70000000000000
+h -> failed
Index: tests/hard_coded/dense_lookup_switch2.m
===================================================================
RCS file: tests/hard_coded/dense_lookup_switch2.m
diff -N tests/hard_coded/dense_lookup_switch2.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/dense_lookup_switch2.m	27 Mar 2006 14:54:26 -0000
@@ -0,0 +1,62 @@
+:- module dense_lookup_switch2.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+:- implementation.
+
+:- type foo
+	--->	a
+	;	b
+	;	c
+	;	d
+	;	e
+	;	f
+	;	g
+	;	h.
+
+:- type bar
+	--->	f1
+	;	f2
+	;	f3(int)
+	;	f4(string)
+	;	f5(float).
+
+main(!IO) :-
+	test(a, !IO),
+	test(b, !IO),
+	test(c, !IO),
+	test(d, !IO),
+	test(e, !IO),
+	test(f, !IO),
+	test(g, !IO),
+	test(h, !IO).
+
+:- pred test(foo::in, io::di, io::uo) is det.
+
+test(Foo, !IO) :-
+	( p(Foo, Str, Bar, Float) ->
+		io.write(Foo, !IO),
+		io.write_string(" -> ", !IO),
+		io.write_string(Str, !IO),
+		io.write_string(" ", !IO),
+		io.write(Bar, !IO),
+		io.write_string(" ", !IO),
+		io.write_float(Float, !IO),
+		io.nl(!IO)
+	;
+		io.write(Foo, !IO),
+		io.write_string(" -> failed", !IO),
+		io.nl(!IO)
+	).
+
+:- pred p(foo::in, string::out, bar::out, float::out) is semidet.
+:- pragma no_inline(p/4).
+
+p(d, "four", f1, 4.4).
+p(e, "five", f2, 5.5).
+p(f, "six", f4("hex"), 6.6).
+p(g, "seven", f5(77.7), 7.7).
Index: tests/hard_coded/dense_lookup_switch3.exp
===================================================================
RCS file: tests/hard_coded/dense_lookup_switch3.exp
diff -N tests/hard_coded/dense_lookup_switch3.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/dense_lookup_switch3.exp	28 Mar 2006 03:01:34 -0000
@@ -0,0 +1,255 @@
+0: no upper no lower
+1: no upper no lower
+2: no upper no lower
+3: no upper no lower
+4: no upper no lower
+5: no upper no lower
+6: no upper no lower
+7: no upper no lower
+8: no upper no lower
+9: no upper no lower
+10: no upper no lower
+11: no upper no lower
+12: no upper no lower
+13: no upper no lower
+14: no upper no lower
+15: no upper no lower
+16: no upper no lower
+17: no upper no lower
+18: no upper no lower
+19: no upper no lower
+20: no upper no lower
+21: no upper no lower
+22: no upper no lower
+23: no upper no lower
+24: no upper no lower
+25: no upper no lower
+26: no upper no lower
+27: no upper no lower
+28: no upper no lower
+29: no upper no lower
+30: no upper no lower
+31: no upper no lower
+32: no upper no lower
+33: no upper no lower
+34: no upper no lower
+35: no upper no lower
+36: no upper no lower
+37: no upper no lower
+38: no upper no lower
+39: no upper no lower
+40: no upper no lower
+41: no upper no lower
+42: no upper no lower
+43: no upper no lower
+44: no upper no lower
+45: no upper no lower
+46: no upper no lower
+47: no upper no lower
+48: no upper no lower
+49: no upper no lower
+50: no upper no lower
+51: no upper no lower
+52: no upper no lower
+53: no upper no lower
+54: no upper no lower
+55: no upper no lower
+56: no upper no lower
+57: no upper no lower
+58: no upper no lower
+59: no upper no lower
+60: no upper no lower
+61: no upper no lower
+62: no upper no lower
+63: no upper no lower
+64: no upper no lower
+65: no upper lower a
+66: no upper lower b
+67: no upper lower c
+68: no upper lower d
+69: no upper lower e
+70: no upper lower f
+71: no upper lower g
+72: no upper lower h
+73: no upper lower i
+74: no upper lower j
+75: no upper lower k
+76: no upper lower l
+77: no upper lower m
+78: no upper lower n
+79: no upper lower o
+80: no upper lower p
+81: no upper lower q
+82: no upper lower r
+83: no upper lower s
+84: no upper lower t
+85: no upper lower u
+86: no upper lower v
+87: no upper lower w
+88: no upper lower x
+89: no upper lower y
+90: no upper lower z
+91: no upper no lower
+92: no upper no lower
+93: no upper no lower
+94: no upper no lower
+95: no upper no lower
+96: no upper no lower
+97: upper A no lower
+98: upper B no lower
+99: upper C no lower
+100: upper D no lower
+101: upper E no lower
+102: upper F no lower
+103: upper G no lower
+104: upper H no lower
+105: upper I no lower
+106: upper J no lower
+107: upper K no lower
+108: upper L no lower
+109: upper M no lower
+110: upper N no lower
+111: upper O no lower
+112: upper P no lower
+113: upper Q no lower
+114: upper R no lower
+115: upper S no lower
+116: upper T no lower
+117: upper U no lower
+118: upper V no lower
+119: upper W no lower
+120: upper X no lower
+121: upper Y no lower
+122: upper Z no lower
+123: no upper no lower
+124: no upper no lower
+125: no upper no lower
+126: no upper no lower
+127: no upper no lower
+128: no upper no lower
+129: no upper no lower
+130: no upper no lower
+131: no upper no lower
+132: no upper no lower
+133: no upper no lower
+134: no upper no lower
+135: no upper no lower
+136: no upper no lower
+137: no upper no lower
+138: no upper no lower
+139: no upper no lower
+140: no upper no lower
+141: no upper no lower
+142: no upper no lower
+143: no upper no lower
+144: no upper no lower
+145: no upper no lower
+146: no upper no lower
+147: no upper no lower
+148: no upper no lower
+149: no upper no lower
+150: no upper no lower
+151: no upper no lower
+152: no upper no lower
+153: no upper no lower
+154: no upper no lower
+155: no upper no lower
+156: no upper no lower
+157: no upper no lower
+158: no upper no lower
+159: no upper no lower
+160: no upper no lower
+161: no upper no lower
+162: no upper no lower
+163: no upper no lower
+164: no upper no lower
+165: no upper no lower
+166: no upper no lower
+167: no upper no lower
+168: no upper no lower
+169: no upper no lower
+170: no upper no lower
+171: no upper no lower
+172: no upper no lower
+173: no upper no lower
+174: no upper no lower
+175: no upper no lower
+176: no upper no lower
+177: no upper no lower
+178: no upper no lower
+179: no upper no lower
+180: no upper no lower
+181: no upper no lower
+182: no upper no lower
+183: no upper no lower
+184: no upper no lower
+185: no upper no lower
+186: no upper no lower
+187: no upper no lower
+188: no upper no lower
+189: no upper no lower
+190: no upper no lower
+191: no upper no lower
+192: no upper no lower
+193: no upper no lower
+194: no upper no lower
+195: no upper no lower
+196: no upper no lower
+197: no upper no lower
+198: no upper no lower
+199: no upper no lower
+200: no upper no lower
+201: no upper no lower
+202: no upper no lower
+203: no upper no lower
+204: no upper no lower
+205: no upper no lower
+206: no upper no lower
+207: no upper no lower
+208: no upper no lower
+209: no upper no lower
+210: no upper no lower
+211: no upper no lower
+212: no upper no lower
+213: no upper no lower
+214: no upper no lower
+215: no upper no lower
+216: no upper no lower
+217: no upper no lower
+218: no upper no lower
+219: no upper no lower
+220: no upper no lower
+221: no upper no lower
+222: no upper no lower
+223: no upper no lower
+224: no upper no lower
+225: no upper no lower
+226: no upper no lower
+227: no upper no lower
+228: no upper no lower
+229: no upper no lower
+230: no upper no lower
+231: no upper no lower
+232: no upper no lower
+233: no upper no lower
+234: no upper no lower
+235: no upper no lower
+236: no upper no lower
+237: no upper no lower
+238: no upper no lower
+239: no upper no lower
+240: no upper no lower
+241: no upper no lower
+242: no upper no lower
+243: no upper no lower
+244: no upper no lower
+245: no upper no lower
+246: no upper no lower
+247: no upper no lower
+248: no upper no lower
+249: no upper no lower
+250: no upper no lower
+251: no upper no lower
+252: no upper no lower
+253: no upper no lower
+254: no upper no lower
Index: tests/hard_coded/dense_lookup_switch3.m
===================================================================
RCS file: tests/hard_coded/dense_lookup_switch3.m
diff -N tests/hard_coded/dense_lookup_switch3.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/dense_lookup_switch3.m	28 Mar 2006 02:49:37 -0000
@@ -0,0 +1,84 @@
+:- module dense_lookup_switch3.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+:- implementation.
+
+:- import_module char.
+:- import_module int.
+
+main(!IO) :-
+	test_all(0, 255, !IO).
+
+:- pred test_all(int::in, int::in, io::di, io::uo) is det.
+
+test_all(Cur, Max, !IO) :-
+	( Cur < Max ->
+		test(Cur, !IO),
+		test_all(Cur + 1, Max, !IO)
+	;
+		true
+	).
+
+:- pred test(int::in, io::di, io::uo) is det.
+
+test(N, !IO) :-
+	io.write_int(N, !IO),
+	NC = char.det_from_int(N),
+	io.write_string(": ", !IO),
+	( local_lower_upper(NC, UC) ->
+		io.write_string("upper ", !IO),
+		io.write_char(UC, !IO)
+	;
+		io.write_string("no upper", !IO)
+	),
+	io.write_string(" ", !IO),
+	( local_lower_upper(LC, NC) ->
+		io.write_string("lower ", !IO),
+		io.write_char(LC, !IO)
+	;
+		io.write_string("no lower", !IO)
+	),
+	io.nl(!IO).
+
+%-----------------------------------------------------------------------------%
+
+    % local_lower_upper(Lower, Upper) is true iff
+    % Lower is a lower-case letter and Upper is the corresponding
+    % upper-case letter.
+    %
+:- pred local_lower_upper(char, char).
+:- mode local_lower_upper(in, out) is semidet.
+:- mode local_lower_upper(out, in) is semidet.
+:- pragma no_inline(local_lower_upper/2).
+
+local_lower_upper('a', 'A').
+local_lower_upper('b', 'B').
+local_lower_upper('c', 'C').
+local_lower_upper('d', 'D').
+local_lower_upper('e', 'E').
+local_lower_upper('f', 'F').
+local_lower_upper('g', 'G').
+local_lower_upper('h', 'H').
+local_lower_upper('i', 'I').
+local_lower_upper('j', 'J').
+local_lower_upper('k', 'K').
+local_lower_upper('l', 'L').
+local_lower_upper('m', 'M').
+local_lower_upper('n', 'N').
+local_lower_upper('o', 'O').
+local_lower_upper('p', 'P').
+local_lower_upper('q', 'Q').
+local_lower_upper('r', 'R').
+local_lower_upper('s', 'S').
+local_lower_upper('t', 'T').
+local_lower_upper('u', 'U').
+local_lower_upper('v', 'V').
+local_lower_upper('w', 'W').
+local_lower_upper('x', 'X').
+local_lower_upper('y', 'Y').
+local_lower_upper('z', 'Z').
cvs diff: Diffing tests/hard_coded/exceptions
cvs diff: Diffing tests/hard_coded/purity
cvs diff: Diffing tests/hard_coded/sub-modules
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
cvs diff: Diffing tests/invalid/purity
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/mmc_make
cvs diff: Diffing tests/mmc_make/lib
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/trailing
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
Index: tools/binary
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/tools/binary,v
retrieving revision 1.25
diff -u -b -r1.25 binary
--- tools/binary	28 Jan 2005 07:12:02 -0000	1.25
+++ tools/binary	28 Mar 2006 13:50:01 -0000
@@ -1,4 +1,7 @@
 #!/bin/sh
+#
+# vim: ts=4 sw=4 et
+#
 # This script finds miscompiled procedures.
 #
 # Given a stage2 directory that works (stage2.ok) and one that doesn't
@@ -32,8 +35,8 @@
 	-d, --dependency-only
 		Make dependencies for stage3 only. Do not compile stage3.
 	-D <dirname>, --dir <dirname>
-		Confine the search to one directory, library or compiler.
-		(Usually useful only after a previous search.)
+        Confine the search to one directory, library, mdbcomp, analysis
+        or compiler. (Usually useful only after a previous search.)
 	-f <modulename>, --file <modulename>
 		Confine the search to the named file(s).
 		(Usually useful only after a previous search.)
@@ -194,45 +197,27 @@
 
 echo "starting at `date`"
 
-if test -f stage2.ok/library/builtin.o
-then
-	echo "stage2.ok/library seems to have its object files"
-else
-	echo "reconstructing object files in stage2.ok/library"
-	cd stage2.ok/library
-	mmake
-	cd $root
-fi
-
-if test -f stage2.bad/library/builtin.o
-then
-	echo "stage2.bad/library seems to have its object files"
-else
-	echo "reconstructing object files in stage2.bad/library"
-	cd stage2.bad/library
-	mmake
-	cd $root
-fi
-
-if test -f stage2.ok/compiler/arg_info.o
-then
-	echo "stage2.ok/compiler seems to have its object files"
-else
-	echo "reconstructing object files in stage2.ok/compiler"
-	cd stage2.ok/compiler
-	mmake
-	cd $root
-fi
+for dir in $base $trial
+do
+    for subdir in library mdbcomp analysis compiler
+    do
+        case $subdir in
+            library)    example_o=builtin.o ;;
+            mdbcomp)    example_o=mdbcomp.prim_data.o ;;
+            analysis)   example_o=analysis.o ;;
+            compiler)   example_o=check_hlds.cse_detection.o ;;
+        esac
 
-if test -f stage2.bad/compiler/arg_info.o
-then
-	echo "stage2.bad/compiler seems to have its object files"
-else
-	echo "reconstructing object files in stage2.bad/compiler"
-	cd stage2.bad/compiler
+        if test -f stage2.$dir/$subdir/$example_o
+        then
+            echo "stage2.$dir/$subdir seems to have its object files"
+        else
+            echo "reconstructing object files in stage2.$dir/$subdir"
+            cd stage2.$dir/$subdir
 	mmake
-	cd $root
-fi
+        fi
+    done
+done
 
 echo "starting binary at `date`"
 
@@ -253,13 +238,38 @@
 ln -s $root/compiler/[t-z]*.m .
 ln -s $root/compiler/*.pp .
 cp $root/compiler/Mmake* .
+cp $root/compiler/Mercury* .
+cp $root/compiler/*FLAGS* .
+cp $root/compiler/.mgnuc* .
 cd $root/stage2
 mkdir library
 cd library
 ln -s $root/library/[a-l]*.m .
 ln -s $root/library/[m-z]*.m .
 ln -s $root/library/*.init .
+cp $root/library/print_extra_inits .
 cp $root/library/Mmake* .
+cp $root/library/Mercury* .
+cp $root/library/*FLAGS* .
+cp $root/library/.mgnuc* .
+cd $root/stage2
+mkdir mdbcomp
+cd mdbcomp
+ln -s $root/mdbcomp/*.m .
+ln -s $root/mdbcomp/*.init .
+cp $root/mdbcomp/Mmake* .
+cp $root/mdbcomp/Mercury* .
+cp $root/mdbcomp/*FLAGS* .
+cp $root/mdbcomp/.mgnuc* .
+cd $root/stage2
+mkdir analysis
+cd analysis
+ln -s $root/analysis/*.m .
+ln -s $root/analysis/*.init .
+cp $root/analysis/Mmake* .
+cp $root/analysis/Mercury* .
+cp $root/analysis/*FLAGS* .
+cp $root/analysis/.mgnuc* .
 cd $root/stage2
 if "$copy_runtime"
 then
@@ -272,19 +282,22 @@
 	cp $root/runtime/Mmake* .
 	cd $root/stage2
 else
-	ln -s $root/runtime .
+    # $root/runtime may be in a different grade from the stage2 directories.
+    ln -s $root/stage2.ok/runtime .
 fi
 ln -s $root/boehm_gc .
 ln -s $root/browser .
-ln -s $root/mdbcomp .
 ln -s $root/trace .
 ln -s $root/doc .
 ln -s $root/scripts .
 ln -s $root/util .
 ln -s $root/profiler .
+ln -s $root/deep_profiler .
+ln -s $root/tools .
 ln -s $root/conf* .
 ln -s $root/aclocal.m4 .
 ln -s $root/VERSION .
+ln -s $root/Mercury.options .
 ln -s $root/.*.in .
 rm -f config*.log
 cp $root/stage2.ok/Mmake* .
@@ -305,7 +318,25 @@
 cp stage2.ok/library/*.optdate stage2/library
 cp stage2.ok/library/*.trans_opt stage2/library
 cp stage2.ok/library/*.trans_opt_date stage2/library
-cp stage2.ok/library/*.h stage2/library
+cp stage2.ok/library/*.mh stage2/library
+# cp stage2.ok/mdbcomp/*.d stage2/mdbcomp
+cp stage2.ok/mdbcomp/*.dep stage2/mdbcomp
+cp stage2.ok/mdbcomp/*.dv stage2/mdbcomp
+cp stage2.ok/mdbcomp/*.int3 stage2/mdbcomp
+cp stage2.ok/mdbcomp/*.date3 stage2/mdbcomp
+cp stage2.ok/mdbcomp/*.int stage2/mdbcomp
+cp stage2.ok/mdbcomp/*.int2 stage2/mdbcomp
+cp stage2.ok/mdbcomp/*.date stage2/mdbcomp
+cp stage2.ok/mdbcomp/*.mh stage2/mdbcomp
+# cp stage2.ok/analysis/*.d stage2/analysis
+cp stage2.ok/analysis/*.dep stage2/analysis
+cp stage2.ok/analysis/*.dv stage2/analysis
+cp stage2.ok/analysis/*.int3 stage2/analysis
+cp stage2.ok/analysis/*.date3 stage2/analysis
+cp stage2.ok/analysis/*.int stage2/analysis
+cp stage2.ok/analysis/*.int2 stage2/analysis
+cp stage2.ok/analysis/*.date stage2/analysis
+cp stage2.ok/analysis/*.mh stage2/analysis
 # cp stage2.ok/compiler/*.d stage2/compiler
 cp stage2.ok/compiler/*.dep stage2/compiler
 cp stage2.ok/compiler/*.dv stage2/compiler
@@ -314,6 +345,7 @@
 cp stage2.ok/compiler/*.int stage2/compiler
 cp stage2.ok/compiler/*.int2 stage2/compiler
 cp stage2.ok/compiler/*.date stage2/compiler
+cp stage2.ok/compiler/*.mh stage2/compiler
 
 if test "$bootcheck" = ""
 then
@@ -337,28 +369,57 @@
 	ln -s $root/compiler/[t-z]*.m .
 	ln -s $root/compiler/*.pp .
 	cp $root/compiler/Mmake* .
+    cp $root/compiler/Mercury* .
+    cp $root/compiler/*FLAGS* .
+    cp $root/compiler/.mgnuc* .
 	cd $root/stage3
 	mkdir library
 	cd library
 	ln -s $root/library/[a-l]*.m .
 	ln -s $root/library/[m-z]*.m .
 	ln -s $root/library/*.init .
+    cp $root/library/Mercury* .
+    cp $root/library/*FLAGS* .
+    cp $root/library/.mgnuc* .
 	cp $root/library/Mmake* .
 	cd $root/stage3
+    mkdir mdbcomp
+    cd mdbcomp
+    ln -s $root/mdbcomp/*.m .
+    ln -s $root/mdbcomp/*.init .
+    cp $root/mdbcomp/Mercury* .
+    cp $root/mdbcomp/*FLAGS* .
+    cp $root/mdbcomp/.mgnuc* .
+    cp $root/mdbcomp/Mmake* .
+    cd $root/stage3
+    mkdir analysis
+    cd analysis
+    ln -s $root/analysis/*.m .
+    ln -s $root/analysis/*.init .
+    cp $root/analysis/Mercury* .
+    cp $root/analysis/*FLAGS* .
+    cp $root/analysis/.mgnuc* .
+    cp $root/analysis/Mmake* .
+    cd $root/stage3
 	ln -s $root/boehm_gc .
+    ln -s $root/browser .
+    ln -s $root/trace .
 	ln -s $root/doc .
 	ln -s $root/scripts .
+    ln -s $root/util .
 	ln -s $root/profiler .
+    ln -s $root/deep_profiler .
 	ln -s $root/runtime .
-	ln -s $root/util .
+    ln -s $root/tools .
 	ln -s $root/conf* .
 	ln -s $root/aclocal.m4 .
 	ln -s $root/VERSION .
+    ln -s $root/Mercury.options .
 	ln -s $root/.*.in .
 	rm -f config*.log
 	/bin/rm -f Mmake*
 	cp $root/stage2.$basis/Mmake* .
-	cp $root/stage2.ok/so_locations .
+    # cp $root/stage2.ok/so_locations .
 	cd $root
 fi
 
@@ -376,36 +437,68 @@
 fi
 
 cp stage2.ok/main.o stage2
+
 if test "$alldirs" = ""
 then
-	echo testing whether the stage2.bad library works
+    echo testing which directory the problem is in
 
-	set +x
-	echo linking stage2/library from stage2.bad/library 1>&2
-	cp stage2.bad/library/*.[co] stage2/library
-	cp stage2.bad/library/*.pic_o stage2/library
-	echo linking stage2/compiler from stage2.ok/compiler 1>&2
-	cp stage2.ok/compiler/*.[co] stage2/compiler
-	set -x
+    /bin/rm .stage2_problem
+    found=false
+    for testsubdir in library mdbcomp analysis compiler
+    do
+        if $found
+        then
+            echo skipping test of $testsubdir
+        else
+            for subdir in library mdbcomp analysis compiler
+            do
+                if test "$subdir" = "$testsubdir"
+                then
+                    echo linking stage2/$subdir from stage2.bad/$subdir 1>&2
+                    cp stage2.bad/$subdir/*.[co] stage2/$subdir
+                    cp stage2.bad/$subdir/*.pic_o stage2/$subdir
+                else
+                    echo linking stage2/$subdir from stage2.ok/$subdir 1>&2
+                    cp stage2.ok/$subdir/*.[co] stage2/$subdir
+                    cp stage2.ok/$subdir/*.pic_o stage2/$subdir
+                fi
+            done
+
+            binary_step $bootcheck $compile_only $compare_to_bad \
+                $dependency_only $library_only $jfactor -m "$mmake_opts" \
+                $outfile $testdirs -s "$single_command"
+            step_status=$?
+
+            if test -f .stage2_problem
+            then
+                echo could not build stage 2 to test
+                exit 1
+            fi
 
 	if "$negative"
 	then
-		if binary_step $bootcheck $compile_only $compare_to_bad $dependency_only $library_only $jfactor -m "$mmake_opts" $outfile $testdirs -s "$single_command"
+                if test "$step_status" == 0
 		then
-			testeddir=library
-		else
-			testeddir=compiler
-		fi
+                    testeddir=$testsubdir
+                    found=true
 		echo "solution seems to be in the $testeddir directory"
+                fi
 	else
-		if binary_step $bootcheck $compile_only $compare_to_bad $dependency_only $library_only $jfactor -m "$mmake_opts" $outfile $testdirs -s "$single_command"
+                if test "$step_status" != 0
 		then
-			testeddir=compiler
-		else
-			testeddir=library
-		fi
+                    testeddir=$testsubdir
+                    found=true
 		echo "problem seems to be in the $testeddir directory"
 	fi
+            fi
+        fi
+    done
+
+    if test "$found" = false
+    then
+        echo "could not find problem"
+        exit 1
+    fi
 else
 	testeddir=$alldirs
 	if test ! -d stage2/$testeddir
Index: tools/binary_step
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/tools/binary_step,v
retrieving revision 1.21
diff -u -b -r1.21 binary_step
--- tools/binary_step	27 Oct 2003 06:00:47 -0000	1.21
+++ tools/binary_step	28 Mar 2006 13:54:49 -0000
@@ -1,4 +1,7 @@
 #!/bin/sh
+#
+# vim: ts=4 sw=4 et
+#
 # Test the stage2 directory to see whether it passes
 # a bootstrap check and/or a check using the tests directory.
 # If stage2 passes, binary_step returns an exit status of 0 (true);
@@ -160,26 +163,38 @@
 set +x
 
 touch stage2/library/*.c
+touch stage2/mdbcomp/*.c
+touch stage2/analysis/*.c
 touch stage2/compiler/*.c
 
 sleep 2
 
 touch stage2/library/*.int3
+touch stage2/mdbcomp/*.int3
+touch stage2/analysis/*.int3
 touch stage2/compiler/*.int3
 
 sleep 2
 
 touch stage2/library/*.date3
+touch stage2/mdbcomp/*.date3
+touch stage2/analysis/*.date3
 touch stage2/compiler/*.date3
 
 touch stage2/library/*.int2
 touch stage2/library/*.int
+touch stage2/mdbcomp/*.int2
+touch stage2/mdbcomp/*.int
+touch stage2/analysis/*.int2
+touch stage2/analysis/*.int
 touch stage2/compiler/*.int2
 touch stage2/compiler/*.int
 
 sleep 2
 
 touch stage2/library/*.date
+touch stage2/mdbcomp/*.date
+touch stage2/analysis/*.date
 touch stage2/compiler/*.date
 
 touch stage2/library/*.opt
@@ -194,11 +209,14 @@
 touch stage2/library/*.trans_opt_date
 touch stage2/library/*.o
 touch stage2/library/*.pic_o
+touch stage2/mdbcomp/*.o
+touch stage2/analysis/*.o
 touch stage2/compiler/*.o
 
 # Rebuild the stage2 library and compiler from the components already there.
 
 /bin/rm -f stage2/library/lib$STD_LIB_NAME.a stage2/library/lib$STD_LIB_NAME.so
+/bin/rm -f stage2/mdbcomp/lib$STD_LIB_NAME.a stage2/library/lib$STD_LIB_NAME.so
 /bin/rm -f stage2/compiler/mercury_compile
 
 set -x
@@ -212,6 +230,24 @@
 	exit 1
 fi
 
+if (cd stage2/mdbcomp ; mmake $mmake_opts $jfactor library)
+then
+    echo "building of stage 2 mdbcomp successful"
+else
+    echo "building of stage 2 mdbcomp not successful"
+    touch .stage2_problem
+    exit 1
+fi
+
+if (cd stage2/analysis ; mmake $mmake_opts $jfactor library)
+then
+    echo "building of stage 2 analysis successful"
+else
+    echo "building of stage 2 analysis not successful"
+    touch .stage2_problem
+    exit 1
+fi
+
 if (cd stage2/compiler ; mmake $mmake_opts $jfactor mercury_compile)
 then
 	echo "building of stage 2 compiler successful"
cvs diff: Diffing trace
cvs diff: Diffing util
cvs diff: Diffing vim
cvs diff: Diffing vim/after
cvs diff: Diffing vim/ftplugin
cvs diff: Diffing vim/syntax
--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list