[m-rev.] for review: factoring out the types of common static cells

Zoltan Somogyi zs at cs.mu.OZ.AU
Thu May 1 02:56:35 AEST 2003


On 01-May-2003, Zoltan Somogyi <zs at cs.mu.OZ.AU> wrote:
> A simple way to provide that is to make --no-common-data make sure that
> searches that check whether a cell with the given contents has been seen
> before always fail. I will provide an updated diff using this scheme shortly.

Here is the updated log entry and diff. It is being bootchecked now.

Zoltan.

The objective of this change is to reduce the sizes of object files created
by gcc -v with gcc versions using DWARF as the debugging info format (such
as gcc 3.2 on aral), especially when Mercury debugging is enabled also.
Prior to this change, those sizes were unnecessarily high, which lead to
(a) huge executables, sometimes more than 400 Mb, (b) huge linking times
being required to create those executables, sometimes as long as 12 hours,
and (c) huge startup times in gdb (many minutes) for reading in the symbol
tables in those huge executables.

One big reason for large object files is that DWARF, unlike stabs, uses
a text-based, relatively wasteful format for recording information about
structure types. We currently generate lots of those types, effectively
one type for every static cell. There are many such terms, especially
in debugging grades. This diff therefore changing things so that two static
cells whose arguments have the same type use the same C type. Instead of e.g.

static const struct mercury_data_io__common_5_struct {
	MR_Word * f1;
	MR_Integer f2;
}  mercury_data_io__common_5;

static const struct mercury_data_io__common_6_struct {
	MR_Word * f1;
	MR_Integer f2;
}  mercury_data_io__common_6;

we now generate code such as

struct mercury_data_io__common_type_5 {
	MR_Word * f1;
	MR_Integer f2;
};

static const struct mercury_data_io__common_type_5 mercury_data_io__common_5;
static const struct mercury_data_io__common_type_5 mercury_data_io__common_6;

In debugging grades, this can reduce the number of structure types defined
in a module by more than 90%. In non-debugging grades, the reduction is
typically much smaller, such as 10-20%.

Figuring out which common cells have the same type arguments required
finding out what type those arguments are in llds_common, not in llds_out.
The diff therefore moves that functionality from llds_out to llds_common.
In order to avoid having to leave a copy of that code in llds_out,
llds_common now has the task of converting *all* create rvals in the
generated LLDS to references to common structures. This also ensures
that we get the maximum possible benefit from the factorization of
structure types.

compiler/llds.m:
	Change the representation of compiler-generated C data to
	hold only the information we need about common static memory cells.
	While long ago we used comp_gen_c_datas for other purposes
	as well as common static cells, we have not done so since
	the rti and layout modules were added to the compiler.

	Change the rtti name referring to common static cells to record
	not just the cell number but also the cell type number. This would
	allow us to declare the common structure variable given only the
	rtti_name. At the moment, we don't need this capability, since
	each common cell structures is defined (and hence also declared)
	before any references to that structure, either in other cells
	or in code, but we may need it in the future.

	Delete some unused predicates and some unused alternatives
	in types.

compiler/llds_common.m:
	Materialize the types of common static cell arguments, and use them to
	detect when different cells can share the same structure type.

	Create the list of static data structures as we go along, not in
	a post-processing step.

	Check all parts of the generated LLDS for create rvals, not just
	the parts that look likely to hold create rvals that can benefit
	from sharing values (because even if they can't benefit from from
	sharing values, they may benefit from sharing types).

library/set.m:
	Add a utility predicate needed by llds_common.

compiler/llds_out.m:
	Conform to the changes to the llds.m.

	Delete the code whose functionality was moved to llds_common.

	Throw an exception if a create rval remains in the LLDS, since
	outputing it as a constant would require the code we moved
	to llds_common.

	Switch to state variable syntax in the affected predicates.

	Change some predicate nams to avoid giving misleading impressions
	about those predicates' semantics, and clarify their documentation.

compiler/stack_layout.m:
	Return one list of layout structures, not two.

compiler/mercury_compile.m:
	Put all the static structures created by stack_layout.m through
	llds_common.m, not just a subset, to avoid that exception for remaining
	create rvals. The old distinction between static layout structures
	and possibly dynamic layout structures (which are dynamic because
	they contain code addresses that have to be initialized in grades
	without static code addresses) hasn't been relevant to llds_common
	ever since we added layout.m, because the code addresses are all
	the structures defined in layout.m, not in create rvals.

	Always call llds_common, since llds_out can no longer handle the create
	rvals it eliminates.

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/llds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds.m,v
retrieving revision 1.291
diff -u -b -r1.291 llds.m
--- compiler/llds.m	18 Mar 2003 02:43:37 -0000	1.291
+++ compiler/llds.m	30 Apr 2003 10:51:48 -0000
@@ -21,7 +21,8 @@
 :- import_module backend_libs__foreign.
 :- import_module backend_libs__proc_label.
 :- import_module backend_libs__rtti.
-:- import_module hlds__hlds_goal, hlds__hlds_data.
+:- import_module hlds__hlds_data.
+:- import_module hlds__hlds_goal.
 :- import_module hlds__hlds_pred.
 :- import_module libs__tree.
 :- import_module ll_backend__layout.
@@ -66,9 +67,6 @@
 :- pred global_data_add_new_closure_layouts(global_data::in,
 	list(comp_gen_c_data)::in, global_data::out) is det.
 
-:- pred global_data_add_new_non_common_static_datas(global_data::in,
-	list(comp_gen_c_data)::in, global_data::out) is det.
-
 :- pred global_data_maybe_get_proc_layout(global_data::in, pred_proc_id::in,
 	proc_layout_info::out) is semidet.
 
@@ -116,21 +114,18 @@
 	% with one exception: data containing code addresses must
 	% be initialized.
 :- type comp_gen_c_data
