[m-rev.] diff/for review: static cells in arrays

Zoltan Somogyi zs at cs.mu.OZ.AU
Mon Mar 6 14:45:58 AEDT 2006


For review by anyone if anyone is interested. Otherwise, I'll commit this
in a couple of days.

Zoltan.

Change the way we represent static cells. Instead of generating a separate
global variable for each static cell, generate global variables that are
arrays, each containing all the static cells of the same type. By reducing
the number of symbols requiring relocation, this reduces link times, especially
in debug grades (since those have lots of static cells).

compiler/global_data.m:
	Rewrite the part of this module that handles static cells in line
	with the above.

compiler/llds.m:
	Modify the data structures for representing static cells in line with
	the above.

compiler/llds_out.m:
	Delete all the code for grouping together all the static cells of the
	same type, since it is not needed anymore. Replace with simpler code
	to print out the new arrays of static cells.

	Rename some predicates to eliminate ambiguity.

compiler/opt_debug.m:
	Conform to the change in llds.m.

compiler/rtti_out.m:
	Conform to the change in llds_out.m.

compiler/hlds_pred.m:
	Fix a comment.

runtime/mercury_misc.h:
runtime/mercury_stack_layout.h:
	Create variants of the existing shorthand macros to refer to static
	cells that refer to static cells not by cell number but by a specified
	offset in a specified array.

	Once this change has been bootstrapped on all our machines, the old
	variants can be deleted.

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/global_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/global_data.m,v
retrieving revision 1.13
diff -u -b -r1.13 global_data.m
--- compiler/global_data.m	28 Nov 2005 04:11:41 -0000	1.13
+++ compiler/global_data.m	4 Mar 2006 00:34:57 -0000
@@ -13,7 +13,7 @@
 %
 %-----------------------------------------------------------------------------%
 
-:- module ll_backend__global_data.
+:- module ll_backend.global_data.
 :- interface.
 
 :- import_module hlds.hlds_pred.
@@ -98,6 +98,7 @@
 :- import_module ll_backend.layout.
 :- import_module ll_backend.llds_out.
 
+:- import_module bimap.
 :- import_module counter.
 :- import_module int.
 :- import_module map.
@@ -142,45 +143,45 @@
 wrap_layout_data(LayoutData) = layout_data(LayoutData).
 
 global_data_init(StaticCellInfo, GlobalData) :-
-    map__init(EmptyDataMap),
-    map__init(EmptyLayoutMap),
+    map.init(EmptyDataMap),
+    map.init(EmptyLayoutMap),
     GlobalData = global_data(EmptyDataMap, EmptyLayoutMap, [], StaticCellInfo).
 
 global_data_add_new_proc_var(PredProcId, ProcVar, !GlobalData) :-
     ProcVarMap0 = !.GlobalData ^ proc_var_map,
-    map__det_insert(ProcVarMap0, PredProcId, ProcVar, ProcVarMap),
+    map.det_insert(ProcVarMap0, PredProcId, ProcVar, ProcVarMap),
     !:GlobalData = !.GlobalData ^ proc_var_map := ProcVarMap.
 
 global_data_add_new_proc_layout(PredProcId, ProcLayout, !GlobalData) :-
     ProcLayoutMap0 = !.GlobalData ^ proc_layout_map,