-	--->	comp_gen_c_data(
+	--->	common_data(
 			module_name,		% The basename of this C file.
-			data_name,		% A representation of the name
-						% of the variable; it will be
-						% qualified with the basename.
-			bool,			% Should this item be exported
-						% from this Mercury module?
-						% XXX Actually this field is
-						% redundant; see linkage/2
-						% in llds_out.m.
-			list(maybe(rval)),	% The arguments of the create.
-			create_arg_types,	% May specify the types of the
-						% arguments of the create.
-			list(pred_proc_id)	% The procedures referenced.
-						% Used by dead_proc_elim.
+			int,			% The id number of the cell.
+			int,			% The id number of the C type
+						% giving the types of the args.
+						% The data_addr referring to
+						% this common_data will be
+						% data_addr(ModuleName,
+						% common(CellNum, TypeNum)).
+			assoc_list(rval, llds_type)
+						% The arguments of the create,
+						% together with their types.
 		)
 	;	rtti_data(
 			rtti_data
@@ -884,16 +879,16 @@
 	;	layout_addr(layout_name).
 
 :- type data_name
-	--->	common(int)
+	--->	common(int, int)
+			% The first int is the cell number; the second is the
+			% cell type number.
 	;	base_typeclass_info(class_id, string)
 			% class name & class arity, names and arities of the
 			% types
-	;	tabling_pointer(proc_label)
+	;	tabling_pointer(proc_label).
 			% A variable that contains a pointer that points to
 			% the table used to implement memoization, loopcheck
 			% or minimal model semantics for the given procedure.
-	;	deep_profiling_procedure_data(proc_label)
-	.
 
 :- type reg_type	
 	--->	r		% general-purpose (integer) regs
@@ -1262,12 +1257,6 @@
 	ClosureLayouts0 = GlobalData0 ^ closure_layouts,
 	list__append(NewClosureLayouts, ClosureLayouts0, ClosureLayouts),
 	GlobalData = GlobalData0 ^ closure_layouts := ClosureLayouts.
-
-global_data_add_new_non_common_static_datas(GlobalData0, NewNonCommonStatics,
-		GlobalData) :-
-	NonCommonStatics0 = GlobalData0 ^ non_common_data,
-	list__append(NewNonCommonStatics, NonCommonStatics0, NonCommonStatics),
-	GlobalData = GlobalData0 ^ non_common_data := NonCommonStatics.
 
 global_data_maybe_get_proc_layout(GlobalData, PredProcId, ProcLayout) :-
 	ProcLayoutMap = GlobalData ^ proc_layout_map,
Index: compiler/llds_common.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds_common.m,v
retrieving revision 1.47
diff -u -b -r1.47 llds_common.m
--- compiler/llds_common.m	15 Mar 2003 03:08:55 -0000	1.47
+++ compiler/llds_common.m	30 Apr 2003 16:55:26 -0000
@@ -23,11 +23,13 @@
 :- import_module ll_backend__llds.
 :- import_module parse_tree__prog_data. % for module_name
 
+:- import_module bool.
+
 :- import_module list.
 
-:- pred llds_common(list(c_procedure)::in, list(comp_gen_c_data)::in,
-	module_name::in, list(c_procedure)::out, list(comp_gen_c_data)::out)
-	is det.
+:- pred llds_common(module_name::in, bool::in, bool::in,
+	list(c_procedure)::in, list(c_procedure)::out,
+	list(comp_gen_c_data)::in, list(comp_gen_c_data)::out) is det.
 
 :- implementation.
 
@@ -35,86 +37,179 @@
 :- import_module ll_backend__layout.
 :- import_module ll_backend__llds_out.
 
-:- import_module bool, int, assoc_list, map, std_util, require.
+:- import_module bool, int, assoc_list, counter, set, map, std_util, require.
 
-:- type cell_info
-	--->	cell_info(
-			int		% what is the number of the cell?
+:- type cell_type_group
+	--->	cell_type_group(
+			% cell_arg_types		:: list(llds_type)
+			cell_type_number 	:: int,
+			cell_group_members	:: map(list(rval), data_name)
 		).
 
-:- type cell_content	==	pair(list(maybe(rval)), create_arg_types).
-:- type cell_map	==	map(cell_content, cell_info).
-:- type cell_list	==	assoc_list(cell_content, cell_info).
-
 :- type common_info
 	--->	common_info(
-			module_name,	% base file name
-			int,		% next cell number
-			cell_map
-					% map cell contents (including types)
-					% to cell declaration information
+			module_name	:: module_name,	% base file name
+			unbox_float	:: bool,
+			common_data	:: bool,
+			cell_counter	:: counter,	% next cell number
+			type_counter	:: counter,	% next type number
+			cells		:: list(comp_gen_c_data),
+			cell_group_map	:: map(list(llds_type),
+						cell_type_group)
+					% map cell argument types and then cell
+					% contents to the id of the common cell
 		).
 
-llds_common(Procedures0, Data0, BaseName, Procedures, Data) :-
+llds_common(BaseName, UnboxFloat, CommonData, Procedures0, Procedures,
+		Data0, Data) :-
 	map__init(CellMap0),
-	Info0 = common_info(BaseName, 0, CellMap0),
+	Info0 = common_info(BaseName, UnboxFloat, CommonData,
+		counter__init(0), counter__init(0), [], CellMap0),
 	llds_common__process_procs(Procedures0, Procedures, Info0, Info1),
 	llds_common__process_datas(Data0, Data1, Info1, Info),
-	Info = common_info(_, _, CellMap),
-	map__to_assoc_list(CellMap, CellPairs0),
-	list__sort(lambda([CellPairA::in, CellPairB::in, Compare::out] is det, 
-		(
-			CellPairA = _ - cell_info(ANum),
-			CellPairB = _ - cell_info(BNum),
-			compare(Compare, ANum, BNum)
-		)), CellPairs0, CellPairs),
-	llds_common__cell_pairs_to_modules(CellPairs, BaseName, CommonData),
-	list__append(CommonData, Data1, Data).
-
-:- pred llds_common__cell_pairs_to_modules(cell_list::in, module_name::in,
-	list(comp_gen_c_data)::out) is det.
-
-llds_common__cell_pairs_to_modules([], _, []).
-llds_common__cell_pairs_to_modules([CellContent - CellInfo | CellPairs],
-		BaseName, [Common | Commons]) :-
-	CellInfo = cell_info(VarNum),
-	CellContent = Args0 - ArgTypes0,
-		
-		% If we have an empty data structure place a dummy field
-		% in it, so that the generated C structure isn't empty.
-	( Args0 = [] ->
-		Args = [yes(const(int_const(-1)))],
-		ArgTypes = uniform(yes(integer))
+	RevCommonCells = Info ^ cells,
+	list__reverse(RevCommonCells, CommonCells),
+	list__append(CommonCells, Data1, Data).
+
+:- pred llds_common__process_create(tag::in, list(maybe(rval))::in,
+	create_arg_types::in, rval::out, common_info::in, common_info::out)
+	is det.
+
+llds_common__process_create(Tag, MaybeArgs0, ArgTypes0, Rval, !Info) :-
+	list__map_foldl(llds_common__process_convert_maybe_rval,
+		MaybeArgs0, Args1, !Info),
+		% If we have an empty cell, place a dummy field in it,
+		% so that the generated C structure isn't empty.
+	( Args1 = [] ->
+		Args2 = [const(int_const(-1))],
+		ArgTypes2 = uniform(yes(integer))
 	;
-		Args = Args0,
-		ArgTypes = ArgTypes0
+		Args2 = Args1,
+		ArgTypes2 = ArgTypes0
+	),
+	flatten_arg_types(Args2, ArgTypes2, !.Info ^ unbox_float, TypedArgs),
+	assoc_list__keys(TypedArgs, Args),
+	assoc_list__values(TypedArgs, Types),
+	CellGroupMap0 = !.Info ^ cell_group_map,
+	( map__search(CellGroupMap0, Types, CellGroup0) ->
+		TypeNum = CellGroup0 ^ cell_type_number,
+		CellGroup1 = CellGroup0
+	;
+		TypeNumCounter0 = !.Info ^ type_counter,
+		counter__allocate(TypeNum, TypeNumCounter0, TypeNumCounter),
+		!:Info = !.Info ^ type_counter := TypeNumCounter,
+		CellGroup1 = cell_type_group(TypeNum, map__init)
 	),
+	MembersMap0 = CellGroup1 ^ cell_group_members,
+	ModuleName = !.Info ^ module_name,
+	(
+		map__search(MembersMap0, Args, DataNamePrime),
+		% With --no-common-data, deliberately sabotage the search
+		% for DataName in order to ensure that we generate one static
+		% structure for reach create rval. This can be useful when
+		% comparing the LLDS and MLDS backends.
+		!.Info ^ common_data = yes
+	->
+		DataName = DataNamePrime
+	;
+		CellNumCounter0 = !.Info ^ cell_counter,
+		counter__allocate(CellNum, CellNumCounter0, CellNumCounter),
+		!:Info = !.Info ^ cell_counter := CellNumCounter,
+
+		DataName = common(CellNum, TypeNum),
+		map__det_insert(MembersMap0, Args, DataName, MembersMap),
+		CellGroup = CellGroup1 ^ cell_group_members := MembersMap,
+		map__set(CellGroupMap0, Types, CellGroup, CellGroupMap),
+		!:Info = !.Info ^ cell_group_map := CellGroupMap,
+
+		Cells0 = !.Info ^ cells,
+		Cell = common_data(ModuleName, CellNum, TypeNum, TypedArgs),
+		Cells = [Cell | Cells0],
+		!:Info = !.Info ^ cells := Cells
+	),
+	DataConst = data_addr_const(data_addr(ModuleName, DataName)),
+	Rval = mkword(Tag, const(DataConst)).
 
-	Common = comp_gen_c_data(BaseName, common(VarNum), no,
-		Args, ArgTypes, []),
-	llds_common__cell_pairs_to_modules(CellPairs, BaseName, Commons).
+%-----------------------------------------------------------------------------%
 
-:- pred llds_common__process_create(tag::in, list(maybe(rval))::in,
-	create_arg_types::in, rval::out, common_info::in, common_info::out)
+:- pred flatten_arg_types(list(rval)::in, create_arg_types::in,
+	bool::in, assoc_list(rval, llds_type)::out) is det.
+
+flatten_arg_types(Args, uniform(MaybeType), UnboxFloat, TypedRvals) :-
+	flatten_uniform_arg_types(Args, MaybeType, UnboxFloat, TypedRvals).
+flatten_arg_types(Args, initial(InitialTypes, RestTypes), UnboxFloat,
+		TypedRvals) :-
+	flatten_initial_arg_types(Args, InitialTypes, RestTypes, UnboxFloat,
+		TypedRvals).
+flatten_arg_types(Args, none, _, []) :-
+	require(unify(Args, []), "too many args for specified arg types").
+
+:- pred flatten_uniform_arg_types(list(rval)::in, maybe(llds_type)::in,
+	bool::in, assoc_list(rval, llds_type)::out) is det.
+
+flatten_uniform_arg_types([], _, _, []).
+flatten_uniform_arg_types([Rval | Rvals], MaybeType, UnboxFloat,
+		[Rval - Type | TypedRvals]) :-
+	llds_arg_type(Rval, MaybeType, UnboxFloat, Type),
+	flatten_uniform_arg_types(Rvals, MaybeType, UnboxFloat, TypedRvals).
+
+:- pred flatten_initial_arg_types(list(rval)::in, initial_arg_types::in,
+	create_arg_types::in, bool::in, assoc_list(rval, llds_type)::out)
 	is det.
 
-llds_common__process_create(Tag, Args0, ArgTypes, Rval, Info0, Info) :-
-	llds_common__process_maybe_rvals(Args0, Args, Info0, Info1),
-	Info1 = common_info(BaseName, NextCell0, CellMap0),
-	( map__search(CellMap0, Args - ArgTypes, CellInfo0) ->
-		CellInfo0 = cell_info(VarNum),
-		DataConst = data_addr_const(
-			data_addr(BaseName, common(VarNum))),
-		Rval = mkword(Tag, const(DataConst)),
-		Info = Info1
-	;
-		DataConst = data_addr_const(
-			data_addr(BaseName, common(NextCell0))),
-		Rval = mkword(Tag, const(DataConst)),
-		CellInfo = cell_info(NextCell0),
-		NextCell is NextCell0 + 1,
-		map__det_insert(CellMap0, Args - ArgTypes, CellInfo, CellMap),
-		Info = common_info(BaseName, NextCell, CellMap)
+flatten_initial_arg_types(Args, [], RestTypes, UnboxFloat, TypedRvals) :-
+	flatten_arg_types(Args, RestTypes, UnboxFloat, TypedRvals).
+flatten_initial_arg_types(Args, [N - MaybeType | InitTypes], RestTypes,
+		UnboxFloat, TypedRvals) :-
+	flatten_initial_arg_types_2(Args, N, MaybeType, InitTypes, RestTypes,
+		UnboxFloat, TypedRvals).
+
+:- pred flatten_initial_arg_types_2(list(rval)::in, int::in,
+	maybe(llds_type)::in, initial_arg_types::in, create_arg_types::in,
+	bool::in, assoc_list(rval, llds_type)::out) is det.
+
+flatten_initial_arg_types_2([], N, _, _, _, _, []) :-
+	require(unify(N, 0), "not enough args for specified arg types").
+flatten_initial_arg_types_2([Rval | Rvals], N, MaybeType, InitTypes,
+		RestTypes, UnboxFloat, TypedRvals) :-
+	( N = 0 ->
+		flatten_initial_arg_types([Rval | Rvals], InitTypes,
+			RestTypes, UnboxFloat, TypedRvals)
+	;
+		llds_arg_type(Rval, MaybeType, UnboxFloat, Type),
+		flatten_initial_arg_types_2(Rvals, N - 1, MaybeType,
+			InitTypes, RestTypes, UnboxFloat,
+			TypedRvalsTail),
+		TypedRvals = [Rval - Type | TypedRvalsTail]
+	).
+
+	% Given an rval, figure out the type it would have as an argument,
+	% if it is not explicitly specified.
+
+:- pred llds_arg_type(rval::in, maybe(llds_type)::in, bool::in,
+	llds_type::out) is det.
+
+llds_arg_type(Rval, MaybeType, UnboxFloat, Type) :-
+	( MaybeType = yes(SpecType) ->
+		Type = SpecType
+	;
+		rval_type_as_arg(Rval, UnboxFloat, Type)
+	).
+
+	% 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, bool::in, llds_type::out) is det.
+
+rval_type_as_arg(Rval, UnboxFloat, Type) :-
+	llds__rval_type(Rval, Type0),
+	( Type0 = float, UnboxFloat = no ->
+		Type = data_ptr
+	;
+		Type = Type0
 	).
 
 %-----------------------------------------------------------------------------%
@@ -125,88 +220,80 @@
 :- pred llds_common__process_datas(list(comp_gen_c_data)::in,
 	list(comp_gen_c_data)::out, common_info::in, common_info::out) is det.
 
-llds_common__process_datas([], [], Info, Info).
-llds_common__process_datas([Data0 | Datas0], [Data | Datas], Info0, Info) :-
-	llds_common__process_data(Data0, Data, Info0, Info1),
-	llds_common__process_datas(Datas0, Datas, Info1, Info).
+llds_common__process_datas([], [], !Info).
+llds_common__process_datas([Data0 | Datas0], [Data | Datas], !Info) :-
+	llds_common__process_data(Data0, Data, !Info),
+	llds_common__process_datas(Datas0, Datas, !Info).
 
 :- pred llds_common__process_data(comp_gen_c_data::in, comp_gen_c_data::out,
 	common_info::in, common_info::out) is det.
 
-llds_common__process_data(
-		comp_gen_c_data(Name, DataName, Export, Args0, ArgTypes, Refs),
-		comp_gen_c_data(Name, DataName, Export, Args, ArgTypes, Refs),
-		Info0, Info) :-
-	llds_common__process_maybe_rvals(Args0, Args, Info0, Info).
-llds_common__process_data(rtti_data(RttiData), rtti_data(RttiData),
-		Info, Info).
+llds_common__process_data(common_data(Name, CellNum, TypeNum, ArgsTypes0),
+		common_data(Name, CellNum, TypeNum, ArgsTypes), !Info) :-
+	list__map_foldl(llds_common__process_rval_type, ArgsTypes0, ArgsTypes,
+		!Info).
+llds_common__process_data(rtti_data(RttiData), rtti_data(RttiData), !Info).
 llds_common__process_data(layout_data(LayoutData0), layout_data(LayoutData),
-		Info0, Info) :-
-	llds_common__process_layout_data(LayoutData0, LayoutData, Info0, Info).
+		!Info) :-
+	llds_common__process_layout_data(LayoutData0, LayoutData, !Info).
 
 :- pred llds_common__process_layout_data(layout_data::in, layout_data::out,
 	common_info::in, common_info::out) is det.
 
-llds_common__process_layout_data(LayoutData0, LayoutData, Info0, Info) :-
+llds_common__process_layout_data(LayoutData0, LayoutData, !Info) :-
 	LayoutData0 = label_layout_data(Label, ProcLayoutName,
 		MaybePort, MaybeIsHidden, MaybeGoalPath, MaybeVarInfo0),
 	(
 		MaybeVarInfo0 = no,
-		LayoutData = LayoutData0,
-		Info = Info0
+		LayoutData = LayoutData0
 	;
 		MaybeVarInfo0 = yes(VarInfo0),
 		VarInfo0 = label_var_info(EncodedCount,
 			LocnsTypes0, VarNums0, TypeParams0),
-		llds_common__process_rval(LocnsTypes0, LocnsTypes,
-			Info0, Info1),
-		llds_common__process_rval(VarNums0, VarNums,
-			Info1, Info2),
-		llds_common__process_rval(TypeParams0, TypeParams,
-			Info2, Info),
+		llds_common__process_rval(LocnsTypes0, LocnsTypes, !Info),
+		llds_common__process_rval(VarNums0, VarNums, !Info),
+		llds_common__process_rval(TypeParams0, TypeParams, !Info),
 		VarInfo = label_var_info(EncodedCount,
 			LocnsTypes, VarNums, TypeParams),
 		MaybeVarInfo = yes(VarInfo),
 		LayoutData = label_layout_data(Label, ProcLayoutName,
 			MaybePort, MaybeIsHidden, MaybeGoalPath, MaybeVarInfo)
 	).
-llds_common__process_layout_data(LayoutData0, LayoutData, Info0, Info) :-
+llds_common__process_layout_data(LayoutData0, LayoutData, !Info) :-
 	LayoutData0 = proc_layout_data(ProcLabel, Traversal, MaybeRest0),
 	(
 		MaybeRest0 = no_proc_id,
-		LayoutData = LayoutData0,
-		Info = Info0
+		LayoutData = LayoutData0
 	;
 		MaybeRest0 = proc_id_only,
-		LayoutData = LayoutData0,
-		Info = Info0
+		LayoutData = LayoutData0
 	;
 		MaybeRest0 = proc_id_and_exec_trace(Exec0),
-		llds_common__process_exec_trace(Exec0, Exec, Info0, Info),
+		llds_common__process_exec_trace(Exec0, Exec, !Info),
 		MaybeRest = proc_id_and_exec_trace(Exec),
 		LayoutData = proc_layout_data(ProcLabel, Traversal, MaybeRest)
 	).
-llds_common__process_layout_data(LayoutData0, LayoutData, Info, Info) :-
+llds_common__process_layout_data(LayoutData0, LayoutData, !Info) :-
 	LayoutData0 = closure_proc_id_data(_, _, _, _, _, _, _),
 	LayoutData = LayoutData0.
-llds_common__process_layout_data(LayoutData0, LayoutData, Info, Info) :-
+llds_common__process_layout_data(LayoutData0, LayoutData, !Info) :-
 	LayoutData0 = module_layout_data(_, _, _, _, _, _, _),
 	LayoutData = LayoutData0.
-llds_common__process_layout_data(LayoutData0, LayoutData, Info, Info) :-
+llds_common__process_layout_data(LayoutData0, LayoutData, !Info) :-
 	LayoutData0 = proc_static_data(_, _, _, _, _),
 	LayoutData = LayoutData0.
-llds_common__process_layout_data(LayoutData0, LayoutData, Info0, Info) :-
+llds_common__process_layout_data(LayoutData0, LayoutData, !Info) :-
 	LayoutData0 = table_io_decl_data(RttiProcLabel, Kind, NumPTIs,
 		PTIVector0, TVarLocnMap0),
-	llds_common__process_rval(PTIVector0, PTIVector, Info0, Info1),
-	llds_common__process_rval(TVarLocnMap0, TVarLocnMap, Info1, Info),
+	llds_common__process_rval(PTIVector0, PTIVector, !Info),
+	llds_common__process_rval(TVarLocnMap0, TVarLocnMap, !Info),
 	LayoutData = table_io_decl_data(RttiProcLabel, Kind, NumPTIs,
 		PTIVector, TVarLocnMap).
-llds_common__process_layout_data(LayoutData0, LayoutData, Info0, Info) :-
+llds_common__process_layout_data(LayoutData0, LayoutData, !Info) :-
 	LayoutData0 = table_gen_data(RttiProcLabel, NumInputs, NumOutputs,
 		Steps, PTIVector0, TVarLocnMap0),
-	llds_common__process_rval(PTIVector0, PTIVector, Info0, Info1),
-	llds_common__process_rval(TVarLocnMap0, TVarLocnMap, Info1, Info),
+	llds_common__process_rval(PTIVector0, PTIVector, !Info),
+	llds_common__process_rval(TVarLocnMap0, TVarLocnMap, !Info),
 	LayoutData = table_gen_data(RttiProcLabel, NumInputs, NumOutputs,
 		Steps, PTIVector, TVarLocnMap).
 
@@ -269,8 +356,9 @@
 		llds_common__process_instrs(Instrs0, Instrs, Info0, Info),
 		Instr = block(NR, NF, Instrs)
 	;
-		Instr0 = assign(Lval, Rval0),
-		llds_common__process_rval(Rval0, Rval, Info0, Info),
+		Instr0 = assign(Lval0, Rval0),
+		llds_common__process_lval(Lval0, Lval, Info0, Info1),
+		llds_common__process_rval(Rval0, Rval, Info1, Info),
 		Instr = assign(Lval, Rval)
 	;
 		Instr0 = call(_, _, _, _, _, _),
@@ -289,7 +377,6 @@
 		Instr = Instr0,
 		Info = Info0
 	;
-		% unlikely to find anything to share, but why not try?
 		Instr0 = computed_goto(Rval0, Labels),
 		llds_common__process_rval(Rval0, Rval, Info0, Info),
 		Instr = computed_goto(Rval, Labels)
@@ -298,34 +385,31 @@
 		Instr = Instr0,
 		Info = Info0
 	;
-		% unlikely to find anything to share, but why not try?
 		Instr0 = if_val(Rval0, Target),
 		llds_common__process_rval(Rval0, Rval, Info0, Info),
 		Instr = if_val(Rval, Target)
 	;
-		% unlikely to find anything to share, but why not try?
-		Instr0 = incr_hp(Lval, MaybeTag, Rval0, Msg),
-		llds_common__process_rval(Rval0, Rval, Info0, Info),
+		Instr0 = incr_hp(Lval0, MaybeTag, Rval0, Msg),
+		llds_common__process_lval(Lval0, Lval, Info0, Info1),
+		llds_common__process_rval(Rval0, Rval, Info1, Info),
 		Instr = incr_hp(Lval, MaybeTag, Rval, Msg)
 	;
-		Instr0 = mark_hp(_),
-		Instr = Instr0,
-		Info = Info0
+		Instr0 = mark_hp(Lval0),
+		llds_common__process_lval(Lval0, Lval, Info0, Info),
+		Instr = mark_hp(Lval)
 	;
-		% unlikely to find anything to share, but why not try?
 		Instr0 = restore_hp(Rval0),
 		llds_common__process_rval(Rval0, Rval, Info0, Info),
 		Instr = restore_hp(Rval)
 	;
-		Instr0 = free_heap(_),
-		Instr = Instr0,
-		Info = Info0
+		Instr0 = free_heap(Rval0),
+		llds_common__process_rval(Rval0, Rval, Info0, Info),
+		Instr = free_heap(Rval)
 	;
-		Instr0 = store_ticket(_),
-		Instr = Instr0,
-		Info = Info0
+		Instr0 = store_ticket(Lval0),
+		llds_common__process_lval(Lval0, Lval, Info0, Info),
+		Instr = store_ticket(Lval)
 	;
-		% unlikely to find anything to share, but why not try?
 		Instr0 = reset_ticket(Rval0, Reason),
 		llds_common__process_rval(Rval0, Rval, Info0, Info),
 		Instr = reset_ticket(Rval, Reason)
@@ -338,13 +422,13 @@
 		Instr = Instr0,
 		Info = Info0
 	;
-		Instr0 = mark_ticket_stack(_),
-		Instr = Instr0,
-		Info = Info0
+		Instr0 = mark_ticket_stack(Lval0),
+		llds_common__process_lval(Lval0, Lval, Info0, Info),
+		Instr = mark_ticket_stack(Lval)
 	;
-		Instr0 = prune_tickets_to(_),
-		Instr = Instr0,
-		Info = Info0
+		Instr0 = prune_tickets_to(Rval0),
+		llds_common__process_rval(Rval0, Rval, Info0, Info),
+		Instr = prune_tickets_to(Rval)
 	;
 		Instr0 = incr_sp(_, _),
 		Instr = Instr0,
@@ -354,35 +438,95 @@
 		Instr = Instr0,
 		Info = Info0
 	;
-		Instr0 = init_sync_term(_, _),
-		Instr = Instr0,
-		Info = Info0
+		Instr0 = init_sync_term(Lval0, NumBranches),
+		llds_common__process_lval(Lval0, Lval, Info0, Info),
+		Instr = init_sync_term(Lval, NumBranches)
 	;
 		Instr0 = fork(_, _, _),
 		Instr = Instr0,
 		Info = Info0
 	;
-		Instr0 = join_and_terminate(_),
-		Instr = Instr0,
-		Info = Info0
+		Instr0 = join_and_terminate(Lval0),
+		llds_common__process_lval(Lval0, Lval, Info0, Info),
+		Instr = join_and_terminate(Lval)
+	;
+		Instr0 = join_and_continue(Lval0, ContLabel),
+		llds_common__process_lval(Lval0, Lval, Info0, Info),
+		Instr = join_and_continue(Lval, ContLabel)
+	;
+		Instr0 = pragma_c(A, Components0, C, D, E, F, G, H),
+		list__map_foldl(llds_common__process_pragma_c_component,
+			Components0, Components, Info0, Info),
+		Instr = pragma_c(A, Components, C, D, E, F, G, H)
+	).
+
+:- pred llds_common__process_pragma_c_component(pragma_c_component::in,
+	pragma_c_component::out, common_info::in, common_info::out) is det.
+
+llds_common__process_pragma_c_component(Component0, Component, !Info) :-
+	(
+		Component0 = pragma_c_inputs(Inputs0),
+		list__map_foldl(llds_common__process_pragma_c_input,
+			Inputs0, Inputs, !Info),
+		Component = pragma_c_inputs(Inputs)
+	;
+		Component0 = pragma_c_outputs(Outputs0),
+		list__map_foldl(llds_common__process_pragma_c_output,
+			Outputs0, Outputs, !Info),
+		Component = pragma_c_outputs(Outputs)
 	;
-		Instr0 = join_and_continue(_, _),
-		Instr = Instr0,
-		Info = Info0
+		Component0 = pragma_c_user_code(_, _),
+		Component = Component0
 	;
-		Instr0 = pragma_c(_, _, _, _, _, _, _, _),
-		Instr = Instr0,
-		Info = Info0
+		Component0 = pragma_c_raw_code(Code, CCodeLiveLvals0),
+		(
+			CCodeLiveLvals0 = no_live_lvals_info,
+			CCodeLiveLvals = no_live_lvals_info
+		;
+			CCodeLiveLvals0 = live_lvals_info(Lvals0),
+			set__map_fold(llds_common__process_lval,
+				Lvals0, Lvals, !Info),
+			CCodeLiveLvals = live_lvals_info(Lvals)
+		),
+		Component = pragma_c_raw_code(Code, CCodeLiveLvals)
+	;
+		Component0 = pragma_c_fail_to(_),
+		Component = Component0
+	;
+		Component0 = pragma_c_noop,
+		Component = Component0
 	).
 
+:- pred llds_common__process_pragma_c_input(pragma_c_input::in,
+	pragma_c_input::out, common_info::in, common_info::out) is det.
+
+llds_common__process_pragma_c_input(Input0, Input, Info0, Info) :-
+	Input0 = pragma_c_input(Name, Type, Rval0, MaybeCType),
+	llds_common__process_rval(Rval0, Rval, Info0, Info),
+	Input = pragma_c_input(Name, Type, Rval, MaybeCType).
+
+:- pred llds_common__process_pragma_c_output(pragma_c_output::in,
+	pragma_c_output::out, common_info::in, common_info::out) is det.
+
+llds_common__process_pragma_c_output(Output0, Output, Info0, Info) :-
+	Output0 = pragma_c_output(Lval0, Type, Name, MaybeCType),
+	llds_common__process_lval(Lval0, Lval, Info0, Info),
+	Output = pragma_c_output(Lval, Type, Name, MaybeCType).
+
+:- pred llds_common__process_rval_type(pair(rval, llds_type)::in, pair(rval,
+	llds_type)::out, common_info::in, common_info::out) is det.
+
+llds_common__process_rval_type(Rval0 - Type, Rval - Type, !Info) :-
+	llds_common__process_rval(Rval0, Rval, !Info).
+
 :- pred llds_common__process_rval(rval::in, rval::out,
 	common_info::in, common_info::out) is det.
 
 llds_common__process_rval(Rval0, Rval, Info0, Info) :-
 	(
-		Rval0 = lval(_),
-		Rval = Rval0,
-		Info = Info0
+		Rval0 = lval(Lval0),
+		llds_common__process_lval(Lval0, Lval, Info0, Info),
+		Rval = lval(Lval)
 	;
 		Rval0 = var(_),
 		error("var rval found in llds_common__process_rval")
@@ -436,25 +580,92 @@
 	llds_common__process_rval(Rval0, Rval, Info0, Info1),
 	llds_common__process_rvals(Rvals0, Rvals, Info1, Info).
 
-:- pred llds_common__process_maybe_rval(maybe(rval)::in,
-	maybe(rval)::out, common_info::in, common_info::out) is det.
+:- pred llds_common__process_convert_maybe_rval(maybe(rval)::in, rval::out,
+	common_info::in, common_info::out) is det.
 
-llds_common__process_maybe_rval(MaybeRval0, MaybeRval, Info0, Info) :-
+llds_common__process_convert_maybe_rval(MaybeRval0, Rval, !Info) :-
 	(
 		MaybeRval0 = yes(Rval0),
-		llds_common__process_rval(Rval0, Rval, Info0, Info),
+		llds_common__process_rval(Rval0, Rval, !Info)
+	;
+		MaybeRval0 = no,
+		Rval = const(int_const(0))
+	).
+
+:- pred llds_common__process_maybe_rval(maybe(rval)::in, maybe(rval)::out,
+	common_info::in, common_info::out) is det.
+
+llds_common__process_maybe_rval(MaybeRval0, MaybeRval, !Info) :-
+	(
+		MaybeRval0 = yes(Rval0),
+		llds_common__process_rval(Rval0, Rval, !Info),
 		MaybeRval = yes(Rval)
 	;
 		MaybeRval0 = no,
-		MaybeRval = no,
-		Info = Info0
+		MaybeRval = no
 	).
 
-:- pred llds_common__process_maybe_rvals(list(maybe(rval))::in,
-	list(maybe(rval))::out, common_info::in, common_info::out) is det.
+:- pred llds_common__process_lval(lval::in, lval::out,
+	common_info::in, common_info::out) is det.
 
-llds_common__process_maybe_rvals([], [], Info, Info).
-llds_common__process_maybe_rvals([MaybeRval0 | MaybeRvals0],
-		[MaybeRval | MaybeRvals], Info0, Info) :-
-	llds_common__process_maybe_rval(MaybeRval0, MaybeRval, Info0, Info1),
-	llds_common__process_maybe_rvals(MaybeRvals0, MaybeRvals, Info1, Info).
+llds_common__process_lval(Lval0, Lval, !Info) :-
+	(
+		Lval0 = reg(_, _),
+		Lval = Lval0
+	;
+		Lval0 = succip,
+		Lval = Lval0
+	;
+		Lval0 = maxfr,
+		Lval = Lval0
+	;
+		Lval0 = curfr,
+		Lval = Lval0
+	;
+		Lval0 = hp,
+		Lval = Lval0
+	;
+		Lval0 = sp,
+		Lval = Lval0
+	;
+		Lval0 = temp(_, _),
+		Lval = Lval0
+	;
+		Lval0 = stackvar(_),
+		Lval = Lval0
+	;
+		Lval0 = framevar(_),
+		Lval = Lval0
+	;
+		Lval0 = succip(Rval0),
+		llds_common__process_rval(Rval0, Rval, !Info),
+		Lval = succip(Rval)
+	;
+		Lval0 = redoip(Rval0),
+		llds_common__process_rval(Rval0, Rval, !Info),
+		Lval = redoip(Rval)
+	;
+		Lval0 = redofr(Rval0),
+		llds_common__process_rval(Rval0, Rval, !Info),
+		Lval = redofr(Rval)
+	;
+		Lval0 = succfr(Rval0),
+		llds_common__process_rval(Rval0, Rval, !Info),
+		Lval = succfr(Rval)
+	;
+		Lval0 = prevfr(Rval0),
+		llds_common__process_rval(Rval0, Rval, !Info),
+		Lval = prevfr(Rval)
+	;
+		Lval0 = field(MaybeTag, Base0, Offset0),
+		llds_common__process_rval(Base0, Base, !Info),
+		llds_common__process_rval(Offset0, Offset, !Info),
+		Lval = field(MaybeTag, Base, Offset)
+	;
+		Lval0 = mem_ref(Rval0),
+		llds_common__process_rval(Rval0, Rval, !Info),
+		Lval = mem_ref(Rval)
+	;
+		Lval0 = lvar(_),
+		error("llds_common__process_lval: lvar")
+	).
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.209
diff -u -b -r1.209 llds_out.m
--- compiler/llds_out.m	19 Apr 2003 05:52:02 -0000	1.209
+++ compiler/llds_out.m	30 Apr 2003 10:58:37 -0000
@@ -21,6 +21,7 @@
 :- import_module backend_libs__builtin_ops.
 :- import_module libs__globals.
 :- import_module ll_backend__llds.
+:- import_module parse_tree__prog_data.
 
 :- import_module bool, std_util, list, map, io.
 
@@ -142,7 +143,7 @@
 	% The following are exported to rtti_out. It may be worthwhile
 	% to put these in a new module (maybe llds_out_util).
 
-:- type decl_id --->	create_label(int)
+:- type decl_id --->	common_type(module_name, int)
 		;	float_label(string)
 		;	code_addr(code_addr)
 		;	data_addr(data_addr)
@@ -196,7 +197,6 @@
 :- import_module ll_backend__rtti_out.
 :- import_module parse_tree__mercury_to_mercury.
 :- import_module parse_tree__modules.
-:- import_module parse_tree__prog_data.
 :- import_module parse_tree__prog_out.
 :- import_module parse_tree__prog_util.
 
@@ -785,40 +785,37 @@
 	io__state, io__state).
 :- mode output_c_data_type_def(in, in, out, di, uo) is det.
 
-output_c_data_type_def(comp_gen_c_data(ModuleName, VarName, ExportedFromModule,
-		ArgVals, ArgTypes, _Refs), DeclSet0, DeclSet) -->
-	io__write_string("\n"),
-	{ data_name_linkage(VarName, Linkage) },
-	{
-		( Linkage = extern, ExportedFromModule = yes
-		; Linkage = static, ExportedFromModule = no
-		)
-	->
-		true
-	;
-		error("linkage mismatch")
-	},
+output_c_data_type_def(common_data(ModuleName, CellNum, TypeNum, ArgsTypes),
+		!DeclSet, !IO) :-
+	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.
-	( { ExportedFromModule = yes } ->
-		{ ExportedFromFile = yes }
-	;
-		globals__io_lookup_bool_option(split_c_files, SplitFiles),
-		{ ExportedFromFile = SplitFiles }
-	),
+	globals__io_lookup_bool_option(split_c_files, SplitFiles, !IO),
+	ExportedFromFile = SplitFiles,
 
-	{ DeclId = data_addr(data_addr(ModuleName, VarName)) },
-	output_const_term_decl(ArgVals, ArgTypes, DeclId, ExportedFromFile,
-		yes, yes, no, "", "", 0, _),
-	{ decl_set_insert(DeclId, DeclSet0, DeclSet) }.
-output_c_data_type_def(rtti_data(RttiData), DeclSet0, DeclSet) -->
-	output_rtti_data_decl(RttiData, DeclSet0, DeclSet).
-output_c_data_type_def(layout_data(LayoutData), DeclSet0, DeclSet) -->
-	output_maybe_layout_data_decl(LayoutData, DeclSet0, DeclSet).
+	TypeDeclId = common_type(ModuleName, TypeNum),
+	( decl_set_is_member(TypeDeclId, !.DeclSet) ->
+		true
+	;
+		assoc_list__values(ArgsTypes, Types),
+		output_const_term_type(Types, ModuleName, TypeNum,
+			"", "", 0, _, !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(ArgsTypes, ModuleName, CellNum, TypeNum,
+		ExportedFromFile, no, "", "", 0, _, !IO),
+	decl_set_insert(VarDeclId, !DeclSet).
+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_comp_gen_c_module_list(list(comp_gen_c_module)::in,
 	map(label, data_addr)::in, decl_set::in, decl_set::out,
@@ -884,47 +881,29 @@
 :- pred output_comp_gen_c_data(comp_gen_c_data::in,
 	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
 
-output_comp_gen_c_data(comp_gen_c_data(ModuleName, VarName, ExportedFromModule,
-		ArgVals, ArgTypes, _Refs), DeclSet0, DeclSet) -->
-	io__write_string("\n"),
-	output_cons_arg_decls(ArgVals, "", "", 0, _, DeclSet0, DeclSet1),
-
-	%
-	% sanity check: check that the (redundant) ExportedFromModule field
-	% in the c_data, which we use for the definition, matches the linkage
-	% computed by linkage/2 from the dataname, which we use for any
-	% prior declarations.
-	%
-	{ data_name_linkage(VarName, Linkage) },
-	{
-		( Linkage = extern, ExportedFromModule = yes
-		; Linkage = static, ExportedFromModule = no
-		)
-	->
-		true
-	;
-		error("linkage mismatch")
-	},
+output_comp_gen_c_data(common_data(ModuleName, CellNum, TypeNum, ArgsTypes),
+		!DeclSet, !IO) :-
+	io__write_string("\n", !IO),
+	assoc_list__keys(ArgsTypes, Args),
+	output_rvals_decls(Args, "", "", 0, _, !DeclSet, !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.
-	( { ExportedFromModule = yes } ->
-		{ ExportedFromFile = yes }
-	;
-		globals__io_lookup_bool_option(split_c_files, SplitFiles),
-		{ ExportedFromFile = SplitFiles }
-	),
-	{ DeclId = data_addr(data_addr(ModuleName, VarName)) },
-	output_const_term_decl(ArgVals, ArgTypes, DeclId, ExportedFromFile,
-		no, yes, yes, "", "", 0, _),
-	{ decl_set_insert(DeclId, DeclSet1, DeclSet) }.
-output_comp_gen_c_data(rtti_data(RttiData), DeclSet0, DeclSet) -->
-	output_rtti_data_defn(RttiData, DeclSet0, DeclSet).
-output_comp_gen_c_data(layout_data(LayoutData), DeclSet0, DeclSet) -->
-	output_layout_data_defn(LayoutData, DeclSet0, DeclSet).
+	globals__io_lookup_bool_option(split_c_files, SplitFiles, !IO),
+	ExportedFromFile = SplitFiles,
+
+	VarName = common(CellNum, TypeNum),
+	VarDeclId = data_addr(data_addr(ModuleName, VarName)),
+	output_const_term_decl_or_defn(ArgsTypes, ModuleName, CellNum, TypeNum,
+		ExportedFromFile, yes, "", "", 0, _, !IO),
+	decl_set_insert(VarDeclId, !DeclSet).
+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_user_foreign_code_list(list(user_foreign_code)::in,
 	io__state::di, io__state::uo) is det.
@@ -2215,20 +2194,9 @@
 	    { N = N2 },
 	    { DeclSet = DeclSet2 }
 	).
-output_rval_decls(
-		create(_Tag, ArgVals, CreateArgTypes, _StatDyn, Label, _, _),
-		FirstIndent, LaterIndent, N0, N, DeclSet0, DeclSet) -->
-	{ CreateLabel = create_label(Label) },
-	( { decl_set_is_member(CreateLabel, DeclSet0) } ->
-		{ N = N0 },
-		{ DeclSet = DeclSet0 }
-	;
-		{ decl_set_insert(CreateLabel, DeclSet0, DeclSet1) },
-		output_cons_arg_decls(ArgVals, FirstIndent, LaterIndent,
-			N0, N1, DeclSet1, DeclSet),
-		output_const_term_decl(ArgVals, CreateArgTypes, CreateLabel,
-			no, yes, yes, yes, FirstIndent, LaterIndent, N1, N)
-	).
+output_rval_decls(create(_, _, _, _, _, _, _), _, _, _, _, _, _) -->
+	% These should have all been converted to data_addrs by llds_common.
+	{ error("output_rval_decls: create") }.
 output_rval_decls(mem_addr(MemRef), FirstIndent, LaterIndent,
 		N0, N, DeclSet0, DeclSet) -->
 	output_mem_ref_decls(MemRef, FirstIndent, LaterIndent,
@@ -2324,134 +2292,100 @@
 
 	% We output constant terms as follows:
 	%
-	%	static const struct <foo>_struct {
-	%		MR_Word field1;			// Def
-	%		MR_Float field2;
-	%		MR_Word * field3;
+	%	struct <prefix>_common_type_<TypeNum> {		// Type
 	%		...
-	%	}
-	%	<foo> 					// Decl
-	%	= {					// Init
+	%	};
+	%
+	%	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 `const'
-	% from the above structure.
+	% to initialize them dynamically, so we must omit both `const's
+	% above.
 	%
-	% Also we now conditionally output some parts.  The parts that
-	% are conditionally output are Def, Decl and Init.  It is an
-	% error for Init to be yes and Decl to be no.
+	% 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_decl(list(maybe(rval)), create_arg_types, decl_id,
-	bool, bool, bool, bool, string, string, int, int, io__state, io__state).
-:- mode output_const_term_decl(in, in, in, in, in, in,
-	in, in, in, in, out, di, uo) is det.
-
-output_const_term_decl(ArgVals, CreateArgTypes, DeclId, Exported,
-		Def, Decl, Init, FirstIndent, LaterIndent, N1, N) -->
-	(
-		{ Init = yes }, { Decl = no }
-	->
-		{ error("output_const_term_decl: Inconsistent Decl and Init") }
-	;
-		[]
-	),
-	output_indent(FirstIndent, LaterIndent, N1),
-	{ N = N1 + 1 },
-	(
-		{ Decl = yes }
-	->
-		(
-			{ Exported = yes }
-		->
-			[]
-		;
-			io__write_string("static ")
-		),
-		globals__io_get_globals(Globals),
-		{ globals__have_static_code_addresses(Globals, StaticCode) },
-		(
-				% Don't make the structure `const'
-				% if the structure will eventually include
-				% code addresses but we don't have static code
-				% addresses.
-			{ StaticCode = no },
-			{ DeclId = data_addr(DataAddr) },
-			{ data_addr_would_include_code_address(DataAddr)
-				= yes }
-		->
-			[]
-		;
-			% XXX io__write_string("const ")
-			% []
-			io__write_string("const ")
-		)
-	;
-		[]
-	),
-	io__write_string("struct "),
+:- pred output_const_term_type(list(llds_type)::in, module_name::in, int::in,
+	string::in, string::in, int::in, int::out,
+	io__state::di, io__state::uo) is det.
 
-	output_decl_id(DeclId),
-	io__write_string("_struct"),
-	(
-		{ Def = yes }
-	->
-		io__write_string(" {\n"),
-		output_cons_arg_types(ArgVals, CreateArgTypes, "\t", 1),
-		io__write_string("} ")
-	;
-		[]
-	),
-	(
-		{ Decl = yes }
-	->
-		io__write_string(" "),
-		output_decl_id(DeclId),
-		(
-			{ Init = yes }
-		->
-			io__write_string(" = {\n"),
-			output_cons_args(ArgVals, CreateArgTypes, "\t"),
-			io__write_string(LaterIndent),
-			io__write_string("};\n")
-		;
-			io__write_string(";\n")
-		)
-	;
-		io__write_string(";\n")
+output_const_term_type(Types, ModuleName, TypeNum, FirstIndent, LaterIndent,
+		!N, !IO) :-
+	output_indent(FirstIndent, LaterIndent, !.N, !IO),
+	!:N = !.N + 1,
+	io__write_string("struct ", !IO),
+	output_common_cell_type_name(ModuleName, TypeNum, !IO),
+	io__write_string(" {\n", !IO),
+	output_cons_arg_types(Types, "\t", 1, !IO),
+	io__write_string("};\n", !IO).
+
+:- pred output_const_term_decl_or_defn(assoc_list(rval, llds_type)::in,
+	module_name::in, int::in, int::in, bool::in, bool::in,
+	string::in, string::in, int::in, int::out,
+	io__state::di, io__state::uo) is det.
+
+output_const_term_decl_or_defn(ArgsTypes, ModuleName, CellNum, TypeNum,
+		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)
+	),
+	output_common_cell_type_name(ModuleName, TypeNum, !IO),
+	io__write_string("\n\t", !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),
+		output_cons_args(ArgsTypes, "\t", !IO),
+		io__write_string(LaterIndent, !IO),
+		io__write_string("};\n", !IO)
 	).
 
 	% Return true if a data structure of the given type will eventually
-	% include code addresses. Note that we can't just test the data
-	% structure itself, since in the absence of code addresses the earlier
-	% passes will have replaced any code addresses with dummy values
-	% that will have to be overridden with the real code address at
-	% initialization time.
-
-:- func data_addr_would_include_code_address(data_addr) = bool.
-
-data_addr_would_include_code_address(data_addr(_, DataName)) =
-	data_name_would_include_code_address(DataName).
-data_addr_would_include_code_address(rtti_addr(_, RttiName)) =
+	% have code addresses filled in inside it. Note that we can't just
+	% test the data structure itself, since in the absence of static
+	% code addresses the earlier passes will have replaced any code
+	% addresses with dummy values that will have to be overridden with
+	% the real code address at initialization time.
+
+:- func data_addr_may_include_non_static_code_address(data_addr) = bool.
+
+data_addr_may_include_non_static_code_address(data_addr(_, DataName)) =
+	data_name_may_include_non_static_code_address(DataName).
+data_addr_may_include_non_static_code_address(rtti_addr(_, RttiName)) =
 	rtti_name_would_include_code_addr(RttiName).
-data_addr_would_include_code_address(layout_addr(LayoutName)) =
+data_addr_may_include_non_static_code_address(layout_addr(LayoutName)) =
 	layout_name_would_include_code_addr(LayoutName).
 
-:- func data_name_would_include_code_address(data_name) = bool.
+:- func data_name_may_include_non_static_code_address(data_name) = bool.
 
-data_name_would_include_code_address(common(_)) =                 no.
-data_name_would_include_code_address(base_typeclass_info(_, _)) = yes.
-data_name_would_include_code_address(tabling_pointer(_)) =        no.
-data_name_would_include_code_address(deep_profiling_procedure_data(_)) =  no.
+% 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(base_typeclass_info(_, _)) = yes.
+data_name_may_include_non_static_code_address(tabling_pointer(_)) = no.
 
 :- pred output_decl_id(decl_id, io__state, io__state).
 :- mode output_decl_id(in, di, uo) is det.
 
-output_decl_id(create_label(N)) -->
-	io__write_string("mercury_const_"),
-	io__write_int(N).
+output_decl_id(common_type(ModuleName, TypeNum)) -->
+	output_common_cell_type_name(ModuleName, TypeNum).
 output_decl_id(data_addr(DataAddr)) -->
 	output_data_addr(DataAddr).
 output_decl_id(code_addr(_CodeAddress)) -->
@@ -2461,88 +2395,17 @@
 output_decl_id(pragma_c_struct(_Name)) -->
 	{ error("output_decl_id: pragma_c_struct unexpected") }.
 
-:- pred output_cons_arg_types(list(maybe(rval))::in, create_arg_types::in,
-	string::in, int::in, io__state::di, io__state::uo) is det.
-
-output_cons_arg_types(Args, uniform(MaybeType), Indent, ArgNum) -->
-	output_uniform_cons_arg_types(Args, MaybeType, Indent, ArgNum).
-output_cons_arg_types(Args, initial(InitialTypes, RestTypes),
-		Indent, ArgNum) -->
-	output_initial_cons_arg_types(Args, InitialTypes, RestTypes,
-		Indent, ArgNum).
-output_cons_arg_types(Args, none, _, _) -->
-	{ require(unify(Args, []), "too many args for specified arg types") }.
-
-:- pred output_uniform_cons_arg_types(list(maybe(rval))::in,
-	maybe(llds_type)::in, string::in, int::in,
-	io__state::di, io__state::uo) is det.
-
-output_uniform_cons_arg_types([], _, _, _) --> [].
-output_uniform_cons_arg_types([Arg | Args], MaybeType, Indent, ArgNum) -->
-	( { Arg = yes(Rval) } ->
-		io__write_string(Indent),
-		llds_arg_type(Rval, MaybeType, Type),
-		output_llds_type(Type),
-		io__write_string(" f"),
-		io__write_int(ArgNum),
-		io__write_string(";\n"),
-		{ ArgNum1 = ArgNum + 1 },
-		output_uniform_cons_arg_types(Args, MaybeType, Indent, ArgNum1)
-	;
-		{ error("output_uniform_cons_arg_types: missing arg") }
-	).
-
-:- pred output_initial_cons_arg_types(list(maybe(rval))::in,
-	initial_arg_types::in, create_arg_types::in, string::in, int::in,
+:- pred output_cons_arg_types(list(llds_type)::in, string::in, int::in,
 	io__state::di, io__state::uo) is det.
 
-output_initial_cons_arg_types(Args, [], RestTypes, Indent, ArgNum) -->
-	output_cons_arg_types(Args, RestTypes, Indent, ArgNum).
-output_initial_cons_arg_types(Args, [N - MaybeType | InitTypes], RestTypes,
-		Indent, ArgNum) -->
-	output_initial_cons_arg_types_2(Args, N, MaybeType, InitTypes,
-		RestTypes, Indent, ArgNum).
-
-:- pred output_initial_cons_arg_types_2(list(maybe(rval))::in, int::in,
-	maybe(llds_type)::in, initial_arg_types::in, create_arg_types::in,
-	string::in, int::in, io__state::di, io__state::uo) is det.
-
-output_initial_cons_arg_types_2([], N, _, _, _, _, _) -->
-	{ require(unify(N, 0), "not enough args for specified arg types") }.
-output_initial_cons_arg_types_2([Arg | Args], N, MaybeType, InitTypes,
-		RestTypes, Indent, ArgNum) -->
-	( { N = 0 } ->
-		output_initial_cons_arg_types([Arg | Args], InitTypes,
-			RestTypes, Indent, ArgNum)
-	;
-		( { Arg = yes(Rval) } ->
+output_cons_arg_types([], _, _) --> [].
+output_cons_arg_types([Type | Types], Indent, ArgNum) -->
 			io__write_string(Indent),
-			llds_arg_type(Rval, MaybeType, Type),
 			output_llds_type(Type),
 			io__write_string(" f"),
 			io__write_int(ArgNum),
 			io__write_string(";\n"),
-			{ ArgNum1 = ArgNum + 1 },
-			{ N1 = N - 1 },
-			output_initial_cons_arg_types_2(Args, N1, MaybeType,
-				InitTypes, RestTypes, Indent, ArgNum1)
-		;
-			{ error("output_initial_cons_arg_types: missing arg") }
-		)
-	).
-
-	% Given an rval, figure out the type it would have as an argument,
-	% if it is not explicitly specified.
-
-:- pred llds_arg_type(rval::in, maybe(llds_type)::in, llds_type::out,
-	io__state::di, io__state::uo) is det.
-
-llds_arg_type(Rval, MaybeType, Type) -->
-	( { MaybeType = yes(SpecType) } ->
-		{ Type = SpecType }
-	;
-		llds_out__rval_type_as_arg(Rval, Type)
-	).
+	output_cons_arg_types(Types, Indent, ArgNum + 1).
 
 	% Given an rval, figure out the type it would have as
 	% an argument.  Normally that's the same as its usual type;
@@ -2589,120 +2452,21 @@
 output_llds_type(data_ptr)     --> io__write_string("MR_Word *").
 output_llds_type(code_ptr)     --> io__write_string("MR_Code *").
 
-:- pred output_cons_arg_decls(list(maybe(rval))::in, string::in, string::in,
-	int::in, int::out, decl_set::in, decl_set::out,
-	io__state::di, io__state::uo) is det.
-
-output_cons_arg_decls([], _, _, N, N, DeclSet, DeclSet) --> [].
-output_cons_arg_decls([Arg | Args], FirstIndent, LaterIndent, N0, N,
-		DeclSet0, DeclSet) -->
-	( { Arg = yes(Rval) } ->
-		output_rval_decls(Rval, FirstIndent, LaterIndent, N0, N1,
-			DeclSet0, DeclSet1)
-	;
-		{ N1 = N0 },
-		{ DeclSet1 = DeclSet0 }
-	),
-	output_cons_arg_decls(Args, FirstIndent, LaterIndent, N1, N,
-		DeclSet1, DeclSet).
-
 	% Output the arguments, each on its own line prefixing with Indent,
 	% and with a cast appropriate to its type if necessary.
 
-:- pred output_cons_args(list(maybe(rval))::in, create_arg_types::in,
-	string::in, io__state::di, io__state::uo) is det.
+:- pred output_cons_args(assoc_list(rval, llds_type)::in, string::in,
+	io__state::di, io__state::uo) is det.
 
-output_cons_args(Args, uniform(MaybeType), Indent) -->
-	output_uniform_cons_args(Args, MaybeType, Indent).
-output_cons_args(Args, initial(InitTypes, RestTypes), Indent) -->
-	output_initial_cons_args(Args, InitTypes, RestTypes, Indent).
-output_cons_args(Args, none, _) -->
-	{ require(unify(Args, []), "too many args for specified arg types") }.
-
-:- pred output_uniform_cons_args(list(maybe(rval))::in, maybe(llds_type)::in,
-	string::in, io__state::di, io__state::uo) is det.
-
-output_uniform_cons_args([], _, _) --> [].
-output_uniform_cons_args([Arg | Args], MaybeType, Indent) -->
-	( { Arg = yes(Rval) } ->
-		io__write_string(Indent),
-		globals__io_get_globals(Globals),
-		(
-			%
-			% Don't output code_addr_consts if they are not
-			% actually const; instead just output `NULL' here in
-			% the static initializer.  The value will be supplied
-			% by the dynamic initialization code.
-			%
-			{ Rval = const(code_addr_const(_)) },
-			{ globals__have_static_code_addresses(Globals,
-				StaticCode) },
-			{ StaticCode = no }
-		->
-			io__write_string("NULL")
-		;
-			( { MaybeType = yes(_) } ->
-				output_static_rval(Rval)
-			;
-				llds_out__rval_type_as_arg(Rval, Type),
-				output_rval_as_type(Rval, Type)
-			)
-		),
-		( { Args \= [] } ->
-			io__write_string(",\n"),
-			output_uniform_cons_args(Args, MaybeType, Indent)
-		;
-			io__write_string("\n")
-		)
-	;
-		% `Arg = no' means the argument is uninitialized,
-		% but that would mean the term isn't ground
-		{ error("output_uniform_cons_args: missing argument") }
-	).
-
-:- pred output_initial_cons_args(list(maybe(rval))::in, initial_arg_types::in,
-	create_arg_types::in, string::in, io__state::di, io__state::uo) is det.
-
-output_initial_cons_args(Args, [], RestTypes, Indent) -->
-	output_cons_args(Args, RestTypes, Indent).
-output_initial_cons_args(Args, [N - MaybeType | InitTypes], RestTypes,
-		Indent) -->
-	output_initial_cons_args_2(Args, N, MaybeType, InitTypes, RestTypes,
-		Indent).
-
-:- pred output_initial_cons_args_2(list(maybe(rval))::in, int::in,
-	maybe(llds_type)::in, initial_arg_types::in, create_arg_types::in,
-	string::in, io__state::di, io__state::uo) is det.
-
-output_initial_cons_args_2([], N, _, _, _, _) -->
-	{ require(unify(N, 0), "not enough args for specified arg types") }.
-output_initial_cons_args_2([Arg | Args], N, MaybeType, InitTypes, RestTypes,
-		Indent) -->
-	( { N = 0 } ->
-		output_initial_cons_args([Arg | Args], InitTypes, RestTypes,
-			Indent)
+output_cons_args([], _Indent, !IO).
+output_cons_args([Rval - Type | RvalsTypes], Indent, !IO) :-
+	io__write_string(Indent, !IO),
+	output_rval_as_type(Rval, Type, !IO),
+	( RvalsTypes \= [] ->
+		io__write_string(",\n", !IO),
+		output_cons_args(RvalsTypes, Indent, !IO)
 	;
-		( { Arg = yes(Rval) } ->
-			{ N1 = N - 1 },
-			io__write_string(Indent),
-			( { MaybeType = yes(_) } ->
-				output_static_rval(Rval)
-			;
-				llds_out__rval_type_as_arg(Rval, Type),
-				output_rval_as_type(Rval, Type)
-			),
-			( { Args \= [] } ->
-				io__write_string(",\n"),
-				output_initial_cons_args_2(Args, N1, MaybeType,
-					InitTypes, RestTypes, Indent)
-			;
-				{ require(unify(N1, 0),
-				"not enough args for specified arg types") },
-				io__write_string("\n")
-			)
-		;
-			{ error("output_initial_cons_arg: missing argument") }
-		)
+		io__write_string("\n", !IO)
 	).
 
 %-----------------------------------------------------------------------------%
@@ -2983,7 +2747,8 @@
 		io__write_string(LinkageStr),
 
 		{ InclCodeAddr =
-			data_name_would_include_code_address(DataVarName) },
+			data_name_may_include_non_static_code_address(
+				DataVarName) },
 		{ c_data_const_string(Globals, InclCodeAddr, ConstStr) },
 		io__write_string(ConstStr),
 
@@ -2997,10 +2762,9 @@
 
 :- pred data_name_linkage(data_name::in, linkage::out) is det.
 
-data_name_linkage(common(_),                 static).
+data_name_linkage(common(_, _),              static).
 data_name_linkage(base_typeclass_info(_, _), extern).
 data_name_linkage(tabling_pointer(_),        static).
-data_name_linkage(deep_profiling_procedure_data(_), static).
 
 %-----------------------------------------------------------------------------%
 
@@ -3273,13 +3037,12 @@
 
 output_data_addr(ModuleName, VarName) -->
 	(
-		{ VarName = common(N) },
+		{ VarName = common(CellNum, _TypeNum) },
 		{ MangledModuleName = sym_name_mangle(ModuleName) },
 		io__write_string(mercury_data_prefix),
 		io__write_string(MangledModuleName),
 		io__write_string("__common_"),
-		{ string__int_to_string(N, NStr) },
-		io__write_string(NStr)
+		io__write_int(CellNum)
 	;
 			% We don't want to include the module name as part
 			% of the name if it is a base_typeclass_info, since
@@ -3291,13 +3054,18 @@
 	;
 		{ VarName = tabling_pointer(ProcLabel) },
 		output_tabling_pointer_var_name(ProcLabel)
-	;
-		{ VarName = deep_profiling_procedure_data(ProcLabel) },
-		io__write_string(mercury_data_prefix),
-		io__write_string("_deep_profiling_data__"),
-		output_proc_label(ProcLabel)
 	).
 
+:- pred output_common_cell_type_name(module_name::in, int::in,
+	io__state::di, io__state::uo) is det.
+
+output_common_cell_type_name(ModuleName, TypeNum) -->
+	{ MangledModuleName = sym_name_mangle(ModuleName) },
+	io__write_string(mercury_data_prefix),
+	io__write_string(MangledModuleName),
+	io__write_string("__common_type_"),
+	io__write_int(TypeNum).
+
 :- pred output_label_as_code_addr(label, io__state, io__state).
 :- mode output_label_as_code_addr(in, di, uo) is det.
 
@@ -3650,15 +3418,9 @@
 	;
 		output_lval(Lval)
 	).
-output_rval(create(Tag, _Args, _ArgTypes, _StatDyn, CellNum, _Msg, _Reuse)) -->
-		% emit a reference to the static constant which we
-		% declared in output_rval_decls.
-	io__write_string("MR_mkword(MR_mktag("),
-	io__write_int(Tag),
-	io__write_string("), "),
-	io__write_string("&mercury_const_"),
-	io__write_int(CellNum),
-	io__write_string(")").
+output_rval(create(_, _, _, _, _, _, _)) -->
+	% These should have all been converted to data_addrs by llds_common.
+	{ error("output_rval: create") }.
 output_rval(var(_)) -->
 	{ error("Cannot output a var(_) expression in code") }.
 output_rval(mem_addr(MemRef)) -->
@@ -3734,80 +3496,6 @@
 	io__write_string("&"),
 	output_data_addr(DataAddr).
 output_rval_const(label_entry(Label)) -->
-	io__write_string("MR_ENTRY("),
-	output_label(Label),
-	io__write_string(")").
-
-	% Output an rval as an initializer in a static struct.
-	% Make sure it has the C type the corresponding field would have.
-	% This is the "really" natural type of the rval, free of the
-	% Mercury abstract engine's need to shoehorn things into MR_Words.
-
-:- pred output_static_rval(rval, io__state, io__state).
-:- mode output_static_rval(in, di, uo) is det.
-
-output_static_rval(const(Const)) -->
-	output_rval_static_const(Const).
-output_static_rval(unop(_, _)) -->
-	{ error("Cannot output a unop(_, _) in a static initializer") }.
-output_static_rval(binop(_, _, _)) -->
-	{ error("Cannot output a binop(_, _, _) in a static initializer") }.
-output_static_rval(mkword(Tag, Exprn)) -->
-	output_llds_type_cast(data_ptr),
-	io__write_string("MR_mkword("),
-	output_tag(Tag),
-	io__write_string(", "),
-	output_static_rval(Exprn),
-	io__write_string(")").
-output_static_rval(lval(_)) -->
-	{ error("Cannot output an lval(_) in a static initializer") }.
-output_static_rval(
-		create(Tag, _Args, _ArgTypes, _StatDyn, CellNum, _Msg, _Reuse))
-	-->
-		% emit a reference to the static constant which we
-		% declared in output_rval_decls.
-	io__write_string("MR_mkword(MR_mktag("),
-	io__write_int(Tag),
-	io__write_string("), "),
-	io__write_string("&mercury_const_"),
-	io__write_int(CellNum),
-	io__write_string(")").
-output_static_rval(var(_)) -->
-	{ error("Cannot output a var(_) in a static initializer") }.
-output_static_rval(mem_addr(_)) -->
-	{ error("Cannot output a mem_ref(_) in a static initializer") }.
-
-:- pred output_rval_static_const(rval_const, io__state, io__state).
-:- mode output_rval_static_const(in, di, uo) is det.
-
-output_rval_static_const(int_const(N)) -->
-	io__write_int(N).
-output_rval_static_const(float_const(FloatVal)) -->
-	c_util__output_float_literal(FloatVal).
-output_rval_static_const(string_const(String)) -->
-	io__write_string("MR_string_const("""),
-	c_util__output_quoted_string(String),
-	{ string__length(String, StringLength) },
-	io__write_string(""", "),
-	io__write_int(StringLength),
-	io__write_string(")").
-output_rval_static_const(multi_string_const(Length, String)) -->
-	io__write_string("MR_string_const("""),
-	c_util__output_quoted_multi_string(Length, String),
-	io__write_string(""", "),
-	io__write_int(Length),
-	io__write_string(")").
-output_rval_static_const(true) -->
-	io__write_string("MR_TRUE").
-output_rval_static_const(false) -->
-	io__write_string("MR_FALSE").
-output_rval_static_const(code_addr_const(CodeAddress)) -->
-	output_code_addr(CodeAddress).
-output_rval_static_const(data_addr_const(DataAddr)) -->
-	output_llds_type_cast(data_ptr),
-	io__write_string("&"),
-	output_data_addr(DataAddr).
-output_rval_static_const(label_entry(Label)) -->
 	io__write_string("MR_ENTRY("),
 	output_label(Label),
 	io__write_string(")").
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.283
diff -u -b -r1.283 mercury_compile.m
--- compiler/mercury_compile.m	31 Mar 2003 09:27:23 -0000	1.283
+++ compiler/mercury_compile.m	30 Apr 2003 16:51:34 -0000
@@ -3513,7 +3513,6 @@
 		ModuleName, CompileErrors) -->
 	globals__io_lookup_bool_option(verbose, Verbose),
 	globals__io_lookup_bool_option(statistics, Stats),
-	globals__io_lookup_bool_option(common_data, CommonData),
 	%
 	% Here we generate the LLDS representations for
 	% various data structures used for RTTI, type classes,
@@ -3527,7 +3526,7 @@
 	{ list__map(llds__wrap_rtti_data, TypeClassInfoRttiData,
 		TypeClassInfos) },
 	{ stack_layout__generate_llds(HLDS0, HLDS, GlobalData,
-		PossiblyDynamicLayouts, StaticLayouts, LayoutLabels) },
+		StackLayouts, LayoutLabels) },
 	%
 	% Here we perform some optimizations on the LLDS data.
 	% XXX this should perhaps be part of backend_pass
@@ -3539,21 +3538,17 @@
 	{ global_data_get_all_non_common_static_data(GlobalData,
 		NonCommonStaticData) },
 	{ global_data_get_all_closure_layouts(GlobalData, ClosureLayouts) },
-	{ CommonableData0 = StaticLayouts },
-	( { CommonData = yes } ->
-		{ llds_common(Procs0, CommonableData0, ModuleName, Procs1,
-			CommonableData) }
-	;
-		{ CommonableData = CommonableData0 },
-		{ Procs1 = Procs0 }
-	),
+	{ CommonableData0 = list__append(ClosureLayouts, StackLayouts) },
+	globals__io_lookup_bool_option(unboxed_float, UnboxFloat),
+	globals__io_lookup_bool_option(common_data, DoCommonData),
+	{ llds_common(ModuleName, UnboxFloat, DoCommonData, Procs0, Procs1,
+		CommonableData0, CommonableData) },
 
 	%
 	% Next we put it all together and output it to one or more C files.
 	%
-	{ list__condense([CommonableData, NonCommonStaticData, ClosureLayouts,
-		TypeCtorTables, TypeClassInfos, PossiblyDynamicLayouts],
-		AllData) },
+	{ list__condense([CommonableData, NonCommonStaticData,
+		TypeCtorTables, TypeClassInfos], AllData) },
 	mercury_compile__construct_c_file(HLDS, C_InterfaceInfo,
 		Procs1, GlobalVars, AllData, CFile, NumChunks),
 	mercury_compile__output_llds(ModuleName, CFile, LayoutLabels,
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.127
diff -u -b -r1.127 opt_debug.m
--- compiler/opt_debug.m	18 Mar 2003 02:43:40 -0000	1.127
+++ compiler/opt_debug.m	30 Apr 2003 08:21:54 -0000
@@ -353,18 +353,15 @@
 	opt_debug__dump_layout_name(LayoutName, LayoutName_str),
 	string__append_list(["layout_addr(", LayoutName_str, ")"], Str).
 
-opt_debug__dump_data_name(common(N), Str) :-
-	string__int_to_string(N, N_str),
-	string__append("common", N_str, Str).
+opt_debug__dump_data_name(common(CellNum, TypeNum), Str) :-
+	string__int_to_string(CellNum, C_str),
+	string__int_to_string(TypeNum, T_str),
+	string__append_list(["common(", C_str, ", ", T_str, ")"], Str).
 opt_debug__dump_data_name(base_typeclass_info(ClassId, InstanceNum), Str) :-
 	Str = make_base_typeclass_info_name(ClassId, InstanceNum).
 opt_debug__dump_data_name(tabling_pointer(ProcLabel), Str) :-
 	opt_debug__dump_proclabel(ProcLabel, ProcLabelStr),
 	string__append_list(["tabling_pointer(", ProcLabelStr, ")"], Str).
-opt_debug__dump_data_name(deep_profiling_procedure_data(ProcLabel), Str) :-
-	opt_debug__dump_proclabel(ProcLabel, ProcLabelStr),
-	string__append_list(["deep_profiling_procedure_data(",
-				ProcLabelStr, ")"], Str).
 
 opt_debug__dump_rtti_type_ctor(rtti_type_ctor(ModuleName, TypeName, Arity),
 		Str) :-
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.78
diff -u -b -r1.78 stack_layout.m
--- compiler/stack_layout.m	10 Apr 2003 05:32:07 -0000	1.78
+++ compiler/stack_layout.m	30 Apr 2003 07:44:45 -0000
@@ -39,7 +39,7 @@
 
 :- pred stack_layout__generate_llds(module_info::in, module_info::out,
 	global_data::in, list(comp_gen_c_data)::out,
-	list(comp_gen_c_data)::out, map(label, data_addr)::out) is det.
+	map(label, data_addr)::out) is det.
 
 :- pred stack_layout__construct_closure_layout(proc_label::in, int::in,
 	closure_layout_info::in, proc_label::in, module_name::in,
@@ -81,8 +81,8 @@
 	% Process all the continuation information stored in the HLDS,
 	% converting it into LLDS data structures.
 
-stack_layout__generate_llds(ModuleInfo0, ModuleInfo, GlobalData,
-		PossiblyDynamicLayouts, StaticLayouts, LayoutLabels) :-
+stack_layout__generate_llds(ModuleInfo0, ModuleInfo, GlobalData, Layouts,
+		LayoutLabels) :-
 	global_data_get_all_proc_layouts(GlobalData, ProcLayoutList0),
 	list__filter(stack_layout__valid_proc_layout, ProcLayoutList0,
 		ProcLayoutList),
@@ -122,8 +122,8 @@
 	stack_layout__concat_string_list(StringList, StringOffset,
 		ConcatStrings),
 
-	PossiblyDynamicLayouts = ProcLayouts,
-	StaticLayouts0 = list__append(TableIoDecls, InternalLayouts),
+	list__condense([TableIoDecls, ProcLayouts, InternalLayouts],
+		Layouts0),
 	( TraceLayout = yes ->
 		module_info_name(ModuleInfo0, ModuleName),
 		globals__lookup_bool_option(Globals, rtti_line_numbers,
@@ -141,9 +141,9 @@
 		ModuleLayout = layout_data(module_layout_data(ModuleName,
 			StringOffset, ConcatStrings, ProcLayoutNames,
 			SourceFileLayouts, TraceLevel, SuppressedEvents)),
-		StaticLayouts = [ModuleLayout | StaticLayouts0]
+		Layouts = [ModuleLayout | Layouts0]
 	;
-		StaticLayouts = StaticLayouts0
+		Layouts = Layouts0
 	).
 
 :- pred stack_layout__valid_proc_layout(proc_layout_info::in) is semidet.
cvs diff: Diffing compiler/notes
cvs diff: Diffing debian
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/graphics
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/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/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/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/xml
cvs diff: Diffing extras/xml/samples
cvs diff: Diffing java
cvs diff: Diffing java/library
cvs diff: Diffing java/runtime
cvs diff: Diffing library
Index: library/set.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/set.m,v
retrieving revision 1.61
diff -u -b -r1.61 set.m
--- library/set.m	27 Sep 2002 05:21:25 -0000	1.61
+++ library/set.m	30 Apr 2003 07:44:45 -0000
@@ -249,6 +249,13 @@
 	%
 :- func set__map(func(T1) = T2, set(T1)) = set(T2).
 
+	% set__map_fold(P, S0, S, A0, A) :-
+	%	L0 = set__to_sorted_list(S0),
+	%	list__map_foldl(P, L0, L, A0, A),
+	%	S = set__list_to_set(L).
+:- pred set__map_fold(pred(T1, T2, T3, T3), set(T1), set(T2), T3, T3).
+:- mode set__map_fold(pred(in, out, in, out) is det, in, out, in, out) is det.
+
 	% set__filter(P, S) =
 	% 	sorted_list_to_set(list__filter(P, to_sorted_list(S))).
 	%
@@ -453,6 +460,11 @@
 
 set__map(F, S1) = S2 :-
 	S2 = set__list_to_set(list__map(F, set__to_sorted_list(S1))).
+
+set__map_fold(P, S0, S, A0, A) :-
+	L0 = set__to_sorted_list(S0),
+	list__map_foldl(P, L0, L, A0, A),
+	S = set__list_to_set(L).
 
 set__filter(P, S1) = S2 :-
 	S2 = set__sorted_list_to_set(list__filter(P, set__to_sorted_list(S1))).
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 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/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