-    map__det_insert(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
+    map.det_insert(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
     !:GlobalData = !.GlobalData ^ proc_layout_map := ProcLayoutMap.
 
 global_data_update_proc_layout(PredProcId, ProcLayout, !GlobalData) :-
     ProcLayoutMap0 = !.GlobalData ^ proc_layout_map,
-    map__det_update(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
+    map.det_update(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
     !:GlobalData = !.GlobalData ^ proc_layout_map := ProcLayoutMap.
 
 global_data_add_new_closure_layouts(NewClosureLayouts, !GlobalData) :-
     ClosureLayouts0 = !.GlobalData ^ closure_layouts,
-    list__append(NewClosureLayouts, ClosureLayouts0, ClosureLayouts),
+    list.append(NewClosureLayouts, ClosureLayouts0, ClosureLayouts),
     !:GlobalData = !.GlobalData ^ closure_layouts := ClosureLayouts.
 
 global_data_maybe_get_proc_layout(GlobalData, PredProcId, ProcLayout) :-
     ProcLayoutMap = GlobalData ^ proc_layout_map,
-    map__search(ProcLayoutMap, PredProcId, ProcLayout).
+    map.search(ProcLayoutMap, PredProcId, ProcLayout).
 
 global_data_get_proc_layout(GlobalData, PredProcId, ProcLayout) :-
     ProcLayoutMap = GlobalData ^ proc_layout_map,
-    map__lookup(ProcLayoutMap, PredProcId, ProcLayout).
+    map.lookup(ProcLayoutMap, PredProcId, ProcLayout).
 
 global_data_get_all_proc_vars(GlobalData, ProcVars) :-
     ProcVarMap = GlobalData ^ proc_var_map,
-    map__values(ProcVarMap, ProcVars).
+    map.values(ProcVarMap, ProcVars).
 
 global_data_get_all_proc_layouts(GlobalData, ProcLayouts) :-
     ProcLayoutMap = GlobalData ^ proc_layout_map,
-    map__values(ProcLayoutMap, ProcLayouts).
+    map.values(ProcLayoutMap, ProcLayouts).
 
 global_data_get_all_closure_layouts(GlobalData, ClosureLayouts) :-
     ClosureLayouts = GlobalData ^ closure_layouts.
@@ -193,14 +194,6 @@
 
 %-----------------------------------------------------------------------------%
 
-:- type cell_type
-    --->    plain_type(list(llds_type))
-    ;       grouped_type(assoc_list(llds_type, int)).
-
-:- type cell_args
-    --->    plain_args(assoc_list(rval, llds_type))
-    ;       grouped_args(list(common_cell_arg_group)).
-
     % 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
@@ -208,31 +201,40 @@
     %
 :- type cell_type_group
     --->    cell_type_group(
-                cell_type_number    :: int,
-                cell_group_members  :: map(list(rval), data_name)
+                cell_counter        :: counter, % next cell number
+                cell_group_members  :: bimap(list(rval), data_name),
+                cell_rev_array      :: list(common_cell_value)
             ).
 
-:- type static_cell_info
-    --->    static_cell_info(
+:- type static_cell_sub_info
+    --->    static_cell_sub_info(
                 module_name         :: module_name, % base file name
                 unbox_float         :: bool,
-                common_data         :: bool,
-                cell_counter        :: counter, % next cell number
+                common_data         :: bool
+            ).
+
+:- type static_cell_info
+    --->    static_cell_info(
+                sub_info            :: static_cell_sub_info,
                 type_counter        :: counter, % next type number
-                cells               :: map(int, common_data),
-                cell_group_map      :: map(cell_type, cell_type_group)
-                                    % map cell argument types and then cell
-                                    % contents to the id of the common cell
+
+                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.
             ).
 
 init_static_cell_info(BaseName, UnboxFloat, CommonData) = Info0 :-
-    map__init(Cells0),
-    map__init(CellMap0),
-    Info0 = static_cell_info(BaseName, UnboxFloat, CommonData,
-        counter__init(0), counter__init(0), Cells0, CellMap0).
+    SubInfo0 = static_cell_sub_info(BaseName, UnboxFloat, CommonData),
+    Info0 = static_cell_info(SubInfo0, counter.init(0), bimap.init, map.init).
 
 add_static_cell_natural_types(Args, DataAddr, !Info) :-
-    list__map(associate_natural_type(!.Info ^ unbox_float), Args, ArgsTypes),
+    list.map(associate_natural_type(!.Info ^ sub_info ^ unbox_float),
+        Args, ArgsTypes),
     add_static_cell(ArgsTypes, DataAddr, !Info).
 
 add_static_cell(ArgsTypes0, DataAddr, !Info) :-
@@ -248,74 +250,74 @@
     compute_cell_type(ArgsTypes, CellType, CellTypeAndValue),
     do_add_static_cell(ArgsTypes, CellType, CellTypeAndValue, DataAddr, !Info).
 
-:- pred do_add_static_cell(assoc_list(rval, llds_type)::in, cell_type::in,
-    cell_args::in, data_addr::out,
+:- pred do_add_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, CellArgs, DataAddr, !Info) :-
-    assoc_list__keys(ArgsTypes, Args),
+do_add_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,
-    ( map__search(CellGroupMap0, CellType, CellGroup0) ->
-        TypeNum = CellGroup0 ^ cell_type_number,
-        CellGroup1 = CellGroup0
+        ( bimap.search(TypeNumMap0, CellType, TypeNumPrime) ->
+            TypeNum = TypeNumPrime,
+            map.lookup(CellGroupMap0, TypeNum, !:CellGroup)
     ;
         TypeNumCounter0 = !.Info ^ type_counter,
-        counter__allocate(TypeNum, TypeNumCounter0, TypeNumCounter),
+            counter.allocate(TypeNum, TypeNumCounter0, TypeNumCounter),
         !:Info = !.Info ^ type_counter := TypeNumCounter,
-        CellGroup1 = cell_type_group(TypeNum, map__init)
+
+            bimap.det_insert(TypeNumMap0, CellType, TypeNum, TypeNumMap),
+            !:Info = !.Info ^ cell_type_num_map := TypeNumMap,
+
+            !:CellGroup = cell_type_group(counter.init(0), bimap.init, [])
     ),
-    MembersMap0 = CellGroup1 ^ cell_group_members,
-    ModuleName = !.Info ^ module_name,
-    ( map__search(MembersMap0, Args, DataNamePrime) ->
+        MembersMap0 = !.CellGroup ^ cell_group_members,
+        ( bimap.search(MembersMap0, Args, DataNamePrime) ->
         DataName = DataNamePrime
     ;
-        CellNumCounter0 = !.Info ^ cell_counter,
-        counter__allocate(CellNum, CellNumCounter0, CellNumCounter),
-        !:Info = !.Info ^ cell_counter := CellNumCounter,
-        DataName = common(CellNum, TypeNum),
+            CellNumCounter0 = !.CellGroup ^ cell_counter,
+            counter.allocate(CellNum, CellNumCounter0, CellNumCounter),
+            !:CellGroup = !.CellGroup ^ cell_counter := CellNumCounter,
+            DataName = common_ref(TypeNum, CellNum),
+            RevArray0 = !.CellGroup ^ cell_rev_array,
+            RevArray = [CellValue | RevArray0],
+            !:CellGroup = !.CellGroup ^ cell_rev_array := RevArray,
+            InsertCommonData = !.Info ^ sub_info ^ common_data,
         (
-            !.Info ^ common_data = yes,
-            map__set(MembersMap0, Args, DataName, MembersMap),
-            CellGroup = CellGroup1 ^ cell_group_members := MembersMap,
-            map__set(CellGroupMap0, CellType, CellGroup, CellGroupMap),
-            !:Info = !.Info ^ cell_group_map := CellGroupMap
+                InsertCommonData = yes,
+                bimap.det_insert(MembersMap0, Args, DataName, MembersMap),
+                !:CellGroup = !.CellGroup ^ cell_group_members := MembersMap
         ;
-            !.Info ^ common_data = no
+                InsertCommonData = no
             % With --no-common-data, we never insert any cell into
             % CellGroupMap, ensuring that it stays empty. This can
             % be useful when comparing the LLDS and MLDS backends.
         ),
-        Cells0 = !.Info ^ cells,
-        (
-            CellArgs = plain_args(PlainArgs),
-            CellTypeAndValue = plain_type_and_value(TypeNum, PlainArgs)
-        ;
-            CellArgs = grouped_args(GroupedArgs),
-            CellTypeAndValue = grouped_type_and_value(TypeNum, GroupedArgs)
-        ),
-        Cell = common_data(ModuleName, CellNum, CellTypeAndValue),
-        map__det_insert(Cells0, CellNum, Cell, Cells),
-        !:Info = !.Info ^ cells := Cells
+            map.set(CellGroupMap0, TypeNum, !.CellGroup, CellGroupMap),
+            !:Info = !.Info ^ cell_group_map := CellGroupMap
+        )
     ),
+    ModuleName = !.Info ^ sub_info ^ module_name,
     DataAddr = data_addr(ModuleName, DataName).
 
-:- pred compute_cell_type(assoc_list(rval, llds_type)::in, cell_type::out,
-    cell_args::out) is det.
+:- pred compute_cell_type(assoc_list(rval, llds_type)::in,
+    common_cell_type::out, common_cell_value::out) is det.
 
-compute_cell_type(ArgsTypes, CellType, CellTypeAndValue) :-
+compute_cell_type(ArgsTypes, CellType, CellValue) :-
     (
         ArgsTypes = [FirstArg - FirstArgType | LaterArgsTypes],
         threshold_group_types(FirstArgType, [FirstArg], LaterArgsTypes,
             TypeGroups, TypeAndArgGroups),
-        OldLength = list__length(ArgsTypes),
-        NewLength = list__length(TypeAndArgGroups),
+        OldLength = list.length(ArgsTypes),
+        NewLength = list.length(TypeAndArgGroups),
         OldLength >= NewLength * 2
     ->
-        CellType = grouped_type(TypeGroups),
-        CellTypeAndValue = grouped_args(TypeAndArgGroups)
+        CellType = grouped_args_type(TypeGroups),
+        CellValue = grouped_args_value(TypeAndArgGroups)
     ;
-        CellType = plain_type(assoc_list__values(ArgsTypes)),
-        CellTypeAndValue = plain_args(ArgsTypes)
+        CellType = plain_type(assoc_list.values(ArgsTypes)),
+        CellValue = plain_value(ArgsTypes)
     ).
 
 :- pred threshold_group_types(llds_type::in, list(rval)::in,
@@ -351,53 +353,42 @@
         TypeGroup = Type - 1,
         TypeAndArgGroup = common_cell_ungrouped_arg(Type, Arg)
     ;
-        list__length(RevArgs, NumArgs),
-        list__reverse(RevArgs, Args),
+        list.length(RevArgs, NumArgs),
+        list.reverse(RevArgs, Args),
         TypeGroup = Type - NumArgs,
         TypeAndArgGroup = common_cell_grouped_args(Type, NumArgs, Args)
     ).
 
 search_static_cell_offset(Info, DataAddr, Offset, Rval) :-
-    DataAddr = data_addr(Info ^ module_name, DataName),
-    DataName = common(CellNum, _),
-    map__search(Info ^ cells, CellNum, CommonData),
-    CommonData = common_data(_, _, TypeAndValue),
-    (
-        TypeAndValue = plain_type_and_value(_, ArgsTypes),
-        list__index0_det(ArgsTypes, Offset, Rval - _)
-    ;
-        TypeAndValue = grouped_type_and_value(_, ArgGroups),
-        offset_into_group(ArgGroups, Offset, Rval)
-    ).
-
-:- pred offset_into_group(list(common_cell_arg_group)::in, int::in, rval::out)
-    is det.
-
-offset_into_group([], _, _) :-
-    unexpected(this_file, "offset_into_group: offset out of bounds").
-offset_into_group([Group | Groups], Offset, Rval) :-
-    (
-        Group = common_cell_grouped_args(_, NumRvalsInGroup, Rvals),
-        ( Offset < NumRvalsInGroup ->
-            list__index0_det(Rvals, Offset, Rval)
-        ;
-            offset_into_group(Groups, Offset - NumRvalsInGroup, Rval)
-        )
-    ;
-        Group = common_cell_ungrouped_arg(_, GroupRval),
-        ( Offset = 0 ->
-            Rval = GroupRval
-        ;
-            offset_into_group(Groups, Offset - 1, 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) =
-    list__map(wrap_common_data, map__values(Info ^ cells)).
+%-----------------------------------------------------------------------------%
 
-:- func wrap_common_data(common_data) = comp_gen_c_data.
+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].
 
-wrap_common_data(CommonData) = common_data(CommonData).
+%-----------------------------------------------------------------------------%
 
 rval_type_as_arg(Rval, ExprnOpts, Type) :-
     natural_type(ExprnOpts ^ unboxed_float, Rval, Type).
@@ -405,7 +396,7 @@
 :- pred natural_type(bool::in, rval::in, llds_type::out) is det.
 
 natural_type(UnboxFloat, Rval, Type) :-
-    llds__rval_type(Rval, Type0),
+    llds.rval_type(Rval, Type0),
     (
         Type0 = float,
         UnboxFloat = no
Index: compiler/hlds_pred.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_pred.m,v
retrieving revision 1.191
diff -u -b -r1.191 hlds_pred.m
--- compiler/hlds_pred.m	24 Feb 2006 05:49:32 -0000	1.191
+++ compiler/hlds_pred.m	3 Mar 2006 02:04:32 -0000
@@ -105,7 +105,7 @@
 
     % Return an invalid predicate or procedure id. These are intended to be
     % used to initialize the relevant fields in in call(...) goals before
-    % we do type- and mode-checks, or when those check find that there was
+    % we do type- and mode-checks, or when those checks find that there was
     % no predicate matching the call.
     %
 :- func invalid_pred_id = pred_id.
Index: compiler/layout_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout_out.m,v
retrieving revision 1.59
diff -u -b -r1.59 layout_out.m
--- compiler/layout_out.m	1 Mar 2006 03:21:19 -0000	1.59
+++ compiler/layout_out.m	5 Mar 2006 04:04:54 -0000
@@ -503,21 +503,23 @@
 
 %-----------------------------------------------------------------------------%
 
-:- type rval_or_num_or_none
+:- type rval_or_numpair_or_none
     --->    rval(rval)
-    ;       num(int)
+    ;       num_pair(int, int)
     ;       none.
 
-:- pred output_rval_or_num_or_none(rval_or_num_or_none::in,
+:- pred output_rval_or_numpair_or_none(rval_or_numpair_or_none::in,
     io::di, io::uo) is det.
 
-output_rval_or_num_or_none(rval(Rval), !IO) :-
+output_rval_or_numpair_or_none(rval(Rval), !IO) :-
     io__write_string(", ", !IO),
     output_rval_as_addr(Rval, !IO).
-output_rval_or_num_or_none(num(Num), !IO) :-
+output_rval_or_numpair_or_none(num_pair(Num1, Num2), !IO) :-
     io__write_string(", ", !IO),
-    io__write_int(Num, !IO).
-output_rval_or_num_or_none(none, !IO).
+    io__write_int(Num1, !IO),
+    io__write_string(", ", !IO),
+    io__write_int(Num2, !IO).
+output_rval_or_numpair_or_none(none, !IO).
 
 :- pred output_label_layout_data_defn(proc_label::in, int::in, layout_name::in,
     maybe(trace_port)::in, maybe(bool)::in, int::in, maybe(int)::in,
@@ -549,24 +551,24 @@
         LabelVars = label_has_var_info,
         (
             LocnsTypes0 = const(data_addr_const(LTDataAddr, no)),
-            LTDataAddr = data_addr(_, common(LTCellNum, _)),
+            LTDataAddr = data_addr(_, common_ref(LTTypeNum, LTCellNum)),
             VarNums0 = const(data_addr_const(VNDataAddr, no)),
-            VNDataAddr = data_addr(_, common(VNCellNum, _))
+            VNDataAddr = data_addr(_, common_ref(VNTypeNum, VNCellNum))
         ->
             (
                 TypeParams0 = const(data_addr_const(TPDataAddr, no)),
-                TPDataAddr = data_addr(_, common(TPCellNum, _))
+                TPDataAddr = data_addr(_, common_ref(TPTypeNum, TPCellNum))
             ->
-                CommonChars = "CCC",
-                LocnsTypes1 = num(LTCellNum),
-                VarNums1 = num(VNCellNum),
-                TypeParams1 = num(TPCellNum)
+                CommonChars = "XCCC",
+                LocnsTypes1 = num_pair(LTTypeNum, LTCellNum),
+                VarNums1 = num_pair(VNTypeNum, VNCellNum),
+                TypeParams1 = num_pair(TPTypeNum, TPCellNum)
             ;
                 TypeParams0 = const(int_const(0))
             ->
-                CommonChars = "CC0",
-                LocnsTypes1 = num(LTCellNum),
-                VarNums1 = num(VNCellNum),
+                CommonChars = "XCC0",
+                LocnsTypes1 = num_pair(LTTypeNum, LTCellNum),
+                VarNums1 = num_pair(VNTypeNum, VNCellNum),
                 TypeParams1 = none
             ;
                 CommonChars = "",
@@ -619,9 +621,9 @@
             LocnsTypes, VarNums, TypeParams}),
         io__write_string(", ", !IO),
         io__write_int(EncodedVarCount, !IO),
-        output_rval_or_num_or_none(LocnsTypes, !IO),
-        output_rval_or_num_or_none(VarNums, !IO),
-        output_rval_or_num_or_none(TypeParams, !IO)
+        output_rval_or_numpair_or_none(LocnsTypes, !IO),
+        output_rval_or_numpair_or_none(VarNums, !IO),
+        output_rval_or_numpair_or_none(TypeParams, !IO)
     ;
         MaybeVarInfoTuple = no
     ),
@@ -637,8 +639,12 @@
     ( 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)) ->
+            output_data_addr(DataAddr, !IO)
+        ;
         io__write_string(" &", !IO),
         output_data_addr(DataAddr, !IO)
+        )
     ;
         io__write_string("\n", !IO),
         output_rval(Rval, !IO)
Index: compiler/llds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds.m,v
retrieving revision 1.325
diff -u -b -r1.325 llds.m
--- compiler/llds.m	24 Feb 2006 01:41:48 -0000	1.325
+++ compiler/llds.m	3 Mar 2006 23:36:29 -0000
@@ -83,6 +83,19 @@
                                     % this variable represents.
             ).
 
+:- type common_cell_type 
+    --->    plain_type(list(llds_type))
+            % The type is a structure with one field for each one
+            % of the cell's arguments.
+    ;       grouped_args_type(assoc_list(llds_type, int)).
+            % The type is a structure with one field for each group
+            % of the cell's arguments, with each group containing
+            % at least two elements of the same llds_type.
+
+:- type common_cell_value
+    --->    plain_value(assoc_list(rval, llds_type))
+    ;       grouped_args_value(list(common_cell_arg_group)).
+
 :- type common_cell_arg_group
     --->    common_cell_grouped_args(
                 llds_type,      % The shared type of the fields in the group.
@@ -100,43 +113,21 @@
                 rval            % The field value.
             ).
 
-:- type common_cell_type_and_value
-    --->    plain_type_and_value(
-                int,            % The id number of the C type of the form
-                                % common_type_N. That type will be a structure
-                                % with one field for each one of the cell's
-                                % arguments.
-                assoc_list(rval, llds_type)
-                                % The arguments of the create, together with
-                                % their types.
-            )
-    ;       grouped_type_and_value(
-                int,            % The id number of the C type of the form
-                                % common_type_N. That type will be a structure
-                                % with one field for each group of the cell's
-                                % arguments, with each group containing
-                                % elements of the same llds_type.
-                list(common_cell_arg_group)
-            ).
-
     % Global data generated by the compiler. Usually readonly, with one
     % exception: data containing code addresses must be initialized.
     %
 :- type comp_gen_c_data
-    --->    common_data(common_data)
+    --->    common_data(common_data_array)
     ;       rtti_data(rtti_data)
     ;       layout_data(layout_data).
 
-:- type common_data
-    --->    common_data(
+:- type common_data_array
+    --->    common_data_array(
                 module_name,    % The basename of this C file.
-                int,            % The id number of the cell.
-                common_cell_type_and_value
-                                % The data_addr referring to this common_data
-                                % will be data_addr(ModuleName, common(CellNum,
-                                % TypeNum)), where TypeNum is the first field
-                                % of either plain_type_and_value or
-                                % grouped_type_and_value.
+                common_cell_type,   % The type of the elements of the array.
+                int,                % The type number.
+                list(common_cell_value)
+                                    % The array elements, starting at offset 0.
             ).
 
 :- type comp_gen_c_module
@@ -862,9 +853,10 @@
     ;       layout_addr(layout_name).
 
 :- type data_name
-    --->    common(int, int)
-            % The first int is the cell number; the second is the
-            % cell type number.
+    --->    common_ref(int, int)
+            % The first int is the type and thus array number, the second
+            % is the offset in the array.
+
     ;       tabling_pointer(proc_label).
             % A variable that contains a pointer that points to the table
             % used to implement memoization, loopcheck or minimal model
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.270
diff -u -b -r1.270 llds_out.m
--- compiler/llds_out.m	24 Feb 2006 01:41:49 -0000	1.270
+++ compiler/llds_out.m	5 Mar 2006 04:05:12 -0000
@@ -40,7 +40,7 @@
 :- pred output_llds(c_file::in, list(complexity_proc_info)::in,
     map(label, data_addr)::in, io::di, io::uo) is det.
 
-    % output_rval_decls(Rval, DeclSet0, DeclSet) outputs the declarations
+    % output_rval_decls(Rval, !DeclSet) outputs the declarations
     % of any static constants, etc. that need to be declared before
     % output_rval(Rval) is called.
     %
@@ -65,11 +65,10 @@
     % any static constants, etc. that need to be declared before
     % output_data_addr(DataAddr) is called.
     %
-:- pred output_data_addr_decls(data_addr::in, string::in, string::in,
-    int::in, int::out, decl_set::in, decl_set::out, io::di, io::uo) is det.
-
 :- pred output_data_addr_decls(data_addr::in, decl_set::in, decl_set::out,
     io::di, io::uo) is det.
+:- pred output_data_addr_decls_format(data_addr::in, string::in, string::in,
+    int::in, int::out, decl_set::in, decl_set::out, io::di, io::uo) is det.
 
 :- pred output_data_addrs_decls(list(data_addr)::in, string::in, string::in,
     int::in, int::out, decl_set::in, decl_set::out, io::di, io::uo) is det.
@@ -134,6 +133,7 @@
 
 :- type decl_id
     --->    common_type(int)
+    ;       common_array(int)
     ;       float_label(string)
     ;       code_addr(code_addr)
     ;       data_addr(data_addr)
@@ -301,18 +301,18 @@
     io__write_string("\n", !IO),
 
     gather_c_file_labels(Modules, Labels),
-    classify_comp_gen_c_data(Datas, multi_map__init, CommonMap,
-        [], CommonDatas0, [], RttiDatas, [], LayoutDatas),
-    multi_map__to_assoc_list(CommonMap, CommonAssocList),
-    list__foldl2(output_common_decl_group, CommonAssocList, !DeclSet, !IO),
+    classify_comp_gen_c_data(Datas,
+        [], CommonDatas0, [], RttiDatas, [], LayoutDatas0),
+    list__reverse(CommonDatas0, CommonDatas),
+    order_layout_datas(LayoutDatas0, LayoutDatas),
+
+    list__foldl2(output_common_data_decl, CommonDatas, !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__reverse(CommonDatas0, CommonDatas),
     list__foldl2(output_common_data_defn, CommonDatas, !DeclSet, !IO),
     list__foldl2(output_rtti_data_defn, RttiDatas, !DeclSet, !IO),
-    order_layout_datas(LayoutDatas, OrderedLayoutDatas),
-    list__foldl2(output_layout_data_defn, OrderedLayoutDatas, !DeclSet, !IO),
+    list__foldl2(output_layout_data_defn, LayoutDatas, !DeclSet, !IO),
 
     list__foldl2(output_comp_gen_c_module(StackLayoutLabels), Modules,
         !DeclSet, !IO),
@@ -795,20 +795,15 @@
     io__write_int(Number, !IO).
 
 :- pred classify_comp_gen_c_data(list(comp_gen_c_data)::in,
-    multi_map(int, common_data)::in,
-    multi_map(int, common_data)::out,
-    list(common_data)::in, list(common_data)::out,
+    list(common_data_array)::in, list(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([], !CommonMap, !CommonList, !RttiList, !LayoutList).
-classify_comp_gen_c_data([Data | Datas], !CommonMap, !CommonList,
-        !RttiList, !LayoutList) :-
+classify_comp_gen_c_data([], !CommonList, !RttiList, !LayoutList).
+classify_comp_gen_c_data([Data | Datas], !CommonList, !RttiList,
+        !LayoutList) :-
     (
         Data = common_data(CommonData),
-        CommonData = common_data(_ModuleName, _CellNum, TypeAndValue),
-        TypeNum = common_cell_get_type_num(TypeAndValue),
-        multi_map__set(!.CommonMap, TypeNum, CommonData, !:CommonMap),
         !:CommonList = [CommonData | !.CommonList]
     ;
         Data = rtti_data(Rtti),
@@ -817,99 +812,7 @@
         Data = layout_data(Layout),
         !:LayoutList = [Layout | !.LayoutList]
     ),
-    classify_comp_gen_c_data(Datas, !CommonMap, !CommonList,
-        !RttiList, !LayoutList).
-
-:- pred output_common_decl_group(pair(int, list(common_data))::in,
-    decl_set::in, decl_set::out, io::di, io::uo) is det.
-
-output_common_decl_group(TypeNum - CommonDatas, !DeclSet, !IO) :-
-    io__write_string("\n", !IO),
-    (
-        CommonDatas = [CommonData | _],
-        CommonData = common_data(_, _, TypeAndValue)
-    ;
-        CommonDatas = [],
-        unexpected(this_file, "output_common_decl_chunk: empty list")
-    ),
-    TypeDeclId = common_type(TypeNum),
-    ( decl_set_is_member(TypeDeclId, !.DeclSet) ->
-        true
-    ;
-        output_const_term_type(TypeAndValue, "", "", 0, _, !IO),
-        io__write_string("\n", !IO),
-        decl_set_insert(TypeDeclId, !DeclSet)
-    ),
-    % There should be a macro MR_DEF_COMMON<n> for every n up to
-    % ChunkSize.
-    ChunkSize = 10,
-    list__chunk(list__reverse(CommonDatas), ChunkSize, CommonDataChunks),
-    list__foldl2(output_common_decl_shorthand_chunk(TypeNum),
-        CommonDataChunks, !DeclSet, !IO).
-
-:- pred output_common_decl_shorthand_chunk(int::in, list(common_data)::in,
-    decl_set::in, decl_set::out, io::di, io::uo) is det.
-
-output_common_decl_shorthand_chunk(TypeNum, CommonDatas, !DeclSet, !IO) :-
-    io__write_string("MR_DEF_COMMON", !IO),
-    io__write_int(list__length(CommonDatas), !IO),
-    io__write_string("(", !IO),
-    io__write_int(TypeNum, !IO),
-    io__write_string(",", !IO),
-    output_common_decl_shorthand_chunk_entries(CommonDatas, !DeclSet, !IO),
-    io__write_string(")\n", !IO).
-
-:- pred output_common_decl_shorthand_chunk_entries(list(common_data)::in,
-    decl_set::in, decl_set::out, io::di, io::uo) is det.
-
-output_common_decl_shorthand_chunk_entries([], !DeclSet, !IO) :-
-    unexpected(this_file,
-        "output_common_decl_shorthand_chunk_entries: empty list").
-output_common_decl_shorthand_chunk_entries([CommonData | CommonDatas],
-        !DeclSet, !IO) :-
-    CommonData = common_data(ModuleName, CellNum, TypeAndValue),
-    TypeNum = common_cell_get_type_num(TypeAndValue),
-    VarName = common(CellNum, TypeNum),
-    VarDeclId = data_addr(data_addr(ModuleName, VarName)),
-    decl_set_insert(VarDeclId, !DeclSet),
-    io__write_int(CellNum, !IO),
-    (
-        CommonDatas = [_ | _],
-        io__write_string(",", !IO),
-        output_common_decl_shorthand_chunk_entries(CommonDatas, !DeclSet, !IO)
-    ;
-        CommonDatas = []
-    ).
-
-:- pred output_common_decl_chunk(int::in, list(common_data)::in,
-    decl_set::in, decl_set::out, io::di, io::uo) is det.
-
-output_common_decl_chunk(TypeNum, CommonDatas, !DeclSet, !IO) :-
-    io__write_string("const struct ", !IO),
-    output_common_cell_type_name(TypeNum, !IO),
-    io__nl(!IO),
-    output_common_decl_chunk_entries(CommonDatas, !DeclSet, !IO).
-
-:- pred output_common_decl_chunk_entries(list(common_data)::in,
-    decl_set::in, decl_set::out, io::di, io::uo) is det.
-
-output_common_decl_chunk_entries([], !DeclSet, !IO) :-
-    unexpected(this_file, "output_common_decl_chunk_entries: empty list").
-output_common_decl_chunk_entries([CommonData | CommonDatas], !DeclSet, !IO) :-
-    CommonData = common_data(ModuleName, CellNum, TypeAndValue),
-    TypeNum = common_cell_get_type_num(TypeAndValue),
-    VarName = common(CellNum, TypeNum),
-    VarDeclId = data_addr(data_addr(ModuleName, VarName)),
-    output_decl_id(VarDeclId, !IO),
-    decl_set_insert(VarDeclId, !DeclSet),
-    (
-        CommonDatas = [_ | _],
-        io__write_string(",\n", !IO),
-        output_common_decl_chunk_entries(CommonDatas, !DeclSet, !IO)
-    ;
-        CommonDatas = [],
-        io__write_string(";\n", !IO)
-    ).
+    classify_comp_gen_c_data(Datas, !CommonList, !RttiList, !LayoutList).
 
     % output_c_data_type_def outputs the given the type definition.
     % This is needed because some compilers need the type definition
@@ -926,30 +829,37 @@
 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::in,
+:- pred output_common_data_decl(common_data_array::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_common_data_decl(common_data(ModuleName, CellNum, TypeAndValue),
-        !DeclSet, !IO) :-
+output_common_data_decl(CommonDataArray, !DeclSet, !IO) :-
+    CommonDataArray = common_data_array(_ModuleName, CellType, TypeNum,
+        _Values),
     io__write_string("\n", !IO),
 
-    % The code for data local to a Mercury module should normally be visible
-    % only within the C file generated for that module. However, if we generate
-    % multiple C files, the code in each C file must be visible to the other
-    % C files for that Mercury module.
-    TypeNum = common_cell_get_type_num(TypeAndValue),
     TypeDeclId = common_type(TypeNum),
     ( decl_set_is_member(TypeDeclId, !.DeclSet) ->
         true
     ;
-        output_const_term_type(TypeAndValue, "", "", 0, _, !IO),
-        io__write_string("\n", !IO),
+        io__write_string("struct ", !IO),
+        output_common_cell_type_name(TypeNum, !IO),
+        io__write_string(" {\n", !IO),
+        (
+            CellType = plain_type(Types),
+            output_cons_arg_types(Types, "\t", 1, !IO)
+        ;
+            CellType = grouped_args_type(ArgGroups),
+            output_cons_arg_group_types(ArgGroups, "\t", 1, !IO)
+        ),
+        io__write_string("};\n", !IO),
         decl_set_insert(TypeDeclId, !DeclSet)
     ),
-    VarName = common(CellNum, TypeNum),
-    VarDeclId = data_addr(data_addr(ModuleName, VarName)),
-    output_const_term_decl_or_defn(TypeAndValue, ModuleName, CellNum,
-        no, no, "", "", 0, _, !IO),
+    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,
@@ -996,21 +906,47 @@
 output_comp_gen_c_data(layout_data(LayoutData), !DeclSet, !IO) :-
     output_layout_data_defn(LayoutData, !DeclSet, !IO).
 
-:- pred output_common_data_defn(common_data::in,
+:- pred output_common_data_defn(common_data_array::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_common_data_defn(common_data(ModuleName, CellNum, TypeAndValue),
-        !DeclSet, !IO) :-
+output_common_data_defn(CommonData, !DeclSet, !IO) :-
+    CommonData = common_data_array(_ModuleName, _CellType, TypeNum, Values),
     io__write_string("\n", !IO),
-    Args = common_cell_get_rvals(TypeAndValue),
+    ArgLists = list.map(common_cell_get_rvals, Values),
+    list.condense(ArgLists, Args),
     output_rvals_decls(Args, !DeclSet, !IO),
 
-    TypeNum = common_cell_get_type_num(TypeAndValue),
-    VarName = common(CellNum, TypeNum),
-    VarDeclId = data_addr(data_addr(ModuleName, VarName)),
-    output_const_term_decl_or_defn(TypeAndValue, ModuleName, CellNum,
-        no, yes, "", "", 0, _, !IO),
-    decl_set_insert(VarDeclId, !DeclSet).
+    % Although the array should have ben declared by now, it is OK if it
+    % hasn't.
+    VarDeclId = 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_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).
+
+:- func common_cell_get_rvals(common_cell_value) = list(rval).
+
+common_cell_get_rvals(Value) = Rvals :-
+    (
+        Value = plain_value(RvalsTypes),
+        assoc_list.keys(RvalsTypes, Rvals)
+    ;
+        Value = grouped_args_value(Groups),
+        RvalLists = list.map(common_group_get_rvals, Groups),
+        list.condense(RvalLists, Rvals)
+    ).
+
+:- func common_group_get_rvals(common_cell_arg_group) = list(rval).
+
+common_group_get_rvals(common_cell_grouped_args(_, _, Rvals)) = Rvals.
+common_group_get_rvals(common_cell_ungrouped_arg(_, Rval)) = [Rval].
 
 :- pred output_user_foreign_code(user_foreign_code::in, io::di, io::uo) is det.
 
@@ -2255,7 +2191,7 @@
 output_pragma_input_rval_decls([Input | Inputs], !DeclSet, !IO) :-
     Input = pragma_c_input(_VarName, _VarType, _IsDummy, _OrigType, Rval,
         _, _),
-    output_rval_decls(Rval, "\t", "\t", 0, _N, !DeclSet, !IO),
+    output_rval_decls_format(Rval, "\t", "\t", 0, _N, !DeclSet, !IO),
     output_pragma_input_rval_decls(Inputs, !DeclSet, !IO).
 
     % Output the input variable assignments at the top of the
@@ -2343,7 +2279,7 @@
 output_pragma_output_lval_decls([], !DeclSet, !IO).
 output_pragma_output_lval_decls([O | Outputs], !DeclSet, !IO) :-
     O = pragma_c_output(Lval, _VarType, _IsDummy, _OrigType, _VarName, _, _),
-    output_lval_decls(Lval, "\t", "\t", 0, _N, !DeclSet, !IO),
+    output_lval_decls_format(Lval, "\t", "\t", 0, _N, !DeclSet, !IO),
     output_pragma_output_lval_decls(Outputs, !DeclSet, !IO).
 
     % Output the output variable assignments at the bottom of the
@@ -2579,9 +2515,9 @@
     ).
 
 output_rval_decls(Lval, !DeclSet, !IO) :-
-    output_rval_decls(Lval, "", "", 0, _, !DeclSet, !IO).
+    output_rval_decls_format(Lval, "", "", 0, _, !DeclSet, !IO).
 
-    % output_rval_decls(Rval, FirstIndent, LaterIndent, N0, N,
+    % output_rval_decls_format(Rval, FirstIndent, LaterIndent, N0, N,
     % !DeclSet) outputs the declarations of any static constants,
     % etc. that need to be declared before output_rval(Rval) is called.
     % FirstIndent is output before the first declaration, while
@@ -2592,22 +2528,25 @@
     % set of symbols we've already declared. That way, we avoid generating
     % the same symbol twice, which would cause an error in the C code.
     %
-:- pred output_rval_decls(rval::in, string::in, string::in, int::in, int::out,
-    decl_set::in, decl_set::out, io::di, io::uo) is det.
+:- pred output_rval_decls_format(rval::in, string::in, string::in,
+    int::in, int::out, decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_rval_decls(lval(Lval), FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
-    output_lval_decls(Lval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_rval_decls(var(_), _, _, _, _, _, _, !IO) :-
-    unexpected(this_file, "output_rval_decls: unexpected var").
-output_rval_decls(mkword(_, Rval), FirstIndent, LaterIndent,
+output_rval_decls_format(lval(Lval), FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO) :-
+    output_lval_decls_format(Lval, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO).
+output_rval_decls_format(var(_), _, _, _, _, _, _, !IO) :-
+    unexpected(this_file, "output_rval_decls_format: unexpected var").
+output_rval_decls_format(mkword(_, Rval), FirstIndent, LaterIndent,
         !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_rval_decls(const(Const), FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
+output_rval_decls_format(const(Const), FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO) :-
     ( Const = code_addr_const(CodeAddress) ->
-        output_code_addr_decls(CodeAddress, FirstIndent, LaterIndent,
+        output_code_addr_decls_format(CodeAddress, FirstIndent, LaterIndent,
             !N, !DeclSet, !IO)
     ; Const = data_addr_const(DataAddr, _) ->
-        output_data_addr_decls(DataAddr, FirstIndent, LaterIndent,
+        output_data_addr_decls_format(DataAddr, FirstIndent, LaterIndent,
             !N, !DeclSet, !IO)
     ; Const = float_const(FloatVal) ->
         %
@@ -2642,13 +2581,15 @@
     ;
         true
     ).
-output_rval_decls(unop(_, Rval), FirstIndent, LaterIndent,
+output_rval_decls_format(unop(_, Rval), FirstIndent, LaterIndent,
         !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_rval_decls(binop(Op, Rval1, Rval2), FirstIndent, LaterIndent,
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
+output_rval_decls_format(binop(Op, Rval1, Rval2), FirstIndent, LaterIndent,
         !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval1, FirstIndent, LaterIndent, !N, !DeclSet, !IO),
-    output_rval_decls(Rval2, FirstIndent, LaterIndent, !N, !DeclSet, !IO),
+    output_rval_decls_format(Rval1, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO),
+    output_rval_decls_format(Rval2, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO),
         %
         % If floats are boxed, and the static ground terms option is enabled,
         % then for each float constant which we might want to box we declare
@@ -2692,33 +2633,36 @@
     ;
         true
     ).
-output_rval_decls(mem_addr(MemRef), FirstIndent, LaterIndent,
+output_rval_decls_format(mem_addr(MemRef), FirstIndent, LaterIndent,
         !N, !DeclSet, !IO) :-
-    output_mem_ref_decls(MemRef, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
+    output_mem_ref_decls_format(MemRef, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO).
 
 :- pred output_rvals_decls(list(rval)::in, decl_set::in, decl_set::out,
     io::di, io::uo) is det.
 
 output_rvals_decls(Rvals, !DeclSet, !IO) :-
-    output_rvals_decls(Rvals, "", "", 0, _, !DeclSet, !IO).
+    output_rvals_decls_format(Rvals, "", "", 0, _, !DeclSet, !IO).
 
-:- pred output_rvals_decls(list(rval)::in, string::in, string::in,
+:- pred output_rvals_decls_format(list(rval)::in, string::in, string::in,
     int::in, int::out, decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_rvals_decls([], _FirstIndent, _LaterIndent, !N, !DeclSet, !IO).
-output_rvals_decls([Rval | Rvals], FirstIndent, LaterIndent,
+output_rvals_decls_format([], _FirstIndent, _LaterIndent, !N, !DeclSet, !IO).
+output_rvals_decls_format([Rval | Rvals], FirstIndent, LaterIndent,
         !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO),
-    output_rvals_decls(Rvals, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO),
+    output_rvals_decls_format(Rvals, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO). 
 
-:- pred output_mem_ref_decls(mem_ref::in, string::in, string::in,
+:- 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(stackvar_ref(_), _, _, !N, !DeclSet, !IO).
-output_mem_ref_decls(framevar_ref(_), _, _, !N, !DeclSet, !IO).
-output_mem_ref_decls(heap_ref(Rval, _, _), FirstIndent, LaterIndent,
+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,
         !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
 
 %-----------------------------------------------------------------------------%
 %
@@ -2782,112 +2726,6 @@
 
 %-----------------------------------------------------------------------------%
 
-:- func common_cell_get_type_num(common_cell_type_and_value) = int.
-
-common_cell_get_type_num(TypeAndValue) = TypeNum :-
-    (
-        TypeAndValue = plain_type_and_value(TypeNum, _)
-    ;
-        TypeAndValue = grouped_type_and_value(TypeNum, _)
-    ).
-
-:- func common_cell_get_rvals(common_cell_type_and_value) = list(rval).
-
-common_cell_get_rvals(TypeAndValue) = Rvals :-
-    (
-        TypeAndValue = plain_type_and_value(_, RvalsTypes),
-        assoc_list__keys(RvalsTypes, Rvals)
-    ;
-        TypeAndValue = grouped_type_and_value(_, Groups),
-        RvalLists = list__map(common_group_get_rvals, Groups),
-        list__condense(RvalLists, Rvals)
-    ).
-
-:- func common_group_get_rvals(common_cell_arg_group) = list(rval).
-
-common_group_get_rvals(common_cell_grouped_args(_, _, Rvals)) = Rvals.
-common_group_get_rvals(common_cell_ungrouped_arg(_, Rval)) = [Rval].
-
-%-----------------------------------------------------------------------------%
-
-    % We output constant terms as follows:
-    %
-    %   struct <prefix>_common_type_<TypeNum> {     // Type
-    %       ...
-    %   };
-    %
-    %   static const <prefix>_common_type_<TypeNum>
-    %       <prefix>_common_<CellNum>;      // Decl
-    %
-    %   static const <prefix>_common_type_<TypeNum>
-    %       <prefix>_common_<CellNum> = {       // Init
-    %       ...
-    %   };
-    %
-    % Unless the term contains code addresses, and we don't have
-    % static code addresses available, in which case we'll have
-    % to initialize them dynamically, so we must omit both `const's above.
-    %
-    % output_const_term_type outputs the first part above. The second
-    % and third parts are output by output_const_term_decl_or_defn.
-    %
-:- pred output_const_term_type(common_cell_type_and_value::in,
-    string::in, string::in, int::in, int::out, io::di, io::uo) is det.
-
-output_const_term_type(TypeAndValue, FirstIndent, LaterIndent, !N, !IO) :-
-    output_indent(FirstIndent, LaterIndent, !.N, !IO),
-    !:N = !.N + 1,
-    io__write_string("struct ", !IO),
-    TypeNum = common_cell_get_type_num(TypeAndValue),
-    output_common_cell_type_name(TypeNum, !IO),
-    io__write_string(" {\n", !IO),
-    (
-        TypeAndValue = plain_type_and_value(_, ArgsTypes),
-        assoc_list__values(ArgsTypes, Types),
-        output_cons_arg_types(Types, "\t", 1, !IO)
-    ;
-        TypeAndValue = grouped_type_and_value(_, ArgGroups),
-        output_cons_arg_group_types(ArgGroups, "\t", 1, !IO)
-    ),
-    io__write_string("};\n", !IO).
-
-:- pred output_const_term_decl_or_defn(common_cell_type_and_value::in,
-    module_name::in, int::in, bool::in, bool::in,
-    string::in, string::in, int::in, int::out, io::di, io::uo) is det.
-
-output_const_term_decl_or_defn(TypeAndValue, ModuleName, CellNum, Exported,
-        IsDefn, FirstIndent, LaterIndent, !N, !IO) :-
-    output_indent(FirstIndent, LaterIndent, !.N, !IO),
-    !:N = !.N + 1,
-    (
-        Exported = yes,
-        io__write_string("const struct ", !IO)
-    ;
-        Exported = no,
-        io__write_string("static const struct ", !IO)
-    ),
-    TypeNum = common_cell_get_type_num(TypeAndValue),
-    output_common_cell_type_name(TypeNum, !IO),
-    io__write_string(" ", !IO),
-    VarDeclId = data_addr(ModuleName, common(CellNum, TypeNum)),
-    output_decl_id(data_addr(VarDeclId), !IO),
-    (
-        IsDefn = no,
-        io__write_string(";\n", !IO)
-    ;
-        IsDefn = yes,
-        io__write_string(" =\n{\n", !IO),
-        (
-            TypeAndValue = plain_type_and_value(_, ArgsTypes),
-            output_cons_args(ArgsTypes, !IO)
-        ;
-            TypeAndValue = grouped_type_and_value(_, ArgGroups),
-            output_cons_arg_groups(ArgGroups, !IO)
-        ),
-        io__write_string(LaterIndent, !IO),
-        io__write_string("};\n", !IO)
-    ).
-
     % Return true if a data structure of the given type will eventually
     % have code addresses filled in inside it. Note that we can't just
     % test the data structure itself, since in the absence of static
@@ -2908,13 +2746,15 @@
 
 % Common structures can include code addresses, but only in grades with
 % static code addresses.
-data_name_may_include_non_static_code_address(common(_, _)) =  no.
+data_name_may_include_non_static_code_address(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_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_data_addr(DataAddr, !IO).
 output_decl_id(code_addr(_CodeAddress), !IO) :-
@@ -2941,26 +2781,25 @@
     io__write_string(";\n", !IO),
     output_cons_arg_types(Types, Indent, ArgNum + 1, !IO).
 
-:- pred output_cons_arg_group_types(list(common_cell_arg_group)::in,
+:- pred output_cons_arg_group_types(assoc_list(llds_type, int)::in,
     string::in, int::in, io::di, io::uo) is det.
 
 output_cons_arg_group_types([], _, _, !IO).
 output_cons_arg_group_types([Group | Groups], Indent, ArgNum, !IO) :-
     io__write_string(Indent, !IO),
-    (
-        Group = common_cell_grouped_args(Type, ArraySize, _),
+    Group = Type - ArraySize,
+    ( ArraySize = 1 ->
         output_llds_type(Type, !IO),
         io__write_string(" f", !IO),
         io__write_int(ArgNum, !IO),
-        io__write_string("[", !IO),
-        io__write_int(ArraySize, !IO),
-        io__write_string("];\n", !IO)
+        io__write_string(";\n", !IO)
     ;
-        Group = common_cell_ungrouped_arg(Type, _),
         output_llds_type(Type, !IO),
         io__write_string(" f", !IO),
         io__write_int(ArgNum, !IO),
-        io__write_string(";\n", !IO)
+        io__write_string("[", !IO),
+        io__write_int(ArraySize, !IO),
+        io__write_string("];\n", !IO)
     ),
     output_cons_arg_group_types(Groups, Indent, ArgNum + 1, !IO).
 
@@ -3023,8 +2862,21 @@
 output_llds_type(code_ptr, !IO) :-
     io__write_string("MR_Code *", !IO).
 
-    % Output the arguments, each on its own line prefixing with Indent,
-    % and with a cast appropriate to its type if necessary.
+:- pred output_common_cell_value(common_cell_value::in, io::di, io::uo) is det.
+
+output_common_cell_value(CellValue, !IO) :-
+    io.write_string("{\n", !IO),
+    (
+        CellValue = plain_value(ArgsTypes),
+        output_cons_args(ArgsTypes, !IO)
+    ;
+        CellValue = grouped_args_value(ArgGroups),
+        output_cons_arg_groups(ArgGroups, !IO)
+    ),
+    io.write_string("},\n", !IO).
+
+    % Output the arguments, each on its own line, and with a cast appropriate
+    % to its type if that is necessary.
     %
 :- pred output_cons_args(assoc_list(rval, llds_type)::in, io::di, io::uo)
     is det.
@@ -3204,47 +3056,58 @@
     io::di, io::uo) is det.
 
 output_lval_decls(Lval, !DeclSet, !IO) :-
-    output_lval_decls(Lval, "", "", 0, _, !DeclSet, !IO).
+    output_lval_decls_format(Lval, "", "", 0, _, !DeclSet, !IO).
 
-:- pred output_lval_decls(lval::in, string::in, string::in, int::in, int::out,
-    decl_set::in, decl_set::out, io::di, io::uo) is det.
+:- pred output_lval_decls_format(lval::in, string::in, string::in,
+    int::in, int::out, decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_lval_decls(field(_, Rval, FieldNum), FirstIndent, LaterIndent,
+output_lval_decls_format(field(_, Rval, FieldNum), FirstIndent, LaterIndent,
         !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO),
-    output_rval_decls(FieldNum, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_lval_decls(reg(_, _), _, _, !N, !DeclSet, !IO).
-output_lval_decls(stackvar(_), _, _, !N, !DeclSet, !IO).
-output_lval_decls(framevar(_), _, _, !N, !DeclSet, !IO).
-output_lval_decls(succip, _, _, !N, !DeclSet, !IO).
-output_lval_decls(maxfr, _, _, !N, !DeclSet, !IO).
-output_lval_decls(curfr, _, _, !N, !DeclSet, !IO).
-output_lval_decls(succfr(Rval), FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_lval_decls(prevfr(Rval), FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_lval_decls(redofr(Rval), FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_lval_decls(redoip(Rval), FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_lval_decls(succip(Rval), FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
-output_lval_decls(hp, _, _, !N, !DeclSet, !IO).
-output_lval_decls(sp, _, _, !N, !DeclSet, !IO).
-output_lval_decls(lvar(_), _, _, !N, !DeclSet, !IO).
-output_lval_decls(temp(_, _), _, _, !N, !DeclSet, !IO).
-output_lval_decls(mem_ref(Rval), FirstIndent, LaterIndent,
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO),
+    output_rval_decls_format(FieldNum, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO).
+output_lval_decls_format(reg(_, _), _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(stackvar(_), _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(framevar(_), _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(succip, _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(maxfr, _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(curfr, _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(succfr(Rval), FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO) :-
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO).
+output_lval_decls_format(prevfr(Rval), FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO) :-
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO).
+output_lval_decls_format(redofr(Rval), FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO) :-
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO).
+output_lval_decls_format(redoip(Rval), FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO) :-
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO).
+output_lval_decls_format(succip(Rval), FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO) :-
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet,
+        !IO).
+output_lval_decls_format(hp, _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(sp, _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(lvar(_), _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(temp(_, _), _, _, !N, !DeclSet, !IO).
+output_lval_decls_format(mem_ref(Rval), FirstIndent, LaterIndent,
         !N, !DeclSet, !IO) :-
-    output_rval_decls(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
+    output_rval_decls_format(Rval, FirstIndent, LaterIndent, !N, !DeclSet, !IO).
 
 output_code_addr_decls(CodeAddress, !DeclSet, !IO) :-
-    output_code_addr_decls(CodeAddress, "", "", 0, _, !DeclSet, !IO).
+    output_code_addr_decls_format(CodeAddress, "", "", 0, _, !DeclSet, !IO).
 
-:- pred output_code_addr_decls(code_addr::in, string::in, string::in,
+:- pred output_code_addr_decls_format(code_addr::in, string::in, string::in,
     int::in, int::out, decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_code_addr_decls(CodeAddress, FirstIndent, LaterIndent, !N, !DeclSet,
-        !IO) :-
+output_code_addr_decls_format(CodeAddress, FirstIndent, LaterIndent, !N,
+        !DeclSet, !IO) :-
     ( decl_set_is_member(code_addr(CodeAddress), !.DeclSet) ->
         true
     ;
@@ -3360,15 +3223,33 @@
 output_label_as_code_addr_decls(internal(_, _), !IO).
 
 output_data_addr_decls(DataAddr, !DeclSet, !IO) :-
-    output_data_addr_decls(DataAddr, "", "", 0, _, !DeclSet, !IO).
+    output_data_addr_decls_format(DataAddr, "", "", 0, _, !DeclSet, !IO).
 
-output_data_addr_decls(DataAddr, FirstIndent, LaterIndent, !N, !DeclSet,
+output_data_addr_decls_format(DataAddr, FirstIndent, LaterIndent, !N, !DeclSet,
         !IO) :-
-    ( decl_set_is_member(data_addr(DataAddr), !.DeclSet) ->
+    ( DataAddr = data_addr(_, common_ref(TypeNum, _CellNum)) ->
+        DeclId = common_array(TypeNum),
+        ( decl_set_is_member(DeclId, !.DeclSet) ->
+            true
+        ;
+            decl_set_insert(DeclId, !DeclSet),
+            output_indent(FirstIndent, LaterIndent, !.N, !IO),
+            !:N = !.N + 1,
+            io__write_string("static ", !IO),
+            output_common_cell_type_name(TypeNum, !IO),
+            io__write_string(" ", !IO),
+            output_common_cell_array_name(TypeNum, !IO),
+            io__write_string("[];\n", !IO)
+        )
+    ;
+        DeclId = data_addr(DataAddr),
+        ( decl_set_is_member(DeclId, !.DeclSet) ->
         true
     ;
-        decl_set_insert(data_addr(DataAddr), !DeclSet),
-        output_data_addr_decls_2(DataAddr, FirstIndent, LaterIndent, !N, !IO)
+            decl_set_insert(DeclId, !DeclSet),
+            output_data_addr_decls_2(DataAddr, FirstIndent, LaterIndent,
+                !N, !IO)
+        )
     ).
 
 :- pred output_data_addr_decls_2(data_addr::in, string::in, string::in,
@@ -3395,7 +3276,7 @@
 output_data_addrs_decls([], _, _, !N, !DeclSet, !IO).
 output_data_addrs_decls([DataAddr | DataAddrs], FirstIndent, LaterIndent, !N,
         !DeclSet, !IO) :-
-    output_data_addr_decls(DataAddr, FirstIndent, LaterIndent, !N,
+    output_data_addr_decls_format(DataAddr, FirstIndent, LaterIndent, !N,
         !DeclSet, !IO),
     output_data_addrs_decls(DataAddrs, FirstIndent, LaterIndent, !N,
         !DeclSet, !IO).
@@ -3447,15 +3328,15 @@
     io__write_string(c_data_const_string(Globals, InclCodeAddr), !IO),
 
     io__write_string("struct ", !IO),
-    output_data_addr(ModuleName, DataVarName, !IO),
+    output_data_addr_2(ModuleName, DataVarName, !IO),
     io__write_string("_struct\n", !IO),
     io__write_string(LaterIndent, !IO),
     io__write_string("\t", !IO),
-    output_data_addr(ModuleName, DataVarName, !IO).
+    output_data_addr_2(ModuleName, DataVarName, !IO).
 
 :- pred data_name_linkage(data_name::in, linkage::out) is det.
 
-data_name_linkage(common(_, _),       static).
+data_name_linkage(common_ref(_, _),   static).
 data_name_linkage(tabling_pointer(_), static).
 
 %-----------------------------------------------------------------------------%
@@ -3903,20 +3784,23 @@
     % Output a data address.
     %
 output_data_addr(data_addr(ModuleName, DataName), !IO) :-
-    output_data_addr(ModuleName, DataName, !IO).
+    output_data_addr_2(ModuleName, DataName, !IO).
 output_data_addr(rtti_addr(RttiId), !IO) :-
     output_rtti_id(RttiId, !IO).
 output_data_addr(layout_addr(LayoutName), !IO) :-
     output_layout_name(LayoutName, !IO).
 
-:- pred output_data_addr(module_name::in, data_name::in, io::di, io::uo)
+:- pred output_data_addr_2(module_name::in, data_name::in, io::di, io::uo)
     is det.
 
-output_data_addr(_ModuleName, VarName, !IO) :-
+output_data_addr_2(_ModuleName, VarName, !IO) :-
     (
-        VarName = common(CellNum, _TypeNum),
-        output_common_prefix(common_prefix_var, !IO),
-        io__write_int(CellNum, !IO)
+        VarName = common_ref(TypeNum, CellNum),
+        io__write_string("&", !IO),
+        output_common_cell_array_name(TypeNum, !IO),
+        io__write_string("[", !IO),
+        io__write_int(CellNum, !IO),
+        io__write_string("]", !IO)
     ;
         VarName = tabling_pointer(ProcLabel),
         output_tabling_pointer_var_name(ProcLabel, !IO)
@@ -3928,6 +3812,12 @@
     output_common_prefix(common_prefix_type, !IO),
     io__write_int(TypeNum, !IO).
 
+:- pred output_common_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),
+    io__write_int(TypeNum, !IO).
+
 :- type common_prefix
     --->    common_prefix_var
     ;       common_prefix_type.
@@ -4469,11 +4359,13 @@
     (
         Exprn = const(data_addr_const(DataAddr, no)),
         DataAddr = data_addr(_, DataName),
-        DataName = common(CellNum, _TypeNum)
+        DataName = common_ref(TypeNum, CellNum)
     ->
-        io__write_string("MR_TAG_COMMON(", !IO),
+        io__write_string("MR_TAG_XCOMMON(", !IO),
         io__write_int(Tag, !IO),
         io__write_string(",", !IO),
+        io__write_int(TypeNum, !IO),
+        io__write_string(",", !IO),
         io__write_int(CellNum, !IO),
         io__write_string(")", !IO)
     ;
@@ -4593,9 +4485,11 @@
         % file size difference can be very substantial.
         (
             DataAddr = data_addr(_, DataName),
-            DataName = common(CellNum, _TypeNum)
+            DataName = common_ref(TypeNum, CellNum)
         ->
-            io__write_string("MR_COMMON(", !IO),
+            io__write_string("MR_XCOMMON(", !IO),
+            io__write_int(TypeNum, !IO),
+            io__write_string(",", !IO),
             io__write_int(CellNum, !IO),
             io__write_string(")", !IO)
         ;
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.161
diff -u -b -r1.161 opt_debug.m
--- compiler/opt_debug.m	24 Feb 2006 07:11:12 -0000	1.161
+++ compiler/opt_debug.m	3 Mar 2006 23:42:39 -0000
@@ -342,9 +342,9 @@
 dump_data_addr(layout_addr(LayoutName)) =
     "layout_addr(" ++ dump_layout_name(LayoutName) ++ ")".
 
-dump_data_name(common(CellNum, TypeNum)) =
-    "common(" ++ int_to_string(CellNum) ++ ", "
-        ++ int_to_string(TypeNum) ++ ")".
+dump_data_name(common_ref(TypeNum, Offset)) =
+    "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.61
diff -u -b -r1.61 rtti_out.m
--- compiler/rtti_out.m	24 Feb 2006 07:11:14 -0000	1.61
+++ compiler/rtti_out.m	4 Mar 2006 02:15:03 -0000
@@ -1581,7 +1581,7 @@
     io::di, io::uo) is det.
 
 output_rtti_id_decls(RttiId, FirstIndent, LaterIndent, !N, !DeclSet, !IO) :-
-    output_data_addr_decls(rtti_addr(RttiId), FirstIndent, LaterIndent,
+    output_data_addr_decls_format(rtti_addr(RttiId), FirstIndent, LaterIndent,
         !N, !DeclSet, !IO).
 
 :- pred output_cast_addr_of_rtti_ids(string::in, list(rtti_id)::in,
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/aditi
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
Index: runtime/mercury_misc.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_misc.h,v
retrieving revision 1.25
diff -u -b -r1.25 mercury_misc.h
--- runtime/mercury_misc.h	14 Apr 2004 01:31:56 -0000	1.25
+++ runtime/mercury_misc.h	4 Mar 2006 03:00:21 -0000
@@ -57,8 +57,14 @@
 #define	MR_COMMON(cellnum)					\
 	((MR_Word *) &MR_COMMON_NAME(cellnum))
 
+#define	MR_XCOMMON(typenum, cellnum)				\
+	((MR_Word *) &MR_COMMON_NAME(typenum)[cellnum])
+
 #define	MR_TAG_COMMON(tag, cellnum)				\
 	(MR_mkword(MR_mktag(tag), MR_COMMON(cellnum)))
+
+#define	MR_TAG_XCOMMON(tag, typenum, cellnum)			\
+	(MR_mkword(MR_mktag(tag), MR_XCOMMON(typenum, cellnum)))
 
 #define	MR_DEF_COMMON1(typenum,c1)				\
 	static const struct MR_COMMON_TYPE(typenum)		\
Index: runtime/mercury_stack_layout.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_stack_layout.h,v
retrieving revision 1.96
diff -u -b -r1.96 mercury_stack_layout.h
--- runtime/mercury_stack_layout.h	2 Nov 2005 14:02:10 -0000	1.96
+++ runtime/mercury_stack_layout.h	4 Mar 2006 01:42:30 -0000
@@ -460,21 +460,43 @@
 		&MR_PASTE2(mercury_common_, vn),			\
 		&MR_PASTE2(mercury_common_, tv))
 
+#define	MR_DEF_LLXCCC(e, ln, port, num, path, vc, ltt, ltc, vnt, vnc, tvt, tvc)\
+	MR_DEF_LL_GEN(e, ln, port, MR_FALSE, num, path, vc,		\
+		MR_XCOMMON(ltt, ltc),					\
+		MR_XCOMMON(vnt, vnc),					\
+		MR_XCOMMON(tvt, tvc))
+
 #define	MR_DEF_LLCC0(e, ln, port, num, path, vc, lt, vn)		\
 	MR_DEF_LL_GEN(e, ln, port, MR_FALSE, num, path, vc,		\
 		&MR_PASTE2(mercury_common_, lt),			\
 		&MR_PASTE2(mercury_common_, vn), 0)			\
 
+#define	MR_DEF_LLXCC0(e, ln, port, num, path, vc, ltt, ltc, vnt, vnc)	\
+	MR_DEF_LL_GEN(e, ln, port, MR_FALSE, num, path, vc,		\
+		MR_XCOMMON(ltt, ltc),					\
+		MR_XCOMMON(vnt, vnc), 0)
+
 #define	MR_DEF_LLTCCC(e, ln, port, num, path, vc, lt, vn, tv)		\
 	MR_DEF_LL_GEN(e, ln, port, MR_TRUE, num, path, vc,		\
 		&MR_PASTE2(mercury_common_, lt),			\
 		&MR_PASTE2(mercury_common_, vn),			\
 		&MR_PASTE2(mercury_common_, tv))
 
+#define	MR_DEF_LLTXCCC(e, ln, port, num, path, vc, ltt, ltc, vnt, vnc, tvt,tvc)\
+	MR_DEF_LL_GEN(e, ln, port, MR_TRUE, num, path, vc,		\
+		MR_XCOMMON(ltt, ltc),					\
+		MR_XCOMMON(vnt, vnc),					\
+		MR_XCOMMON(tvt, tvc))
+
 #define	MR_DEF_LLTCC0(e, ln, port, num, path, vc, lt, vn)		\
 	MR_DEF_LL_GEN(e, ln, port, MR_TRUE, num, path, vc,		\
 		&MR_PASTE2(mercury_common_, lt),			\
 		&MR_PASTE2(mercury_common_, vn), 0)
+
+#define	MR_DEF_LLTXCC0(e, ln, port, num, path, vc, ltt, ltc, vnt, vnc)	\
+	MR_DEF_LL_GEN(e, ln, port, MR_TRUE, num, path, vc,		\
+		MR_XCOMMON(ltt, ltc),					\
+		MR_XCOMMON(vnt, vnc), 0)
 
 #define	MR_DEF_LLNVI(e, ln, port, num, path)				\
 	MR_DEF_LLNVI_GEN(e, ln, port, MR_FALSE, path)
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
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
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
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