[m-rev.] for review: simplify the handling of static ground terms

Zoltan Somogyi zs at cs.mu.OZ.AU
Thu May 8 17:47:04 AEST 2003


For review by Fergus.

Zoltan.

Estimated hours taken: 5

Simplify the handling of static ground terms in the LLDS backend. Instead of
creating code, rtti and layout structures all containing create rvals and then
converting those rvals to static cells, create the static cells directly.

compiler/llds.m:
	Remove the create alternative from rvals, and the types used only by
	create.

	Delete the code handling the global_data type, which has been moved to
	global_data.m.

compiler/global_data.m:
	A new module handling static data structures for the LLDS backend.
	The basis of this module is the code that used to be in llds.m handling
	the global_data type, but this has been augmented to manage static
	cells as well as the data structures defined in rtti.m and layout.m.

	Also, rename the non_common_data field of global_data, which no longer
	makes sense, to refer to deep profiling, since it holds deep profiling
	data structures.

compiler/llds_common.m:
	Delete this file, since it is no longer needed. The operative part
	is now in global data.m; the rest (including the code to traverse code
	and data structures looking for create rvals) is no longer needed.

compiler/ll_backend.m:
	Delete the deleted module, and add the added module.
	XXX These changes should be also be documented in
	notes/compiler_design.html when Fergus finishes his changes
	to that file.

compiler/code_info.m:
	Add the database of static cells to the code generator state.

compiler/code_gen.m:
compiler/ll_pseudo_type_info.m:
compiler/lookup_switch.m:
compiler/mercury_compile.m:
compiler/stack_layout.m:
compiler/static_term.m:
compiler/string_switch.m:
compiler/unify_gen.m:
compiler/var_locn.m:
	Instead of creating create rvals, create static cells and return
	references to those cells. The static cell database ensures that we
	never create duplicate cells (unless --no-common-data forces us
	to do so). Pass around the static cell database.

compiler/code_util.m:
compiler/continuation_info.m:
compiler/dupelim.m:
compiler/exprn_aux.m:
compiler/jumpopt.m:
compiler/livemap.m:
compiler/llds_out.m:
compiler/middle_rec.m:
compiler/opt_debug.m:
compiler/opt_util.m:
compiler/optimize.m:
	Minor changes to conform to the above, mostly consisting of the
	deletion of code that handled create rvals.

cvs diff: Diffing .
cvs diff: Diffing analysis
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/doc
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing boehm_gc/tests
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/code_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_gen.m,v
retrieving revision 1.111
diff -u -b -r1.111 code_gen.m
--- compiler/code_gen.m	1 May 2003 22:50:47 -0000	1.111
+++ compiler/code_gen.m	6 May 2003 03:13:33 -0000
@@ -35,6 +35,7 @@
 :- import_module hlds__hlds_module.
 :- import_module hlds__hlds_pred.
 :- import_module ll_backend__code_info.
+:- import_module ll_backend__global_data.
 :- import_module ll_backend__llds.
 
 :- import_module list, io.
@@ -245,7 +246,7 @@
 %---------------------------------------------------------------------------%
 
 generate_proc_code(PredInfo, ProcInfo, ProcId, PredId, ModuleInfo,
-		GlobalData0, GlobalData, Proc) :-
+		!GlobalData, Proc) :-
 	proc_info_interface_determinism(ProcInfo, Detism),
 	proc_info_interface_code_model(ProcInfo, CodeModel),
 	proc_info_goal(ProcInfo, Goal),
@@ -274,15 +275,18 @@
 		% procedures, always needed for model_semi procedures, and
 		% needed for model_non procedures only if we are doing
 		% execution tracing.
+	global_data_get_static_cell_info(!.GlobalData, StaticCellInfo0),
 	code_info__init(SaveSuccip, Globals, PredId, ProcId, PredInfo,
-		ProcInfo, FollowVars, ModuleInfo, OutsideResumePoint,
-		TraceSlotInfo, CodeInfo0),
+		ProcInfo, FollowVars, ModuleInfo, StaticCellInfo0,
+		OutsideResumePoint, TraceSlotInfo, CodeInfo0),
 
 		% Generate code for the procedure.
 	generate_category_code(CodeModel, Goal, OutsideResumePoint,
 		TraceSlotInfo, CodeTree, MaybeTraceCallLabel, FrameInfo,
 		CodeInfo0, CodeInfo),
 	code_info__get_max_reg_in_use_at_trace(MaxTraceReg, CodeInfo, _),
+	code_info__get_static_cell_info(StaticCellInfo, CodeInfo, _),
+	global_data_set_static_cell_info(StaticCellInfo, !GlobalData),
 
 	globals__get_trace_level(Globals, TraceLevel),
 	code_info__get_created_temp_frame(CreatedTempFrame, CodeInfo, _),
@@ -362,18 +366,17 @@
 			InstMap0, TraceSlotInfo, ForceProcId, VarSet, VarTypes,
 			InternalMap, MaybeTableInfo, IsBeingTraced,
 			NeedsAllNames),
-		global_data_add_new_proc_layout(GlobalData0,
-			proc(PredId, ProcId), ProcLayout, GlobalData1)
+		global_data_add_new_proc_layout(proc(PredId, ProcId),
+			ProcLayout, !GlobalData)
 	;
-		GlobalData1 = GlobalData0
+		true
 	),
 
 	code_info__get_closure_layouts(ClosureLayouts, CodeInfo, _),
-	global_data_add_new_closure_layouts(GlobalData1, ClosureLayouts,
-		GlobalData2),
+	global_data_add_new_closure_layouts(ClosureLayouts, !GlobalData),
 	ProcLabel = make_proc_label(ModuleInfo, PredId, ProcId),
 	maybe_add_tabling_pointer_var(ModuleInfo, PredId, ProcId, ProcInfo,
-		ProcLabel, GlobalData2, GlobalData),
+		ProcLabel, !GlobalData),
 
 	pred_info_name(PredInfo, Name),
 	pred_info_arity(PredInfo, Arity),
@@ -416,15 +419,15 @@
 	global_data::in, global_data::out) is det.
 
 maybe_add_tabling_pointer_var(ModuleInfo, PredId, ProcId, ProcInfo, ProcLabel,
-		GlobalData0, GlobalData) :-
+		!GlobalData) :-
 	proc_info_eval_method(ProcInfo, EvalMethod),
 	( eval_method_has_per_proc_tabling_pointer(EvalMethod) = yes ->
 		module_info_name(ModuleInfo, ModuleName),
 		Var = tabling_pointer_var(ModuleName, ProcLabel),
-		global_data_add_new_proc_var(GlobalData0,
-			proc(PredId, ProcId), Var, GlobalData)
+		global_data_add_new_proc_var(proc(PredId, ProcId), Var,
+			!GlobalData)
 	;
-		GlobalData = GlobalData0
+		true
 	).
 
 %---------------------------------------------------------------------------%
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.276
diff -u -b -r1.276 code_info.m
--- compiler/code_info.m	7 May 2003 00:50:20 -0000	1.276
+++ compiler/code_info.m	7 May 2003 00:52:15 -0000
@@ -40,6 +40,7 @@
 :- import_module libs__globals.
 :- import_module libs__trace_params.
 :- import_module ll_backend__continuation_info.
+:- import_module ll_backend__global_data.
 :- import_module ll_backend__llds.
 :- import_module ll_backend__trace.
 :- import_module parse_tree__prog_data.
@@ -88,7 +89,7 @@
 		% stack slots used for tracing purposes.
 :- pred code_info__init(bool::in, globals::in, pred_id::in, proc_id::in,
 	pred_info::in, proc_info::in, follow_vars::in, module_info::in,
-	resume_point_info::out, trace_slot_info::out,
+	static_cell_info::in, resume_point_info::out, trace_slot_info::out,
 	code_info::out) is det.
 
 		% Get the globals table.
@@ -155,9 +156,7 @@
 	code_info::in, code_info::out) is det.
 
 		% Get the global static data structures that have
-		% been created during code generation and which do
-		% not have to be scanned by llds_common, since they
-		% have no common parts by construction.
+		% been created during code generation for closure layouts.
 :- pred code_info__get_closure_layouts(list(comp_gen_c_data)::out,
 	code_info::in, code_info::out) is det.
 
@@ -172,6 +171,12 @@
 :- pred code_info__get_created_temp_frame(bool::out,
 	code_info::in, code_info::out) is det.
 
+:- pred code_info__get_static_cell_info(static_cell_info::out,
+	code_info::in, code_info::out) is det.
+
+:- pred code_info__set_static_cell_info(static_cell_info::in,
+	code_info::in, code_info::out) is det.
+
 %---------------------------------------------------------------------------%
 
 :- implementation.
@@ -363,16 +368,17 @@
 				% are equal to or smaller than this field.
 				% This slot contains -1 if tracing is not
 				% enabled.
-		created_temp_frame:: bool
+		created_temp_frame:: bool,
 				% True iff the procedure has created one or
 				% more temporary nondet frames.
+		static_cell_info :: static_cell_info
 	).
 
 %---------------------------------------------------------------------------%
 
 code_info__init(SaveSuccip, Globals, PredId, ProcId, PredInfo, ProcInfo,
-		FollowVars, ModuleInfo, ResumePoint, TraceSlotInfo,
-		CodeInfo) :-
+		FollowVars, ModuleInfo, StaticCellInfo,
+		ResumePoint, TraceSlotInfo, CodeInfo) :-
 	proc_info_get_initial_instmap(ProcInfo, ModuleInfo, InstMap),
 	proc_info_liveness_info(ProcInfo, Liveness),
 	proc_info_interface_code_model(ProcInfo, CodeModel),
@@ -443,7 +449,8 @@
 			counter__init(1),
 			[],
 			-1,
-			no
+			no,
+			StaticCellInfo
 		)
 	),
 	code_info__init_maybe_trace_info(TraceLevel, Globals, ModuleInfo,
@@ -499,6 +506,8 @@
 	CI, CI).
 code_info__get_created_temp_frame(CI^code_info_persistent^created_temp_frame,
 	CI, CI).
+code_info__get_static_cell_info(CI^code_info_persistent^static_cell_info,
+	CI, CI).
 
 %---------------------------------------------------------------------------%
 
@@ -528,6 +537,8 @@
 	CI^code_info_persistent^max_reg_used := MR).
 code_info__set_created_temp_frame(MR, CI,
 	CI^code_info_persistent^created_temp_frame := MR).
+code_info__set_static_cell_info(SCI, CI,
+	CI^code_info_persistent^static_cell_info := SCI).
 
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
@@ -658,6 +669,12 @@
 :- pred code_info__add_closure_layout(comp_gen_c_data, code_info, code_info).
 :- mode code_info__add_closure_layout(in, in, out) is det.
 
+:- pred code_info__add_static_cell(assoc_list(rval, llds_type)::in,
+	data_addr::out, code_info::in, code_info::out) is det.
+
+:- pred code_info__add_static_cell_natural_types(list(rval)::in,
+	data_addr::out, code_info::in, code_info::out) is det.
+
 %---------------------------------------------------------------------------%
 
 :- implementation.
@@ -900,6 +917,18 @@
 	code_info__get_closure_layouts(ClosureLayouts),
 	code_info__set_closure_layouts([ClosureLayout | ClosureLayouts]).
 
+code_info__add_static_cell(RvalsTypes, DataAddr) -->
+	code_info__get_static_cell_info(StaticCellInfo0),
+	{ add_static_cell(RvalsTypes, DataAddr,
+		StaticCellInfo0, StaticCellInfo) },
+	code_info__set_static_cell_info(StaticCellInfo).
+
+code_info__add_static_cell_natural_types(Rvals, DataAddr) -->
+	code_info__get_static_cell_info(StaticCellInfo0),
+	{ add_static_cell_natural_types(Rvals, DataAddr,
+		StaticCellInfo0, StaticCellInfo) },
+	code_info__set_static_cell_info(StaticCellInfo).
+
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
 
@@ -3154,7 +3183,8 @@
 
 code_info__assign_lval_to_var(Var, Lval, Code) -->
 	code_info__get_var_locn_info(VarLocnInfo0),
-	{ var_locn__assign_lval_to_var(Var, Lval, Code,
+	code_info__get_static_cell_info(StaticCellInfo),
+	{ var_locn__assign_lval_to_var(Var, Lval, StaticCellInfo, Code,
 		VarLocnInfo0, VarLocnInfo) },
 	code_info__set_var_locn_info(VarLocnInfo).
 
@@ -3179,9 +3209,11 @@
 
 code_info__assign_cell_to_var(Var, Ptag, Vector, TypeMsg, Code) -->
 	code_info__get_var_locn_info(VarLocnInfo0),
-	{ var_locn__assign_cell_to_var(Var, Ptag, Vector, TypeMsg,
-		Code, VarLocnInfo0, VarLocnInfo) },
-	code_info__set_var_locn_info(VarLocnInfo).
+	code_info__get_static_cell_info(StaticCellInfo0),
+	{ var_locn__assign_cell_to_var(Var, Ptag, Vector, TypeMsg, Code,
+		StaticCellInfo0, StaticCellInfo, VarLocnInfo0, VarLocnInfo) },
+	code_info__set_var_locn_info(VarLocnInfo),
+	code_info__set_static_cell_info(StaticCellInfo).
 
 code_info__place_var(Var, Lval, Code) -->
 	code_info__get_var_locn_info(VarLocnInfo0),
Index: compiler/code_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_util.m,v
retrieving revision 1.145
diff -u -b -r1.145 code_util.m
--- compiler/code_util.m	1 May 2003 22:50:48 -0000	1.145
+++ compiler/code_util.m	5 May 2003 06:39:15 -0000
@@ -393,7 +393,6 @@
 code_util__lvals_in_rval(lval(Lval), [Lval | Lvals]) :-
 	code_util__lvals_in_lval(Lval, Lvals).
 code_util__lvals_in_rval(var(_), []).
-code_util__lvals_in_rval(create(_, _, _, _, _, _), []).
 code_util__lvals_in_rval(mkword(_, Rval), Lvals) :-
 	code_util__lvals_in_rval(Rval, Lvals).
 code_util__lvals_in_rval(const(_), []).
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.48
diff -u -b -r1.48 continuation_info.m
--- compiler/continuation_info.m	16 Mar 2003 08:01:26 -0000	1.48
+++ compiler/continuation_info.m	6 May 2003 03:44:59 -0000
@@ -58,6 +58,7 @@
 :- import_module hlds__instmap.
 :- import_module libs__globals.
 :- import_module libs__trace_params.
+:- import_module ll_backend__global_data.
 :- import_module ll_backend__llds.
 :- import_module ll_backend__trace.
 :- import_module parse_tree__inst.
@@ -394,10 +395,10 @@
 	global_data::in, global_data::out) is det.
 
 continuation_info__process_proc_llds(PredProcId, Instructions,
-		WantReturnInfo, GlobalData0, GlobalData) :-
+		WantReturnInfo, !GlobalData) :-
 
 		% Get all the continuation info from the call instructions.
-	global_data_get_proc_layout(GlobalData0, PredProcId, ProcLayoutInfo0),
+	global_data_get_proc_layout(!.GlobalData, PredProcId, ProcLayoutInfo0),
 	Internals0 = ProcLayoutInfo0^internal_map,
 	GetCallInfo = lambda([Instr::in, Call::out] is semidet, (
 		Instr = call(Target, label(ReturnLabel), LiveInfo, Context,
@@ -412,8 +413,8 @@
 		Calls, Internals0, Internals),
 
 	ProcLayoutInfo = ProcLayoutInfo0^internal_map := Internals,
-	global_data_update_proc_layout(GlobalData0, PredProcId, ProcLayoutInfo,
-		GlobalData).
+	global_data_update_proc_layout(PredProcId, ProcLayoutInfo,
+		!GlobalData).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/dupelim.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/dupelim.m,v
retrieving revision 1.55
diff -u -b -r1.55 dupelim.m
--- compiler/dupelim.m	1 May 2003 22:50:48 -0000	1.55
+++ compiler/dupelim.m	5 May 2003 06:39:25 -0000
@@ -477,9 +477,6 @@
 		Rval1 = var(_),
 		error("var in standardize_rval")
 	;
-		Rval1 = create(_, _, _, _, _, _),
-		Rval = Rval1
-	;
 		Rval1 = mkword(_, _),
 		Rval = Rval1
 	;
@@ -808,10 +805,6 @@
 	;
 		Rval1 = var(_),
 		error("var in most_specific_rval")
-	;
-		Rval1 = create(_, _, _, _, _, _),
-		Rval2 = Rval1,
-		Rval = Rval1
 	;
 		Rval1 = mkword(_, _),
 		Rval2 = Rval1,
Index: compiler/exprn_aux.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/exprn_aux.m,v
retrieving revision 1.47
diff -u -b -r1.47 exprn_aux.m
--- compiler/exprn_aux.m	1 May 2003 22:50:48 -0000	1.47
+++ compiler/exprn_aux.m	6 May 2003 03:17:04 -0000
@@ -16,10 +16,10 @@
 
 :- type exprn_opts
 	--->	nlg_asm_sgt_ubf(
-			bool,	% --use-non-local-gotos
-			bool,	% --use-asm-labels
-			bool,	% --static-ground-terms
-			bool	% --unboxed-float
+			non_local_gotos		:: bool,
+			asm_labels		:: bool,
+			static_ground_terms	:: bool,
+			unboxed_float		:: bool
 		).
 
 :- pred exprn_aux__init_exprn_opts(option_table::in, exprn_opts::out) is det.
@@ -179,8 +179,6 @@
 
 exprn_aux__rval_contains_lval(lval(Lval0), Lval) :-
 	exprn_aux__lval_contains_lval(Lval0, Lval).
-exprn_aux__rval_contains_lval(create(_, Rvals, _, _, _, Reuse), Lval) :-
-	exprn_aux__args_contain_lval([Reuse | Rvals], Lval).
 exprn_aux__rval_contains_lval(mkword(_, Rval), Lval) :-
 	exprn_aux__rval_contains_lval(Rval, Lval).
 exprn_aux__rval_contains_lval(unop(_, Rval), Lval) :-
@@ -215,19 +213,6 @@
 		fail
 	).
 
-:- pred exprn_aux__args_contain_lval(list(maybe(rval))::in, lval::in)
-	is semidet.
-
-exprn_aux__args_contain_lval([M | Ms], Lval) :-
-	(
-		M = yes(Rval),
-		exprn_aux__rval_contains_lval(Rval, Lval)
-	->
-		true
-	;
-		exprn_aux__args_contain_lval(Ms, Lval)
-	).
-
 %------------------------------------------------------------------------------%
 
 exprn_aux__rval_contains_rval(Rval0, Rval) :-
@@ -238,9 +223,6 @@
 			Rval0 = lval(Lval),
 			exprn_aux__lval_contains_rval(Lval, Rval)
 		;
-			Rval0 = create(_, Rvals, _, _, _, Reuse),
-			exprn_aux__args_contain_rval([Reuse | Rvals], Rval)
-		;
 			Rval0 = mkword(_, Rval1),
 			exprn_aux__rval_contains_rval(Rval1, Rval)
 		;
@@ -280,8 +262,6 @@
 exprn_aux__vars_in_rval(lval(Lval), Vars) :-
 	exprn_aux__vars_in_lval(Lval, Vars).
 exprn_aux__vars_in_rval(var(Var), [Var]).
-exprn_aux__vars_in_rval(create(_, Rvals, _, _, _, Reuse), Vars) :-
-	exprn_aux__vars_in_args([Reuse | Rvals], Vars).
 exprn_aux__vars_in_rval(mkword(_, Rval), Vars) :-
 	exprn_aux__vars_in_rval(Rval, Vars).
 exprn_aux__vars_in_rval(const(_Conts), []).
@@ -328,21 +308,6 @@
 exprn_aux__vars_in_mem_ref(heap_ref(Rval, _Tag, _FieldNum), Vars) :-
 	exprn_aux__vars_in_rval(Rval, Vars).
 
-:- pred exprn_aux__vars_in_args(list(maybe(rval))::in, list(prog_var)::out)
-	is det.
-
-exprn_aux__vars_in_args([], []).
-exprn_aux__vars_in_args([M | Ms], Vars) :-
-	exprn_aux__vars_in_args(Ms, Vars0),
-	(
-		M = yes(Rval)
-	->
-		exprn_aux__vars_in_rval(Rval, Vars1),
-		list__append(Vars1, Vars0, Vars)
-	;
-		Vars = Vars0
-	).
-
 %------------------------------------------------------------------------------%
 
 exprn_aux__substitute_lval_in_lval(OldLval, NewLval, Lval0, Lval) :-
@@ -599,13 +564,6 @@
 		Rval = Rval0,
 		N = N0
 	;
-		Rval0 = create(Tag, Rvals0, ArgTypes, StatDyn, Msg, Reuse0),
-		exprn_aux__substitute_lval_in_args(OldLval, NewLval,
-			Rvals0, Rvals, N0, N1),
-		exprn_aux__substitute_lval_in_arg(OldLval, NewLval,
-			Reuse0, Reuse, N1, N),
-		Rval = create(Tag, Rvals, ArgTypes, StatDyn, Msg, Reuse)
-	;
 		Rval0 = mkword(Tag, Rval1),
 		exprn_aux__substitute_lval_in_rval_count(OldLval, NewLval,
 			Rval1, Rval2, N0, N),
@@ -788,14 +746,6 @@
 			Rval0 = var(_Var),
 			Rval = Rval0
 		;
-			Rval0 = create(Tag, Rvals0, ATs, StatDyn,
-				Msg, Reuse0),
-			exprn_aux__substitute_rval_in_args(OldRval, NewRval,
-				Rvals0, Rvals),
-			exprn_aux__substitute_rval_in_arg(OldRval, NewRval,
-				Reuse0, Reuse),
-			Rval = create(Tag, Rvals, ATs, StatDyn, Msg, Reuse)
-		;
 			Rval0 = mkword(Tag, Rval1),
 			exprn_aux__substitute_rval_in_rval(OldRval, NewRval,
 				Rval1, Rval2),
@@ -989,31 +939,11 @@
 
 exprn_aux__simplify_rval_2(Rval0, Rval) :-
 	(
-		Rval0 = lval(field(MaybeTag, Base, Field)),
-		Base = create(Tag, Args, _, _, _, _),
-		(
-			MaybeTag = yes(Tag)
-		;
-			MaybeTag = no
-		),
-		Field = const(int_const(FieldNum))
-	->
-		list__index0_det(Args, FieldNum, yes(Rval))
-	;
 		Rval0 = lval(field(MaybeTag, Rval1, Num)),
 		exprn_aux__simplify_rval_2(Rval1, Rval2)
 	->
 		Rval = lval(field(MaybeTag, Rval2, Num))
 	;
-		Rval0 = create(Tag, Args0, ArgTypes, StatDyn, Msg, Reuse0),
-		exprn_aux__simplify_args(Args0, Args),
-		exprn_aux__simplify_arg(Reuse0, Reuse),
-		( Args \= Args0
-		; Reuse \= Reuse0
-		)
-	->
-		Rval = create(Tag, Args, ArgTypes, StatDyn, Msg, Reuse)
-	;
 		Rval0 = unop(UnOp, Rval1),
 		exprn_aux__simplify_rval_2(Rval1, Rval2)
 	->
@@ -1060,10 +990,6 @@
 exprn_aux__rval_addrs(lval(Lval), CodeAddrs, DataAddrs) :-
 	exprn_aux__lval_addrs(Lval, CodeAddrs, DataAddrs).
 exprn_aux__rval_addrs(var(_Var), [], []).
-exprn_aux__rval_addrs(create(_, MaybeRvals, _, _, _, Reuse),
-		CodeAddrs, DataAddrs) :-
-	exprn_aux__maybe_rval_list_addrs([Reuse | MaybeRvals],
-		CodeAddrs, DataAddrs).
 exprn_aux__rval_addrs(mkword(_Tag, Rval), CodeAddrs, DataAddrs) :-
 	exprn_aux__rval_addrs(Rval, CodeAddrs, DataAddrs).
 exprn_aux__rval_addrs(const(Const), CodeAddrs, DataAddrs) :-
Index: compiler/jumpopt.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/jumpopt.m,v
retrieving revision 1.65
diff -u -b -r1.65 jumpopt.m
--- compiler/jumpopt.m	1 May 2003 22:50:48 -0000	1.65
+++ compiler/jumpopt.m	5 May 2003 07:14:26 -0000
@@ -792,12 +792,6 @@
 	jumpopt__short_labels_lval(Lval0, Instrmap, Lval).
 jumpopt__short_labels_rval(var(_), _, _) :-
 	error("var rval in jumpopt__short_labels_rval").
-jumpopt__short_labels_rval(
-		create(Tag, Rvals0, ArgTypes, StatDyn, Type, Reuse0),
-		Instrmap,
-		create(Tag, Rvals, ArgTypes, StatDyn, Type, Reuse)) :-
-	jumpopt__short_labels_maybe_rvals(Rvals0, Instrmap, Rvals),
-	jumpopt__short_labels_maybe_rval(Reuse0, Instrmap, Reuse).
 jumpopt__short_labels_rval(mkword(Tag, Rval0), Instrmap,
 		mkword(Tag, Rval)) :-
 	jumpopt__short_labels_rval(Rval0, Instrmap, Rval).
Index: compiler/livemap.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/livemap.m,v
retrieving revision 1.56
diff -u -b -r1.56 livemap.m
--- compiler/livemap.m	1 May 2003 22:50:48 -0000	1.56
+++ compiler/livemap.m	5 May 2003 07:14:38 -0000
@@ -496,8 +496,6 @@
 	),
 	opt_util__lval_access_rvals(Lval, AccessRvals),
 	livemap__make_live_in_rvals(AccessRvals, Live1, Live).
-livemap__make_live_in_rval(create(_, _, _, _, _, _), Live, Live).
-	% All terms inside creates in the optimizer must be static.
 livemap__make_live_in_rval(mkword(_, Rval), Live0, Live) :-
 	livemap__make_live_in_rval(Rval, Live0, Live).
 livemap__make_live_in_rval(const(_), Live, Live).
Index: compiler/ll_backend.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ll_backend.m,v
retrieving revision 1.4
diff -u -b -r1.4 ll_backend.m
--- compiler/ll_backend.m	7 May 2003 00:50:21 -0000	1.4
+++ compiler/ll_backend.m	7 May 2003 00:50:54 -0000
@@ -63,13 +63,14 @@
 % An alternative HLDS->LLDS code generator for fact tables.
 :- include_module fact_table.
 
-%:- module llds_rtti.
+%:- module llds_data.
    :- include_module ll_pseudo_type_info.
    :- include_module layout.
    :- include_module stack_layout.
    :- include_module prog_rep.
    :- include_module static_term.
-%:- end_module llds_rtti.
+   :- include_module global_data.
+%:- end_module llds_data.
 
 % LLDS->LLDS optimization passes.
 :- include_module optimize.
@@ -82,20 +83,10 @@
    :- include_module reassign.
    :- include_module wrap_blocks.
    :- include_module use_local_vars.
-%   :- include_module value_number.
-%      :- include_module vn_block.
-%      :- include_module vn_cost.
-%      :- include_module vn_debug.
-%      :- include_module vn_filter.
-%      :- include_module vn_flush.
-%      :- include_module vn_order.
-%      :- include_module vn_temploc.
-%      :- include_module vn_util.
-%      :- include_module vn_verify.
-%      :- include_module vn_type.
-%      :- include_module vn_table.
-   :- include_module llds_common.
-   :- include_module livemap, basic_block, opt_util, opt_debug.
+   :- include_module livemap.
+   :- include_module basic_block.
+   :- include_module opt_util.
+   :- include_module opt_debug.
                 
 % The LLDS->C output phase.
 :- include_module transform_llds.
Index: compiler/ll_pseudo_type_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ll_pseudo_type_info.m,v
retrieving revision 1.8
diff -u -b -r1.8 ll_pseudo_type_info.m
--- compiler/ll_pseudo_type_info.m	1 May 2003 22:50:48 -0000	1.8
+++ compiler/ll_pseudo_type_info.m	6 May 2003 03:08:09 -0000
@@ -23,6 +23,7 @@
 
 :- interface.
 
+:- import_module ll_backend__global_data.
 :- import_module ll_backend__llds.
 :- import_module parse_tree__prog_data.
 
@@ -41,13 +42,15 @@
 	% quantified type variables of the constructor in question.
 
 :- pred ll_pseudo_type_info__construct_typed_llds_pseudo_type_info((type)::in,
-	int::in, existq_tvars::in, rval::out, llds_type::out) is det.
+	int::in, existq_tvars::in, static_cell_info::in, static_cell_info::out,
+	rval::out, llds_type::out) is det.
 
 	% This is the same as the previous predicate, but does not return
 	% the LLDS type.
 
 :- pred ll_pseudo_type_info__construct_llds_pseudo_type_info((type)::in,
-	int::in, existq_tvars::in, rval::out) is det.
+	int::in, existq_tvars::in, static_cell_info::in, static_cell_info::out,
+	rval::out) is det.
 
 %-----------------------------------------------------------------------------%
 
@@ -59,20 +62,21 @@
 :- import_module std_util, list, bool, int.
 
 ll_pseudo_type_info__construct_llds_pseudo_type_info(Type, NumUnivQTvars,
-		ExistQTvars, Pseudo) :-
+		ExistQTvars, !StaticCellInfo, Pseudo) :-
 	ll_pseudo_type_info__construct_typed_llds_pseudo_type_info(Type,
-		NumUnivQTvars, ExistQTvars, Pseudo, _LldsType).
+		NumUnivQTvars, ExistQTvars, !StaticCellInfo, Pseudo, _LldsType).
 
 ll_pseudo_type_info__construct_typed_llds_pseudo_type_info(Type, NumUnivQTvars,
-		ExistQTvars, PseudoRval, LldsType) :-
+		ExistQTvars, !StaticCellInfo, PseudoRval, LldsType) :-
 	pseudo_type_info__construct_pseudo_type_info(Type, NumUnivQTvars,
 			ExistQTvars, Pseudo),
-	convert_pseudo_type_info(Pseudo, PseudoRval, LldsType).
+	convert_pseudo_type_info(Pseudo, !StaticCellInfo, PseudoRval, LldsType).
 
 :- pred convert_pseudo_type_info(rtti_pseudo_type_info::in,
+	static_cell_info::in, static_cell_info::out,
 	rval::out, llds_type::out) is det.
 
-convert_pseudo_type_info(Pseudo, Rval, LldsType) :-
+convert_pseudo_type_info(Pseudo, !StaticCellInfo, Rval, LldsType) :-
 	(
 		Pseudo = type_var(Int),
 		Rval = const(int_const(Int)),
@@ -85,20 +89,21 @@
 	;
 		Pseudo = plain_pseudo_type_info(RttiTypeCtor, Args),
 		convert_compound_pseudo_type_info(RttiTypeCtor, [], Args,
-			Rval, LldsType)
+			!StaticCellInfo, Rval, LldsType)
 	;
 		Pseudo = var_arity_pseudo_type_info(VarArityId, Args),
 		list__length(Args, Arity),
-		ArityArg = yes(const(int_const(Arity))),
+		ArityArg = const(int_const(Arity)),
 		RttiTypeCtor = var_arity_id_to_rtti_type_ctor(VarArityId),
 		convert_compound_pseudo_type_info(RttiTypeCtor, [ArityArg],
-			Args, Rval, LldsType)
+			Args, !StaticCellInfo, Rval, LldsType)
 	).
 
 :- pred convert_plain_type_info(rtti_type_info::in,
+	static_cell_info::in, static_cell_info::out,
 	rval::out, llds_type::out) is det.
 
-convert_plain_type_info(TypeInfo, Rval, LldsType) :-
+convert_plain_type_info(TypeInfo, !StaticCellInfo, Rval, LldsType) :-
 	(
 		TypeInfo = plain_arity_zero_type_info(RttiTypeCtor),
 		DataAddr = rtti_addr(RttiTypeCtor, type_info(TypeInfo)),
@@ -107,52 +112,55 @@
 	;
 		TypeInfo = plain_type_info(RttiTypeCtor, Args),
 		convert_compound_type_info(RttiTypeCtor, [], Args,
-			Rval, LldsType)
+			!StaticCellInfo, Rval, LldsType)
 	;
 		TypeInfo = var_arity_type_info(VarArityId, Args),
 		list__length(Args, Arity),
-		ArityArg = yes(const(int_const(Arity))),
+		ArityArg = const(int_const(Arity)),
 		RttiTypeCtor = var_arity_id_to_rtti_type_ctor(VarArityId),
-		convert_compound_type_info(RttiTypeCtor, [ArityArg],
-			Args, Rval, LldsType)
+		convert_compound_type_info(RttiTypeCtor, [ArityArg], Args,
+			!StaticCellInfo, Rval, LldsType)
 	).
 
 :- pred convert_compound_pseudo_type_info(rtti_type_ctor::in,
-	list(maybe(rval))::in, list(rtti_maybe_pseudo_type_info)::in,
+	list(rval)::in, list(rtti_maybe_pseudo_type_info)::in,
+	static_cell_info::in, static_cell_info::out,
 	rval::out, llds_type::out) is det.
 
 convert_compound_pseudo_type_info(RttiTypeCtor, ArgRvals0, Args,
-		Rval, LldsType) :-
+		!StaticCellInfo, Rval, LldsType) :-
 	TypeCtorInfoDataAddr = rtti_addr(RttiTypeCtor, type_ctor_info),
-	TypeCtorInfoRval = yes(const(data_addr_const(TypeCtorInfoDataAddr))),
+	TypeCtorInfoRval = const(data_addr_const(TypeCtorInfoDataAddr)),
 	LldsType = data_ptr,
-	list__map((pred(A::in, yes(AR)::out) is det :-
+	list__map_foldl((pred(A::in, AR::out, SCI0::in, SCI::out) is det :-
 		(
 			A = pseudo(PTI),
-			convert_pseudo_type_info(PTI, AR, _LldsType)
+			convert_pseudo_type_info(PTI, SCI0, SCI, AR, _LldsType)
 		;
 			A = plain(TI),
-			convert_plain_type_info(TI, AR, _LldsType)
+			convert_plain_type_info(TI, SCI0, SCI, AR, _LldsType)
 		)
-	), Args, ArgRvals1),
+	), Args, ArgRvals1, !StaticCellInfo),
 	list__append(ArgRvals0, ArgRvals1, ArgRvals),
-	Reuse = no,
-	Rval = create(0, [TypeCtorInfoRval | ArgRvals],
-		uniform(no), must_be_static, "type_info", Reuse).
+	add_static_cell_natural_types([TypeCtorInfoRval | ArgRvals], DataAddr,
+		!StaticCellInfo),
+	Rval = const(data_addr_const(DataAddr)).
 
-:- pred convert_compound_type_info(rtti_type_ctor::in, list(maybe(rval))::in,
-	list(rtti_type_info)::in, rval::out, llds_type::out) is det.
+:- pred convert_compound_type_info(rtti_type_ctor::in, list(rval)::in,
+	list(rtti_type_info)::in, static_cell_info::in, static_cell_info::out,
+	rval::out, llds_type::out) is det.
 
-convert_compound_type_info(RttiTypeCtor, ArgRvals0, Args, Rval, LldsType) :-
+convert_compound_type_info(RttiTypeCtor, ArgRvals0, Args, !StaticCellInfo,
+		Rval, LldsType) :-
 	TypeCtorInfoData =
 		type_info(plain_arity_zero_type_info(RttiTypeCtor)),
 	TypeCtorInfoDataAddr = rtti_addr(RttiTypeCtor, TypeCtorInfoData),
-	TypeCtorInfoRval = yes(const(data_addr_const(TypeCtorInfoDataAddr))),
+	TypeCtorInfoRval = const(data_addr_const(TypeCtorInfoDataAddr)),
 	LldsType = data_ptr,
-	list__map((pred(A::in, yes(AR)::out) is det :-
-		convert_plain_type_info(A, AR, _LldsType)
-	), Args, ArgRvals1),
+	list__map_foldl((pred(A::in, AR::out, SCI0::in, SCI::out) is det :-
+		convert_plain_type_info(A, SCI0, SCI, AR, _LldsType)
+	), Args, ArgRvals1, !StaticCellInfo),
 	list__append(ArgRvals0, ArgRvals1, ArgRvals),
-	Reuse = no,
-	Rval = create(0, [TypeCtorInfoRval | ArgRvals],
-		uniform(no), must_be_static, "type_info", Reuse).
+	add_static_cell_natural_types([TypeCtorInfoRval | ArgRvals],
+		DataAddr, !StaticCellInfo),
+	Rval = const(data_addr_const(DataAddr)).
Index: compiler/llds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds.m,v
retrieving revision 1.293
diff -u -b -r1.293 llds.m
--- compiler/llds.m	1 May 2003 22:50:48 -0000	1.293
+++ compiler/llds.m	7 May 2003 11:39:13 -0000
@@ -49,44 +49,6 @@
 
 %-----------------------------------------------------------------------------%
 
-:- import_module ll_backend__continuation_info.
-
-:- type global_data.
-
-:- pred global_data_init(list(layout_data)::in, global_data::out) is det.
-
-:- pred global_data_add_new_proc_var(global_data::in,
-	pred_proc_id::in, comp_gen_c_var::in, global_data::out) is det.
-
-:- pred global_data_add_new_proc_layout(global_data::in,
-	pred_proc_id::in, proc_layout_info::in, global_data::out) is det.
-
-:- pred global_data_update_proc_layout(global_data::in,
-	pred_proc_id::in, proc_layout_info::in, global_data::out) is det.
-
-:- pred global_data_add_new_closure_layouts(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.
-
-:- pred global_data_get_proc_layout(global_data::in, pred_proc_id::in,
-	proc_layout_info::out) is det.
-
-:- pred global_data_get_all_proc_vars(global_data::in,
-	list(comp_gen_c_var)::out) is det.
-
-:- pred global_data_get_all_proc_layouts(global_data::in,
-	list(proc_layout_info)::out) is det.
-
-:- pred global_data_get_all_closure_layouts(global_data::in,
-	list(comp_gen_c_data)::out) is det.
-
-:- pred global_data_get_all_non_common_static_data(global_data::in,
-	list(comp_gen_c_data)::out) is det.
-
-%-----------------------------------------------------------------------------%
-
 %
 % The type `c_file' is the actual LLDS.
 %
@@ -764,46 +726,6 @@
 		% but should not be present in the LLDS at any
 		% stage after code generation.
 
-	;	create(tag, list(maybe(rval)), create_arg_types,
-			static_or_dynamic, string, maybe(rval))
-		% create(Tag, Arguments, MaybeArgTypes, StaticOrDynamic,
-		%	CellKind, CellToReuse):
-		% A `create' instruction is used during code generation
-		% for creating a term, either on the heap or
-		% (if the term is constant) as a static constant.
-		% After code generation, only constant term create() rvals
-		% should be present in the LLDS, others will get transformed
-		% to incr_hp(..., Tag, Size) plus assignments to the fields.
-		%
-		% MaybeArgTypes may explicitly give the C level types of
-		% the arguments, although usually these types will be implicit.
-		%
-		% StaticOrDynamic may say that the cell must be allocated
-		% dynamically on the heap, because the resulting data structure
-		% must be unique (e.g. if we're doing to do destructive update
-		% on it). It may say that the cell must be allocated
-		% statically, e.g. because the MaybeArgTypes includes
-		% explicitly specified types that differ in size from Word
-		% (the code generator cannot fill in such cells).
-		% Or it may say that this cell can be allocated either way,
-		% subject to other constraints (e.g. a cell cannot be allocated
-		% statically unless all of its components are statically
-		% allocated as well).
-		%
-		% The string argument gives the name of the type constructor
-		% of the function symbol of which this is a cell, for use
-		% in memory profiling.
-		%
-		% The maybe(rval) contains the location of a cell to reuse.
-		% This will always be `no' after code generation.
-		%
-		% For the time being, you must leave the argument types
-		% implicit if the cell is to be unique. This is because
-		% (a) the code generator assumes that each argument of a cell
-		% it creates on the heap is the same size as a Word; (b)
-		% this assumption may be incorrect with explicitly defined
-		% argument types.
-
 	;	mkword(tag, rval)
 		% Given a pointer and a tag, mkword returns a tagged pointer.
 
@@ -817,34 +739,6 @@
 		% The address of a word in the heap, the det stack or
 		% the nondet stack.
 
-:- type static_or_dynamic
-	--->	must_be_static
-	;	can_be_either
-	;	must_be_dynamic.
-
-	% Values of this type specify the C types and therefore the sizes
-	% of the arguments of a create rval.
-	%
-	% If the type is given as yes(LldsType), then the type is the C type
-	% corresponding to LldsType. If the type is given as no, then the
-	% type is implicit; it is what llds_out__rval_type_as_arg says
-	% when given the actual argument.
-:- type create_arg_types
-	--->	uniform(maybe(llds_type))	% All the arguments have
-						% the given C type.
-	;	initial(initial_arg_types, create_arg_types)
-						% Each element of the assoc
-						% list N - T specifies that
-						% the next N arguments have
-						% type T. The types of the
-						% remainder of the arguments
-						% are given by the recursive
-						% create_arg_types.
-	;	none.				% There ought to be no more
-						% arguments.
-
-:- type initial_arg_types == assoc_list(int, maybe(llds_type)).
-
 :- type mem_ref
 	--->	stackvar_ref(int)		% stack slot number
 	;	framevar_ref(int)		% stack slot number
@@ -1008,13 +902,6 @@
 	% given a register, figure out its type
 :- pred llds__register_type(reg_type::in, llds_type::out) is det.
 
-	% check whether the types of all argument are the same size as word
-:- pred llds__all_args_are_word_size(create_arg_types::in, bool::out) is det.
-
-	% check whether an arg of the given type is the same size as word
-	% (floats may be bigger than a word, but if so, they are boxed)
-:- pred llds__type_is_word_size_as_arg(llds_type::in, bool::out) is det.
-
 :- func get_proc_label(label) = proc_label.
 
 :- func get_defining_module_name(proc_label) = module_name.
@@ -1057,9 +944,8 @@
 	llds__lval_type(Lval, Type).
 llds__rval_type(var(_), _) :-
 	error("var unexpected in llds__rval_type").
-llds__rval_type(create(_, _, _, _, _, _), data_ptr).
 	%
-	% Note that create and mkword must both be of type data_ptr,
+	% Note that mkword and data_addr consts must be of type data_ptr,
 	% not of type word, to ensure that static consts containing
 	% them get type `const Word *', not type `Word'; this is
 	% necessary because casts from pointer to int must not be used
@@ -1150,36 +1036,6 @@
 llds__register_type(r, word).
 llds__register_type(f, float).
 
-llds__all_args_are_word_size(uniform(MaybeType), AllWordSize) :-
-	llds__maybe_type_is_word_size(MaybeType, AllWordSize).
-llds__all_args_are_word_size(initial(Init, Rest), AllWordSize) :-
-	assoc_list__values(Init, MaybeTypes),
-	list__map(llds__maybe_type_is_word_size, MaybeTypes, InitWordSizes),
-	llds__all_args_are_word_size(Rest, RestWordSize),
-	bool__and_list([RestWordSize | InitWordSizes], AllWordSize).
-llds__all_args_are_word_size(none, yes).
-
-:- pred llds__maybe_type_is_word_size(maybe(llds_type)::in, bool::out) is det.
-
-llds__maybe_type_is_word_size(no, yes).
-llds__maybe_type_is_word_size(yes(Type), IsWordSize) :-
-	llds__type_is_word_size_as_arg(Type, IsWordSize).
-
-llds__type_is_word_size_as_arg(int_least8,   no).
-llds__type_is_word_size_as_arg(uint_least8,  no).
-llds__type_is_word_size_as_arg(int_least16,  no).
-llds__type_is_word_size_as_arg(uint_least16, no).
-llds__type_is_word_size_as_arg(int_least32,  no).
-llds__type_is_word_size_as_arg(uint_least32, no).
-llds__type_is_word_size_as_arg(bool,         yes).
-llds__type_is_word_size_as_arg(integer,      yes).
-llds__type_is_word_size_as_arg(unsigned,     yes).
-llds__type_is_word_size_as_arg(float,        yes).
-llds__type_is_word_size_as_arg(string,       yes).
-llds__type_is_word_size_as_arg(data_ptr,     yes).
-llds__type_is_word_size_as_arg(code_ptr,     yes).
-llds__type_is_word_size_as_arg(word,         yes).
-
 get_proc_label(exported(ProcLabel)) = ProcLabel.
 get_proc_label(local(ProcLabel)) = ProcLabel.
 get_proc_label(c_local(ProcLabel)) = ProcLabel.
@@ -1187,94 +1043,6 @@
 
 get_defining_module_name(proc(ModuleName, _, _, _, _, _)) = ModuleName.
 get_defining_module_name(special_proc(ModuleName, _, _, _, _, _)) = ModuleName.
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
-
-:- type proc_var_map	==	map(pred_proc_id, comp_gen_c_var).
-:- type proc_layout_map	==	map(pred_proc_id, proc_layout_info).
-
-:- type global_data
-	--->	global_data(
-			proc_var_map		:: proc_var_map,
-						% Information about the global
-						% variables defined by each
-						% procedure.
-			proc_layout_map		:: proc_layout_map,
-						% Information about the
-						% layout structures defined
-						% by each procedure.
-			closure_layouts		:: list(comp_gen_c_data),
-						% The list of all closure
-						% layouts generated in this
-						% module. While all closure
-						% layouts are different from
-						% all other comp_gen_c_datas,
-						% it is possible, although
-						% unlikely, for two closures
-						% to have the same layout.
-			non_common_data		:: list(comp_gen_c_data)
-						% The list of global data
-						% structures that do not need
-						% to be checked by llds_common,
-						% because their construction
-						% ensures no overlaps.
-		).
-
-:- func wrap_layout_data(layout_data) = comp_gen_c_data.
-
-wrap_layout_data(LayoutData) = layout_data(LayoutData).
-
-global_data_init(LayoutData, GlobalData) :-
-	map__init(EmptyDataMap),
-	map__init(EmptyLayoutMap),
-	NonCommon = list__map(wrap_layout_data, LayoutData),
-	GlobalData = global_data(EmptyDataMap, EmptyLayoutMap, [], NonCommon).
-
-global_data_add_new_proc_var(GlobalData0, PredProcId, ProcVar, GlobalData) :-
-	ProcVarMap0 = GlobalData0 ^ proc_var_map,
-	map__det_insert(ProcVarMap0, PredProcId, ProcVar, ProcVarMap),
-	GlobalData = GlobalData0 ^ proc_var_map := ProcVarMap.
-
-global_data_add_new_proc_layout(GlobalData0, PredProcId, ProcLayout,
-		GlobalData) :-
-	ProcLayoutMap0 = GlobalData0 ^ proc_layout_map,
-	map__det_insert(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
-	GlobalData = GlobalData0 ^ proc_layout_map := ProcLayoutMap.
-
-global_data_update_proc_layout(GlobalData0, PredProcId, ProcLayout,
-		GlobalData) :-
-	ProcLayoutMap0 = GlobalData0 ^ proc_layout_map,
-	map__det_update(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
-	GlobalData = GlobalData0 ^ proc_layout_map := ProcLayoutMap.
-
-global_data_add_new_closure_layouts(GlobalData0, NewClosureLayouts,
-		GlobalData) :-
-	ClosureLayouts0 = GlobalData0 ^ closure_layouts,
-	list__append(NewClosureLayouts, ClosureLayouts0, ClosureLayouts),
-	GlobalData = GlobalData0 ^ closure_layouts := ClosureLayouts.
-
-global_data_maybe_get_proc_layout(GlobalData, PredProcId, ProcLayout) :-
-	ProcLayoutMap = GlobalData ^ proc_layout_map,
-	map__search(ProcLayoutMap, PredProcId, ProcLayout).
-
-global_data_get_proc_layout(GlobalData, PredProcId, ProcLayout) :-
-	ProcLayoutMap = GlobalData ^ proc_layout_map,
-	map__lookup(ProcLayoutMap, PredProcId, ProcLayout).
-
-global_data_get_all_proc_vars(GlobalData, ProcVars) :-
-	ProcVarMap = GlobalData ^ proc_var_map,
-	map__values(ProcVarMap, ProcVars).
-
-global_data_get_all_proc_layouts(GlobalData, ProcLayouts) :-
-	ProcLayoutMap = GlobalData ^ proc_layout_map,
-	map__values(ProcLayoutMap, ProcLayouts).
-
-global_data_get_all_closure_layouts(GlobalData, ClosureLayouts) :-
-	ClosureLayouts = GlobalData ^ closure_layouts.
-
-global_data_get_all_non_common_static_data(GlobalData, NonCommonStatics) :-
-	NonCommonStatics = GlobalData ^ non_common_data.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.212
diff -u -b -r1.212 llds_out.m
--- compiler/llds_out.m	7 May 2003 03:21:39 -0000	1.212
+++ compiler/llds_out.m	7 May 2003 03:44:26 -0000
@@ -2194,9 +2194,6 @@
 	    { N = N2 },
 	    { DeclSet = DeclSet2 }
 	).
-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,
@@ -3411,9 +3408,6 @@
 	;
 		output_lval(Lval)
 	).
-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)) -->
Index: compiler/lookup_switch.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/lookup_switch.m,v
retrieving revision 1.47
diff -u -b -r1.47 lookup_switch.m
--- compiler/lookup_switch.m	7 May 2003 00:50:21 -0000	1.47
+++ compiler/lookup_switch.m	7 May 2003 00:50:54 -0000
@@ -83,6 +83,7 @@
 :- import_module ll_backend__code_gen.
 :- import_module ll_backend__dense_switch.
 :- import_module ll_backend__exprn_aux.
+:- import_module ll_backend__global_data.
 :- import_module parse_tree__prog_data.
 
 :- import_module int, require, bool, assoc_list.
@@ -266,15 +267,6 @@
 	lookup_switch__rval_is_constant(Exprn1, ExprnOpts).
 lookup_switch__rval_is_constant(mkword(_, Exprn0), ExprnOpts) :-
 	lookup_switch__rval_is_constant(Exprn0, ExprnOpts).
-lookup_switch__rval_is_constant(create(_, Args, _, StatDyn, _, _),
-		ExprnOpts) :-
-	(
-		StatDyn = must_be_static
-	;
-		ExprnOpts = nlg_asm_sgt_ubf(_, _, StaticGroundTerms, _),
-		StaticGroundTerms = yes,
-		lookup_switch__rvals_are_constant(Args, ExprnOpts)
-	).
 
 :- pred lookup_switch__rvals_are_constant(list(maybe(rval))::in,
 	exprn_opts::in) is semidet.
@@ -359,7 +351,7 @@
 lookup_switch__generate_bitvec_test(Index, CaseVals, Start, _End,
 		CheckCode) -->
 	lookup_switch__get_word_bits(WordBits, Log2WordBits),
-	{ generate_bit_vec(CaseVals, Start, WordBits, BitVec) },
+	generate_bit_vec(CaseVals, Start, WordBits, BitVecArgs, BitVecRval),
 
 		%
 		% Optimize the single-word case:
@@ -369,9 +361,7 @@
 		% of the index specify which word to use and the
 		% low bits specify which bit.
 		%
-	{
-		BitVec = create(_, [yes(SingleWord)], _, _, _, _)
-	->
+	{ BitVecArgs = [SingleWord] ->
 		Word = SingleWord,
 		BitNum = Index
 	;
@@ -380,7 +370,7 @@
 		% except that it can generate more efficient code.
 		WordNum = binop(>>, Index, const(int_const(Log2WordBits))),
 
-		Word = lval(field(yes(0), BitVec, WordNum)),
+		Word = lval(field(yes(0), BitVecRval, WordNum)),
 
 		% This is the same as
 		% BitNum = binop(mod, Index, const(int_const(WordBits)))
@@ -416,47 +406,43 @@
 log2_rounded_down(X) = Log :-
 	int__log2(X + 1, Log + 1).  % int__log2 rounds up
 
-:- pred generate_bit_vec(case_consts::in, int::in, int::in, rval::out) is det.
+:- pred generate_bit_vec(case_consts::in, int::in, int::in,
+	list(rval)::out, rval::out, code_info::in, code_info::out) is det.
 
 	% we generate the bitvector by iterating through the cases
 	% marking the bit for each case. (We represent the bitvector
 	% here as a map from the word number in the vector to the bits
 	% for that word.
-generate_bit_vec(CaseVals, Start, WordBits, BitVec) :-
+generate_bit_vec(CaseVals, Start, WordBits, Args, BitVec, !CodeInfo) :-
 	map__init(Empty),
 	generate_bit_vec_2(CaseVals, Start, WordBits, Empty, BitMap),
 	map__to_assoc_list(BitMap, WordVals),
 	generate_bit_vec_args(WordVals, 0, Args),
-	Reuse = no,
-	BitVec = create(0, Args, uniform(no), must_be_static,
-		"lookup_switch_bit_vector", Reuse).
+	add_static_cell_natural_types(Args, DataAddr, !CodeInfo),
+	BitVec = const(data_addr_const(DataAddr)).
 
 :- pred generate_bit_vec_2(case_consts::in, int::in, int::in,
 	map(int, int)::in, map(int, int)::out) is det.
 
 generate_bit_vec_2([], _, _, Bits, Bits).
 generate_bit_vec_2([Tag - _ | Rest], Start, WordBits, Bits0, Bits) :-
-	Val is Tag - Start,
-	Word is Val // WordBits,
-	Offset is Val mod WordBits,
-	(
-		map__search(Bits0, Word, X0)
-	->
-		X1 is X0 \/ (1 << Offset)
+	Val = Tag - Start,
+	Word = Val // WordBits,
+	Offset = Val mod WordBits,
+	( map__search(Bits0, Word, X0) ->
+		X1 = X0 \/ (1 << Offset)
 	;
-		X1 is (1 << Offset)
+		X1 = (1 << Offset)
 	),
 	map__set(Bits0, Word, X1, Bits1),
 	generate_bit_vec_2(Rest, Start, WordBits, Bits1, Bits).
 
 :- pred generate_bit_vec_args(list(pair(int))::in, int::in,
-	list(maybe(rval))::out) is det.
+	list(rval)::out) is det.
 
 generate_bit_vec_args([], _, []).
-generate_bit_vec_args([Word - Bits | Rest], Count, [yes(Rval) | Rvals]) :-
-	(
-		Count < Word
-	->
+generate_bit_vec_args([Word - Bits | Rest], Count, [Rval | Rvals]) :-
+	( Count < Word ->
 		WordVal = 0,
 		Remainder = [Word - Bits | Rest]
 	;
@@ -464,7 +450,7 @@
 		Remainder = Rest
 	),
 	Rval = const(int_const(WordVal)),
-	Count1 is Count + 1,
+	Count1 = Count + 1,
 	generate_bit_vec_args(Remainder, Count1, Rvals).
 
 %------------------------------------------------------------------------------%
@@ -491,23 +477,20 @@
 	{ map__lookup(Map, Var, Vals0) },
 	{ list__sort(Vals0, Vals) },
 	{ construct_args(Vals, 0, Args) },
-	{ Reuse = no },
-	{ ArrayTerm = create(0, Args, uniform(no), must_be_static,
-		"lookup_switch_data", Reuse) },
+	code_info__add_static_cell_natural_types(Args, DataAddr),
+	{ ArrayTerm = const(data_addr_const(DataAddr)) },
 	{ LookupLval = field(yes(0), ArrayTerm, Index) },
 	code_info__assign_lval_to_var(Var, LookupLval, Code),
 	{ require(tree__is_empty(Code),
 		"lookup_switch__generate_terms_2: nonempty code") },
 	lookup_switch__generate_terms_2(Index, Vars, Map).
 
-:- pred construct_args(list(pair(int, rval))::in, int::in,
-	list(maybe(rval))::out) is det.
+:- pred construct_args(list(pair(int, rval))::in, int::in, list(rval)::out)
+	is det.
 
 construct_args([], _, []).
-construct_args([Index - Rval | Rest], Count0, [yes(Arg) | Args]) :-
-	(
-		Count0 < Index
-	->
+construct_args([Index - Rval | Rest], Count0, [Arg | Args]) :-
+	( Count0 < Index ->
 		% If this argument (array element) is a place-holder and
 		% will never be referenced, just fill it in with a `0'
 		Arg = const(int_const(0)),
@@ -516,7 +499,7 @@
 		Arg = Rval,
 		Remainder = Rest
 	),
-	Count1 is Count0 + 1,
+	Count1 = Count0 + 1,
 	construct_args(Remainder, Count1, Args).
 
 %------------------------------------------------------------------------------%
@@ -531,7 +514,7 @@
 rearrange_vals(_Vars, [], _Start, Map, Map).
 rearrange_vals(Vars, [Tag - Rvals | Rest], Start, Map0, Map) :-
 	assoc_list__from_corresponding_lists(Vars, Rvals, Pairs),
-	Index is Tag - Start,
+	Index = Tag - Start,
 	rearrange_vals_2(Pairs, Index, Map0, Map1),
 	rearrange_vals(Vars, Rest, Start, Map1, Map).
 
@@ -540,9 +523,7 @@
 
 rearrange_vals_2([], _, Map, Map).
 rearrange_vals_2([Var - Rval | Rest], Tag, Map0, Map) :-
-	(
-		map__search(Map0, Var, Vals0)
-	->
+	( map__search(Map0, Var, Vals0) ->
 		Vals = [Tag - Rval | Vals0]
 	;
 		Vals = [Tag - Rval]
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.285
diff -u -b -r1.285 mercury_compile.m
--- compiler/mercury_compile.m	1 May 2003 22:50:49 -0000	1.285
+++ compiler/mercury_compile.m	6 May 2003 03:06:42 -0000
@@ -92,11 +92,11 @@
 :- import_module ll_backend__store_alloc.
 :- import_module ll_backend__code_gen.
 :- import_module ll_backend__optimize.
-:- import_module ll_backend__llds_common.
 :- import_module ll_backend__transform_llds.
 :- import_module ll_backend__llds_out.
 :- import_module ll_backend__continuation_info.
 :- import_module ll_backend__stack_layout.
+:- import_module ll_backend__global_data.
 :- import_module backend_libs__foreign.
 :- import_module backend_libs__export.
 :- import_module backend_libs__base_typeclass_info.
@@ -2234,7 +2234,13 @@
 
 mercury_compile__backend_pass(HLDS50, HLDS, DeepProfilingStructures,
 		GlobalData, LLDS) -->
-	{ global_data_init(DeepProfilingStructures, GlobalData0) },
+	{ module_info_name(HLDS50, ModuleName) },
+	globals__io_lookup_bool_option(unboxed_float, UnboxFloat),
+	globals__io_lookup_bool_option(common_data, DoCommonData),
+	{ StaticCellInfo0 = init_static_cell_info(ModuleName, UnboxFloat,
+		DoCommonData) },
+	{ global_data_init(DeepProfilingStructures, StaticCellInfo0,
+		GlobalData0) },
 
 	globals__io_lookup_bool_option(verbose, Verbose),
 	globals__io_lookup_bool_option(statistics, Stats),
@@ -3500,7 +3506,7 @@
 	io__state, io__state).
 :- mode mercury_compile__output_pass(in, in, in, in, in, out, di, uo) is det.
 
-mercury_compile__output_pass(HLDS0, GlobalData, Procs0, MaybeRLFile,
+mercury_compile__output_pass(HLDS, GlobalData0, Procs, MaybeRLFile,
 		ModuleName, CompileErrors) -->
 	globals__io_lookup_bool_option(verbose, Verbose),
 	globals__io_lookup_bool_option(statistics, Stats),
@@ -3511,12 +3517,12 @@
 	% XXX this should perhaps be part of backend_pass
 	% rather than output_pass.
 	%
-	{ type_ctor_info__generate_rtti(HLDS0, TypeCtorRttiData) },
-	{ base_typeclass_info__generate_rtti(HLDS0, TypeClassInfoRttiData) },
+	{ type_ctor_info__generate_rtti(HLDS, TypeCtorRttiData) },
+	{ base_typeclass_info__generate_rtti(HLDS, TypeClassInfoRttiData) },
 	{ list__map(llds__wrap_rtti_data, TypeCtorRttiData, TypeCtorTables) },
 	{ list__map(llds__wrap_rtti_data, TypeClassInfoRttiData,
 		TypeClassInfos) },
-	{ stack_layout__generate_llds(HLDS0, HLDS, GlobalData,
+	{ stack_layout__generate_llds(HLDS, GlobalData0, GlobalData,
 		StackLayouts, LayoutLabels) },
 	%
 	% Here we perform some optimizations on the LLDS data.
@@ -3526,22 +3532,18 @@
 	% XXX We assume that the foreign language we use is C
 	{ get_c_interface_info(HLDS, c, C_InterfaceInfo) },
 	{ global_data_get_all_proc_vars(GlobalData, GlobalVars) },
-	{ global_data_get_all_non_common_static_data(GlobalData,
-		NonCommonStaticData) },
+	{ global_data_get_all_deep_prof_data(GlobalData, DeepProfData) },
 	{ global_data_get_all_closure_layouts(GlobalData, ClosureLayouts) },
-	{ 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) },
+	{ global_data_get_static_cell_info(GlobalData, StaticCellInfo) },
+	{ StaticCells = get_static_cells(StaticCellInfo) },
 
 	%
 	% Next we put it all together and output it to one or more C files.
 	%
-	{ list__condense([CommonableData, NonCommonStaticData,
-		TypeCtorTables, TypeClassInfos], AllData) },
+	{ list__condense([StaticCells, ClosureLayouts, StackLayouts,
+		DeepProfData, TypeCtorTables, TypeClassInfos], AllData) },
 	mercury_compile__construct_c_file(HLDS, C_InterfaceInfo,
-		Procs1, GlobalVars, AllData, CFile, NumChunks),
+		Procs, GlobalVars, AllData, CFile, NumChunks),
 	mercury_compile__output_llds(ModuleName, CFile, LayoutLabels,
 		MaybeRLFile, Verbose, Stats),
 
Index: compiler/middle_rec.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/middle_rec.m,v
retrieving revision 1.93
diff -u -b -r1.93 middle_rec.m
--- compiler/middle_rec.m	1 May 2003 22:50:49 -0000	1.93
+++ compiler/middle_rec.m	5 May 2003 07:18:47 -0000
@@ -504,10 +504,6 @@
 		Rval = var(_),
 		error("var found in middle_rec__find_used_registers_rval")
 	;
-		Rval = create(_, MaybeRvals, _, _, _, Reuse),
-		middle_rec__find_used_registers_maybe_rvals(
-			[Reuse | MaybeRvals], Used0, Used)
-	;
 		Rval = mkword(_, Rval1),
 		middle_rec__find_used_registers_rval(Rval1, Used0, Used)
 	;
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.129
diff -u -b -r1.129 opt_debug.m
--- compiler/opt_debug.m	1 May 2003 22:50:49 -0000	1.129
+++ compiler/opt_debug.m	5 May 2003 07:18:53 -0000
@@ -267,21 +267,6 @@
 opt_debug__dump_rval(const(C), Str) :-
 	opt_debug__dump_const(C, C_str),
 	string__append_list(["const(", C_str, ")"], Str).
-opt_debug__dump_rval(create(T, MA, _, U, _, _), Str) :-
-	string__int_to_string(T, T_str),
-	opt_debug__dump_maybe_rvals(MA, 3, MA_str),
-	(
-		U = must_be_static,
-		U_str = "static"
-	;
-		U = can_be_either,
-		U_str = "either"
-	;
-		U = must_be_dynamic,
-		U_str = "dynamic"
-	),
-	string__append_list(["create(", T_str, ", ", MA_str, ", ",
-		U_str, ")"], Str).
 opt_debug__dump_rval(unop(O, N), Str) :-
 	opt_debug__dump_unop(O, O_str),
 	opt_debug__dump_rval(N, N_str),
Index: compiler/opt_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/opt_util.m,v
retrieving revision 1.119
diff -u -b -r1.119 opt_util.m
--- compiler/opt_util.m	1 May 2003 22:50:49 -0000	1.119
+++ compiler/opt_util.m	5 May 2003 21:54:03 -0000
@@ -687,8 +687,6 @@
 	opt_util__lval_refers_stackvars(Lval, Refers).
 opt_util__rval_refers_stackvars(var(_), _) :-
 	error("found var in rval_refers_stackvars").
-opt_util__rval_refers_stackvars(create(_, Rvals, _, _, _, _), Refers) :-
-	opt_util__rvals_refer_stackvars(Rvals, Refers).
 opt_util__rval_refers_stackvars(mkword(_, Rval), Refers) :-
 	opt_util__rval_refers_stackvars(Rval, Refers).
 opt_util__rval_refers_stackvars(const(_), no).
@@ -701,6 +699,7 @@
 opt_util__rval_refers_stackvars(mem_addr(MemRef), Refers) :-
 	opt_util__mem_ref_refers_stackvars(MemRef, Refers).
 
+% XXX probably unused
 opt_util__rvals_refer_stackvars([], no).
 opt_util__rvals_refer_stackvars([MaybeRval | Tail], Refers) :-
 	(
@@ -1588,7 +1587,6 @@
 opt_util__touches_nondet_ctrl_rval(lval(Lval), Touch) :-
 	opt_util__touches_nondet_ctrl_lval(Lval, Touch).
 opt_util__touches_nondet_ctrl_rval(var(_), no).
-opt_util__touches_nondet_ctrl_rval(create(_, _, _, _, _, _), no).
 opt_util__touches_nondet_ctrl_rval(mkword(_, Rval), Touch) :-
 	opt_util__touches_nondet_ctrl_rval(Rval, Touch).
 opt_util__touches_nondet_ctrl_rval(const(_), no).
@@ -1670,7 +1668,6 @@
 	opt_util__rvals_free_of_lval(Rvals, Forbidden).
 opt_util__rval_free_of_lval(var(_), _) :-
 	error("found var in opt_util__rval_free_of_lval").
-opt_util__rval_free_of_lval(create(_, _, _, _, _, _), _).
 opt_util__rval_free_of_lval(mkword(_, Rval), Forbidden) :-
 	opt_util__rval_free_of_lval(Rval, Forbidden).
 opt_util__rval_free_of_lval(const(_), _).
@@ -2004,9 +2001,6 @@
 opt_util__replace_labels_rval(lval(Lval0), ReplMap, lval(Lval)) :-
 	opt_util__replace_labels_lval(Lval0, ReplMap, Lval).
 opt_util__replace_labels_rval(var(Var), _, var(Var)).
-opt_util__replace_labels_rval(
-		create(Tag, Rvals, ArgTypes, StatDyn, Msg, Reuse), _,
-		create(Tag, Rvals, ArgTypes, StatDyn, Msg, Reuse)).
 opt_util__replace_labels_rval(mkword(Tag, Rval0), ReplMap,
 		mkword(Tag, Rval)) :-
 	opt_util__replace_labels_rval(Rval0, ReplMap, Rval).
Index: compiler/optimize.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/optimize.m,v
retrieving revision 1.36
diff -u -b -r1.36 optimize.m
--- compiler/optimize.m	16 Mar 2003 08:01:30 -0000	1.36
+++ compiler/optimize.m	6 May 2003 03:14:12 -0000
@@ -14,6 +14,7 @@
 
 :- interface.
 
+:- import_module ll_backend__global_data.
 :- import_module ll_backend__llds.
 
 :- import_module io, list.
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.80
diff -u -b -r1.80 stack_layout.m
--- compiler/stack_layout.m	1 May 2003 22:50:49 -0000	1.80
+++ compiler/stack_layout.m	6 May 2003 03:08:00 -0000
@@ -16,9 +16,7 @@
 %
 % The tables we generate are mostly of (Mercury) types defined in layout.m,
 % which are turned into C code (global variable declarations and
-% initializations) by layout_out.m. However, these data structures also have
-% a number of `create' rvals within them; llds_common.m converts these into
-% static data structures.
+% initializations) by layout_out.m.
 % 
 % The C types of the structures we generate are defined and documented in
 % runtime/mercury_stack_layout.h. 
@@ -32,19 +30,21 @@
 :- import_module backend_libs__proc_label.
 :- import_module hlds__hlds_module.
 :- import_module ll_backend__continuation_info.
+:- import_module ll_backend__global_data.
 :- import_module ll_backend__llds.
 :- import_module parse_tree__prog_data.
 
-:- import_module std_util, list, map.
+:- import_module list, assoc_list, map.
 
-:- pred stack_layout__generate_llds(module_info::in, module_info::out,
-	global_data::in, list(comp_gen_c_data)::out,
-	map(label, data_addr)::out) is det.
+:- pred stack_layout__generate_llds(module_info::in,
+	global_data::in, global_data::out,
+	list(comp_gen_c_data)::out, 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,
-	string::in, int::in, string::in, list(maybe(rval))::out,
-	create_arg_types::out, comp_gen_c_data::out) is det.
+	string::in, int::in, string::in,
+	static_cell_info::in, static_cell_info::out,
+	assoc_list(rval, llds_type)::out, comp_gen_c_data::out) is det.
 
 	% Construct a representation of a variable location as a 32-bit
 	% integer.
@@ -72,7 +72,7 @@
 :- import_module parse_tree__prog_out.
 :- import_module parse_tree__prog_util.
 
-:- import_module assoc_list, bool, char, string, int, require.
+:- import_module std_util, bool, char, string, int, require.
 :- import_module map, term, set, varset.
 
 %---------------------------------------------------------------------------%
@@ -80,9 +80,8 @@
 	% Process all the continuation information stored in the HLDS,
 	% converting it into LLDS data structures.
 
-stack_layout__generate_llds(ModuleInfo0, ModuleInfo, GlobalData, Layouts,
-		LayoutLabels) :-
-	global_data_get_all_proc_layouts(GlobalData, ProcLayoutList0),
+stack_layout__generate_llds(ModuleInfo0, !GlobalData, Layouts, LayoutLabels) :-
+	global_data_get_all_proc_layouts(!.GlobalData, ProcLayoutList0),
 	list__filter(stack_layout__valid_proc_layout, ProcLayoutList0,
 		ProcLayoutList),
 
@@ -99,16 +98,16 @@
 	map__init(StringMap0),
 	map__init(LabelTables0),
 	StringTable0 = string_table(StringMap0, [], 0),
+	global_data_get_static_cell_info(!.GlobalData, StaticCellInfo0),
 	LayoutInfo0 = stack_layout_info(ModuleInfo0,
 		AgcLayout, TraceLayout, ProcIdLayout,
 		StaticCodeAddr, [], [], [], LayoutLabels0, [],
-		StringTable0, LabelTables0, map__init),
+		StringTable0, LabelTables0, map__init, StaticCellInfo0),
 	stack_layout__lookup_string_in_table("", _, LayoutInfo0, LayoutInfo1),
 	stack_layout__lookup_string_in_table("<too many variables>", _,
 		LayoutInfo1, LayoutInfo2),
 	list__foldl(stack_layout__construct_layouts, ProcLayoutList,
 		LayoutInfo2, LayoutInfo),
-	ModuleInfo = LayoutInfo ^ module_info,
 	TableIoDecls = LayoutInfo ^ table_infos,
 	ProcLayouts = LayoutInfo ^ proc_layouts,
 	InternalLayouts = LayoutInfo ^ internal_layouts,
@@ -116,6 +115,8 @@
 	ProcLayoutNames = LayoutInfo ^ proc_layout_name_list,
 	StringTable = LayoutInfo ^ string_table,
 	LabelTables = LayoutInfo ^ label_tables,
+	global_data_set_static_cell_info(LayoutInfo ^ static_cell_info,
+		!GlobalData),
 	StringTable = string_table(_, RevStringList, StringOffset),
 	list__reverse(RevStringList, StringList),
 	stack_layout__concat_string_list(StringList, StringOffset,
@@ -521,8 +522,11 @@
 		{ MaybeTableInfo = no }
 	;
 		{ MaybeTableInfo = yes(TableInfo) },
-		stack_layout__make_table_data(RttiProcLabel, Kind,
-			TableInfo, TableData),
+		stack_layout__get_static_cell_info(StaticCellInfo0),
+		{ stack_layout__make_table_data(RttiProcLabel, Kind,
+			TableInfo, TableData,
+			StaticCellInfo0, StaticCellInfo) },
+		stack_layout__set_static_cell_info(StaticCellInfo),
 		stack_layout__add_table_data(TableData)
 	).
 
@@ -536,34 +540,38 @@
 stack_layout__construct_trace_layout(RttiProcLabel, EvalMethod, MaybeCallLabel,
 		MaxTraceReg, HeadVars, MaybeGoal, InstMap, TraceSlotInfo,
 		VarSet, VarTypes, UsedVarNameMap, MaybeTableInfo,
-		NeedsAllNames, ExecTrace) -->
+		NeedsAllNames, ExecTrace, !Info) :-
 	stack_layout__construct_var_name_vector(VarSet, UsedVarNameMap,
-		NeedsAllNames, MaxVarNum, VarNameVector),
-	{ list__map(term__var_to_int, HeadVars, HeadVarNumVector) },
+		NeedsAllNames, MaxVarNum, VarNameVector, !Info),
+	list__map(term__var_to_int, HeadVars, HeadVarNumVector),
 	(
-		{ MaybeGoal = no },
-		{ MaybeProcRepRval = no }
+		MaybeGoal = no,
+		MaybeProcRepRval = no
 	;
-		{ MaybeGoal = yes(Goal) },
-		stack_layout__get_module_info(ModuleInfo),
-		{ prog_rep__represent_proc(HeadVars, Goal, InstMap, VarTypes,
-			ModuleInfo, ProcRep) },
-		{ type_to_univ(ProcRep, ProcRepUniv) },
-		{ static_term__term_to_rval(ProcRepUniv, MaybeProcRepRval) }
+		MaybeGoal = yes(Goal),
+		ModuleInfo = !.Info ^ module_info,
+		prog_rep__represent_proc(HeadVars, Goal, InstMap, VarTypes,
+			ModuleInfo, ProcRep),
+		type_to_univ(ProcRep, ProcRepUniv),
+		StaticCellInfo0 = !.Info ^ static_cell_info,
+		static_term__term_to_rval(ProcRepUniv, ProcRepRval,
+			StaticCellInfo0, StaticCellInfo),
+		MaybeProcRepRval = yes(ProcRepRval),
+		!:Info = !.Info ^ static_cell_info := StaticCellInfo
 	),
-	{
+	(
 		MaybeCallLabel = yes(CallLabelPrime),
 		CallLabel = CallLabelPrime
 	;
 		MaybeCallLabel = no,
 		error("stack_layout__construct_trace_layout: call label not present")
-	},
-	{ TraceSlotInfo = trace_slot_info(MaybeFromFullSlot,
+	),
+	TraceSlotInfo = trace_slot_info(MaybeFromFullSlot,
 		MaybeIoSeqSlot, MaybeTrailSlots, MaybeMaxfrSlot,
-		MaybeCallTableSlot) },
+		MaybeCallTableSlot),
 		% The label associated with an event must have variable info.
-	{ CallLabelLayout = label_layout(CallLabel, label_has_var_info) },
-	{
+	CallLabelLayout = label_layout(CallLabel, label_has_var_info),
+	(
 		MaybeTableInfo = no,
 		MaybeTableName = no
 	;
@@ -575,12 +583,12 @@
 			TableInfo = table_gen_info(_, _, _, _),
 			MaybeTableName = yes(table_gen_info(RttiProcLabel))
 		)
-	},
-	{ ExecTrace = proc_layout_exec_trace(CallLabelLayout, MaybeProcRepRval,
+	),
+	ExecTrace = proc_layout_exec_trace(CallLabelLayout, MaybeProcRepRval,
 		MaybeTableName, HeadVarNumVector, VarNameVector,
 		MaxVarNum, MaxTraceReg, MaybeFromFullSlot, MaybeIoSeqSlot,
 		MaybeTrailSlots, MaybeMaxfrSlot, EvalMethod,
-		MaybeCallTableSlot) }.
+		MaybeCallTableSlot).
 
 :- pred stack_layout__construct_var_name_vector(prog_varset::in,
 	map(int, string)::in, bool::in, int::out, list(int)::out,
@@ -771,39 +779,39 @@
 	rval::out, stack_layout_info::in, stack_layout_info::out) is det.
 
 stack_layout__construct_livelval_rvals(LiveLvalSet, TVarLocnMap, EncodedLength,
-		LiveValRval, NamesRval, TypeParamRval) -->
-	{ set__to_sorted_list(LiveLvalSet, LiveLvals) },
-	{ stack_layout__sort_livevals(LiveLvals, SortedLiveLvals) },
+		LiveValRval, NamesRval, TypeParamRval, !Info) :-
+	set__to_sorted_list(LiveLvalSet, LiveLvals),
+	stack_layout__sort_livevals(LiveLvals, SortedLiveLvals),
 	stack_layout__construct_liveval_arrays(SortedLiveLvals,
-		EncodedLength, LiveValRval, NamesRval),
-	{ stack_layout__construct_tvar_vector(TVarLocnMap,
-		TypeParamRval) }.
+		EncodedLength, LiveValRval, NamesRval, !Info),
+	StaticCellInfo0 = !.Info ^ static_cell_info,
+	stack_layout__construct_tvar_vector(TVarLocnMap,
+		TypeParamRval, StaticCellInfo0, StaticCellInfo),
+	!:Info = !.Info ^ static_cell_info := StaticCellInfo.
 
 :- pred stack_layout__construct_tvar_vector(map(tvar, set(layout_locn))::in,
-	rval::out) is det.
+	rval::out, static_cell_info::in, static_cell_info::out) is det.
 
-stack_layout__construct_tvar_vector(TVarLocnMap, TypeParamRval) :-
+stack_layout__construct_tvar_vector(TVarLocnMap, TypeParamRval,
+		!StaticCellInfo) :-
 	( map__is_empty(TVarLocnMap) ->
 		TypeParamRval = const(int_const(0))
 	;
-		stack_layout__construct_tvar_rvals(TVarLocnMap,
-			Vector, VectorTypes),
-		Reuse = no,
-		TypeParamRval = create(0, Vector, VectorTypes, must_be_static,
-			"stack_layout_type_param_locn_vector", Reuse)
+		stack_layout__construct_tvar_rvals(TVarLocnMap, Vector),
+		add_static_cell(Vector, DataAddr, !StaticCellInfo),
+		TypeParamRval = const(data_addr_const(DataAddr))
 	).
 
 :- pred stack_layout__construct_tvar_rvals(map(tvar, set(layout_locn))::in,
-	list(maybe(rval))::out, create_arg_types::out) is det.
+	assoc_list(rval, llds_type)::out) is det.
 
-stack_layout__construct_tvar_rvals(TVarLocnMap, Vector, VectorTypes) :-
+stack_layout__construct_tvar_rvals(TVarLocnMap, Vector) :-
 	map__to_assoc_list(TVarLocnMap, TVarLocns),
 	stack_layout__construct_type_param_locn_vector(TVarLocns, 1,
 		TypeParamLocs),
 	list__length(TypeParamLocs, TypeParamsLength),
 	LengthRval = const(int_const(TypeParamsLength)),
-	Vector = [yes(LengthRval) | TypeParamLocs],
-	VectorTypes = uniform(yes(uint_least32)).
+	Vector = [LengthRval - uint_least32 | TypeParamLocs].
 
 %---------------------------------------------------------------------------%
 
@@ -835,8 +843,7 @@
 	% debugger somewhat easier, the sorting of the named var block makes
 	% the output of the debugger look nicer, and the sorting of the both
 	% blocks makes it more likely that different labels' layout structures
-	% will have common parts (e.g. name vectors) that can be optimized
-	% by llds_common.m.
+	% will have common parts (e.g. name vectors).
 
 :- pred stack_layout__sort_livevals(list(var_info)::in, list(var_info)::out)
 	is det.
@@ -883,13 +890,13 @@
 
 :- pred stack_layout__construct_type_param_locn_vector(
 	assoc_list(tvar, set(layout_locn))::in,
-	int::in, list(maybe(rval))::out) is det.
+	int::in, assoc_list(rval, llds_type)::out) is det.
 
 stack_layout__construct_type_param_locn_vector([], _, []).
 stack_layout__construct_type_param_locn_vector([TVar - Locns | TVarLocns],
 		CurSlot, Vector) :-
 	term__var_to_int(TVar, TVarNum),
-	NextSlot is CurSlot + 1,
+	NextSlot = CurSlot + 1,
 	( TVarNum = CurSlot ->
 		( set__remove_least(Locns, LeastLocn, _) ->
 			Locn = LeastLocn
@@ -899,12 +906,12 @@
 		stack_layout__represent_locn_as_int_rval(Locn, Rval),
 		stack_layout__construct_type_param_locn_vector(TVarLocns,
 			NextSlot, VectorTail),
-		Vector = [yes(Rval) | VectorTail]
+		Vector = [Rval - uint_least32 | VectorTail]
 	; TVarNum > CurSlot ->
 		stack_layout__construct_type_param_locn_vector(
 			[TVar - Locns | TVarLocns], NextSlot, VectorTail),
 			% This slot will never be referred to.
-		Vector = [yes(const(int_const(0))) | VectorTail]
+		Vector = [const(int_const(0)) - uint_least32 | VectorTail]
 	;
 		error("unsorted tvars in construct_type_param_locn_vector")
 	).
@@ -948,50 +955,53 @@
 	{ EncodedLength = IntArrayLength << stack_layout__short_count_bits
 		+ ByteArrayLength },
 
-	{ SelectLocns = (pred(ArrayInfo::in, MaybeLocnRval::out) is det :-
-		ArrayInfo = live_array_info(LocnRval, _, _, _),
-		MaybeLocnRval = yes(LocnRval)
-	) },
-	{ SelectTypes = (pred(ArrayInfo::in, MaybeTypeRval::out) is det :-
-		ArrayInfo = live_array_info(_, TypeRval, _, _),
-		MaybeTypeRval = yes(TypeRval)
+	{ SelectLocns = (pred(ArrayInfo::in, LocnRval::out) is det :-
+		ArrayInfo = live_array_info(LocnRval, _, _, _)
 	) },
-	{ SelectTypeTypes = (pred(ArrayInfo::in, CountTypeType::out) is det :-
-		ArrayInfo = live_array_info(_, _, TypeType, _),
-		CountTypeType = 1 - yes(TypeType)
+	{ SelectTypes = (pred(ArrayInfo::in, TypeRval - TypeType::out) is det :-
+		ArrayInfo = live_array_info(_, TypeRval, TypeType, _)
 	) },
 	{ AddRevNums = (pred(ArrayInfo::in, NumRvals0::in, NumRvals::out)
 			is det :-
 		ArrayInfo = live_array_info(_, _, _, NumRval),
-		NumRvals = [yes(NumRval) | NumRvals0]
+		NumRvals = [NumRval | NumRvals0]
 	) },
 
-	{ list__map(SelectTypes, AllArrayInfo, AllTypes) },
-	{ list__map(SelectTypeTypes, AllArrayInfo, AllTypeTypes) },
+	{ list__map(SelectTypes, AllArrayInfo, AllTypeRvalsTypes) },
 	{ list__map(SelectLocns, IntArrayInfo, IntLocns) },
+	{ list__map(associate_type(uint_least32), IntLocns, IntLocnsTypes) },
 	{ list__map(SelectLocns, ByteArrayInfo, ByteLocns) },
-	{ list__append(IntLocns, ByteLocns, AllLocns) },
-	{ list__append(AllTypes, AllLocns, TypeLocnVectorRvals) },
-	{ LocnArgTypes = [IntArrayLength - yes(uint_least32),
-			ByteArrayLength - yes(uint_least8)] },
-	{ list__append(AllTypeTypes, LocnArgTypes, ArgTypes) },
-	{ Reuse = no },
-	{ TypeLocnVector = create(0, TypeLocnVectorRvals,
-		initial(ArgTypes, none), must_be_static,
-		"stack_layout_locn_vector", Reuse) },
+	{ list__map(associate_type(uint_least8), ByteLocns, ByteLocnsTypes) },
+	{ list__append(IntLocnsTypes, ByteLocnsTypes, AllLocnsTypes) },
+	{ list__append(AllTypeRvalsTypes, AllLocnsTypes,
+		TypeLocnVectorRvalsTypes) },
+	stack_layout__get_static_cell_info(StaticCellInfo0),
+	{ add_static_cell(TypeLocnVectorRvalsTypes, TypeLocnVectorAddr,
+		StaticCellInfo0, StaticCellInfo1) },
+	{ TypeLocnVector = const(data_addr_const(TypeLocnVectorAddr)) },
+	stack_layout__set_static_cell_info(StaticCellInfo1),
 
 	stack_layout__get_trace_stack_layout(TraceStackLayout),
 	( { TraceStackLayout = yes } ->
 		{ list__foldl(AddRevNums, AllArrayInfo,
 			[], RevVarNumRvals) },
 		{ list__reverse(RevVarNumRvals, VarNumRvals) },
-		{ NumVector = create(0, VarNumRvals,
-			uniform(yes(uint_least16)), must_be_static,
-			"stack_layout_var_num_vector", Reuse) }
+		{ list__map(associate_type(uint_least16), VarNumRvals,
+			VarNumRvalsTypes) },
+		stack_layout__get_static_cell_info(StaticCellInfo2),
+		{ add_static_cell(VarNumRvalsTypes, NumVectorAddr,
+			StaticCellInfo2, StaticCellInfo) },
+		stack_layout__set_static_cell_info(StaticCellInfo),
+		{ NumVector = const(data_addr_const(NumVectorAddr)) }
 	;
 		{ NumVector = const(int_const(0)) }
 	).
 
+:- pred associate_type(llds_type::in, rval::in, pair(rval, llds_type)::out)
+	is det.
+
+associate_type(LldsType, Rval, Rval - LldsType).
+
 :- pred stack_layout__construct_liveval_array_infos(list(var_info)::in,
 	int::in, int::in,
 	list(liveval_array_info)::out, list(liveval_array_info)::out,
@@ -1071,43 +1081,40 @@
 
 stack_layout__construct_closure_layout(CallerProcLabel, SeqNo,
 		ClosureLayoutInfo, ClosureProcLabel, ModuleName,
-		FileName, LineNumber, GoalPath, Rvals, ArgTypes, Data) :-
+		FileName, LineNumber, GoalPath, !StaticCellInfo,
+		RvalsTypes, Data) :-
 	DataAddr = layout_addr(
 		closure_proc_id(CallerProcLabel, SeqNo, ClosureProcLabel)),
 	Data = layout_data(closure_proc_id_data(CallerProcLabel, SeqNo,
 		ClosureProcLabel, ModuleName, FileName, LineNumber, GoalPath)),
-	MaybeProcIdRval = yes(const(data_addr_const(DataAddr))),
-	ProcIdType = 1 - yes(data_ptr),
+	ProcIdRvalType = const(data_addr_const(DataAddr)) - data_ptr,
 	ClosureLayoutInfo = closure_layout_info(ClosureArgs, TVarLocnMap),
 	stack_layout__construct_closure_arg_rvals(ClosureArgs,
-		MaybeClosureArgRvals, ClosureArgTypes),
-	stack_layout__construct_tvar_vector(TVarLocnMap, TVarVectorRval),
-	MaybeTVarVectorRval = yes(TVarVectorRval),
-	TVarVectorType = 1 - yes(data_ptr),
-	Rvals = [MaybeProcIdRval, MaybeTVarVectorRval | MaybeClosureArgRvals],
-	ArgTypes = initial([ProcIdType, TVarVectorType | ClosureArgTypes],
-		none).
+		ClosureArgRvalsTypes, !StaticCellInfo),
+	stack_layout__construct_tvar_vector(TVarLocnMap, TVarVectorRval,
+		!StaticCellInfo),
+	RvalsTypes = [ProcIdRvalType, TVarVectorRval - data_ptr |
+		ClosureArgRvalsTypes].
 
 :- pred stack_layout__construct_closure_arg_rvals(list(closure_arg_info)::in,
-	list(maybe(rval))::out, initial_arg_types::out) is det.
+	assoc_list(rval, llds_type)::out,
+	static_cell_info::in, static_cell_info::out) is det.
 
-stack_layout__construct_closure_arg_rvals(ClosureArgs, ClosureArgRvals,
-		ClosureArgTypes) :-
-	list__map(stack_layout__construct_closure_arg_rval,
-		ClosureArgs, MaybeArgRvalsTypes),
-	assoc_list__keys(MaybeArgRvalsTypes, MaybeArgRvals),
-	list__map(stack_layout__add_one, MaybeArgRvalsTypes, ArgRvalTypes),
-	list__length(MaybeArgRvals, Length),
-	ClosureArgRvals = [yes(const(int_const(Length))) | MaybeArgRvals],
-	ClosureArgTypes = [1 - yes(integer) | ArgRvalTypes].
+stack_layout__construct_closure_arg_rvals(ClosureArgs, ClosureArgRvalsTypes,
+		!StaticCellInfo) :-
+	list__map_foldl(stack_layout__construct_closure_arg_rval,
+		ClosureArgs, ArgRvalsTypes, !StaticCellInfo),
+	list__length(ArgRvalsTypes, Length),
+	ClosureArgRvalsTypes =
+		[const(int_const(Length)) - integer | ArgRvalsTypes].
 
 :- pred stack_layout__construct_closure_arg_rval(closure_arg_info::in,
-	pair(maybe(rval), llds_type)::out) is det.
+	pair(rval, llds_type)::out,
+	static_cell_info::in, static_cell_info::out) is det.
 
-stack_layout__construct_closure_arg_rval(ClosureArg,
-		yes(ArgRval) - ArgRvalType) :-
+stack_layout__construct_closure_arg_rval(ClosureArg, ArgRval - ArgRvalType,
+		!StaticCellInfo) :-
 	ClosureArg = closure_arg_info(Type, _Inst),
-
 		% For a stack layout, we can treat all type variables as
 		% universally quantified. This is not the argument of a
 		% constructor, so we do not need to distinguish between type
@@ -1115,61 +1122,55 @@
 		% variable number directly from the procedure's tvar set.
 	ExistQTvars = [],
 	NumUnivQTvars = -1,
-
 	ll_pseudo_type_info__construct_typed_llds_pseudo_type_info(Type,
-		NumUnivQTvars, ExistQTvars, ArgRval, ArgRvalType).
-
-:- pred stack_layout__add_one(pair(maybe(rval), llds_type)::in,
-	pair(int, maybe(llds_type))::out) is det.
-
-stack_layout__add_one(_MaybeRval - LldsType, 1 - yes(LldsType)).
+		NumUnivQTvars, ExistQTvars, !StaticCellInfo,
+		ArgRval, ArgRvalType).
 
 %---------------------------------------------------------------------------%
 
 :- pred stack_layout__make_table_data(rtti_proc_label::in,
 	proc_layout_kind::in, proc_table_info::in, layout_data::out,
-	stack_layout_info::in, stack_layout_info::out) is det.
+	static_cell_info::in, static_cell_info::out) is det.
 
-stack_layout__make_table_data(RttiProcLabel, Kind, TableInfo,
-		TableData) -->
+stack_layout__make_table_data(RttiProcLabel, Kind, TableInfo, TableData,
+		!StaticCellInfo) :-
 	(
-		{ TableInfo = table_io_decl_info(TableArgInfo) },
+		TableInfo = table_io_decl_info(TableArgInfo),
 		stack_layout__convert_table_arg_info(TableArgInfo,
-			NumPTIs, PTIVectorRval, TVarVectorRval),
-		{ TableData = table_io_decl_data(RttiProcLabel, Kind,
-			NumPTIs, PTIVectorRval, TVarVectorRval) }
+			NumPTIs, PTIVectorRval, TVarVectorRval,
+			!StaticCellInfo),
+		TableData = table_io_decl_data(RttiProcLabel, Kind,
+			NumPTIs, PTIVectorRval, TVarVectorRval)
 	;
-		{ TableInfo = table_gen_info(NumInputs, NumOutputs, Steps,
-			TableArgInfo) },
+		TableInfo = table_gen_info(NumInputs, NumOutputs, Steps,
+			TableArgInfo),
 		stack_layout__convert_table_arg_info(TableArgInfo,
-			NumPTIs, PTIVectorRval, TVarVectorRval),
-		{ NumArgs = NumInputs + NumOutputs },
-		{ require(unify(NumArgs, NumPTIs),
-			"stack_layout__make_table_data: args mismatch") },
-		{ TableData = table_gen_data(RttiProcLabel,
+			NumPTIs, PTIVectorRval, TVarVectorRval,
+			!StaticCellInfo),
+		NumArgs = NumInputs + NumOutputs,
+		require(unify(NumArgs, NumPTIs),
+			"stack_layout__make_table_data: args mismatch"),
+		TableData = table_gen_data(RttiProcLabel,
 			NumInputs, NumOutputs, Steps,
-			PTIVectorRval, TVarVectorRval) }
+			PTIVectorRval, TVarVectorRval)
 	).
 
 :- pred stack_layout__convert_table_arg_info(table_arg_infos::in,
 	int::out, rval::out, rval::out,
-	stack_layout_info::in, stack_layout_info::out) is det.
+	static_cell_info::in, static_cell_info::out) is det.
 
 stack_layout__convert_table_arg_info(TableArgInfos, NumPTIs,
-		PTIVectorRval, TVarVectorRval) -->
-	{ TableArgInfos = table_arg_infos(Args, TVarSlotMap) },
-	{ list__length(Args, NumPTIs) },
-	{ list__map(stack_layout__construct_table_arg_pti_rval,
-		Args, MaybePTIRvalTypes) },
-	{ list__map(stack_layout__add_one, MaybePTIRvalTypes, PTITypes) },
-	{ assoc_list__keys(MaybePTIRvalTypes, MaybePTIRvals) },
-	{ PTIVectorTypes = initial(PTITypes, none) },
-	{ Reuse = no },
-	{ PTIVectorRval = create(0, MaybePTIRvals, PTIVectorTypes,
-		must_be_static, "stack_layout_table_ptis", Reuse) },
-	{ map__map_values(stack_layout__convert_slot_to_locn_map,
-		TVarSlotMap, TVarLocnMap) },
-	{ stack_layout__construct_tvar_vector(TVarLocnMap, TVarVectorRval) }.
+		PTIVectorRval, TVarVectorRval, !StaticCellInfo) :-
+	TableArgInfos = table_arg_infos(Args, TVarSlotMap),
+	list__length(Args, NumPTIs),
+	list__map_foldl(stack_layout__construct_table_arg_pti_rval,
+		Args, PTIRvalsTypes, !StaticCellInfo),
+	add_static_cell(PTIRvalsTypes, PTIVectorAddr, !StaticCellInfo),
+	PTIVectorRval = const(data_addr_const(PTIVectorAddr)),
+	map__map_values(stack_layout__convert_slot_to_locn_map,
+		TVarSlotMap, TVarLocnMap),
+	stack_layout__construct_tvar_vector(TVarLocnMap, TVarVectorRval,
+		!StaticCellInfo).
 
 :- pred stack_layout__convert_slot_to_locn_map(tvar::in, table_locn::in,
 	set(layout_locn)::out) is det.
@@ -1185,15 +1186,17 @@
 	LvalLocns = set__make_singleton_set(LvalLocn).
 
 :- pred stack_layout__construct_table_arg_pti_rval(
-	table_arg_info::in, pair(maybe(rval), llds_type)::out) is det.
+	table_arg_info::in, pair(rval, llds_type)::out,
+	static_cell_info::in, static_cell_info::out) is det.
 
 stack_layout__construct_table_arg_pti_rval(ClosureArg,
-		yes(ArgRval) - ArgRvalType) :-
+		ArgRval - ArgRvalType, !StaticCellInfo) :-
 	ClosureArg = table_arg_info(_, _, Type),
 	ExistQTvars = [],
 	NumUnivQTvars = -1,
 	ll_pseudo_type_info__construct_typed_llds_pseudo_type_info(Type,
-		NumUnivQTvars, ExistQTvars, ArgRval, ArgRvalType).
+		NumUnivQTvars, ExistQTvars, !StaticCellInfo,
+		ArgRval, ArgRvalType).
 
 %---------------------------------------------------------------------------%
 
@@ -1256,8 +1259,11 @@
 		% variable number directly from the procedure's tvar set.
 	{ ExistQTvars = [] },
 	{ NumUnivQTvars = -1 },
+	stack_layout__get_static_cell_info(StaticCellInfo0),
 	{ ll_pseudo_type_info__construct_typed_llds_pseudo_type_info(Type,
-		NumUnivQTvars, ExistQTvars, Rval, LldsType) }.
+		NumUnivQTvars, ExistQTvars, StaticCellInfo0, StaticCellInfo,
+		Rval, LldsType) },
+	stack_layout__set_static_cell_info(StaticCellInfo).
 
 %---------------------------------------------------------------------------%
 
@@ -1539,12 +1545,13 @@
 					   % contributes labels to this module
 					   % to a table describing those
 					   % labels.
-		cur_proc_named_vars	:: map(int, string)
+		cur_proc_named_vars	:: map(int, string),
 					   % Maps the number of each variable
 					   % in the current procedure whose
 					   % name is of interest in an internal
 					   % label's layout structure to the
 					   % name of that variable.
+		static_cell_info	:: static_cell_info
 	).
 
 :- pred stack_layout__get_module_info(module_info::out,
@@ -1583,6 +1590,9 @@
 :- pred stack_layout__get_cur_proc_named_vars(map(int, string)::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
+:- pred stack_layout__get_static_cell_info(static_cell_info::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
+
 stack_layout__get_module_info(LI ^ module_info, LI, LI).
 stack_layout__get_agc_stack_layout(LI ^ agc_stack_layout, LI, LI).
 stack_layout__get_trace_stack_layout(LI ^ trace_stack_layout, LI, LI).
@@ -1595,6 +1605,7 @@
 stack_layout__get_string_table(LI ^ string_table, LI, LI).
 stack_layout__get_label_tables(LI ^ label_tables, LI, LI).
 stack_layout__get_cur_proc_named_vars(LI ^ cur_proc_named_vars, LI, LI).
+stack_layout__get_static_cell_info(LI ^ static_cell_info, LI, LI).
 
 :- pred stack_layout__get_module_name(module_name::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
@@ -1641,9 +1652,6 @@
 	LI = ((LI0 ^ internal_layouts := InternalLayouts)
 		^ label_set := LabelSet).
 
-:- pred stack_layout__set_module_info(module_info::in,
-	stack_layout_info::in, stack_layout_info::out) is det.
-
 :- pred stack_layout__set_string_table(string_table::in,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
@@ -1653,11 +1661,15 @@
 :- pred stack_layout__set_cur_proc_named_vars(map(int, string)::in,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
-stack_layout__set_module_info(MI, LI0, LI0 ^ module_info := MI).
+:- pred stack_layout__set_static_cell_info(static_cell_info::in,
+	stack_layout_info::in, stack_layout_info::out) is det.
+
 stack_layout__set_string_table(ST, LI0, LI0 ^ string_table := ST).
 stack_layout__set_label_tables(LT, LI0, LI0 ^ label_tables := LT).
 stack_layout__set_cur_proc_named_vars(NV, LI0,
 	LI0 ^ cur_proc_named_vars := NV).
+stack_layout__set_static_cell_info(SCI, LI0,
+	LI0 ^ static_cell_info := SCI).
 
 %---------------------------------------------------------------------------%
 
Index: compiler/static_term.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/static_term.m,v
retrieving revision 1.5
diff -u -b -r1.5 static_term.m
--- compiler/static_term.m	1 May 2003 22:50:50 -0000	1.5
+++ compiler/static_term.m	6 May 2003 03:07:17 -0000
@@ -17,11 +17,13 @@
 
 :- interface.
 
+:- import_module ll_backend__global_data.
 :- import_module ll_backend__llds.
 
 :- import_module std_util.
 
-:- pred static_term__term_to_rval(univ::in, maybe(rval)::out) is det.
+:- pred static_term__term_to_rval(univ::in, rval::out,
+	static_cell_info::in, static_cell_info::out) is det.
 
 %---------------------------------------------------------------------------%
 
@@ -31,50 +33,53 @@
 
 :- import_module deconstruct, list, require.
 
-static_term__term_to_rval(Univ, Rval) :-
+static_term__term_to_rval(Univ, Rval, !StaticCellInfo) :-
 	( deconstruct__get_functor_info(Univ, FunctorInfo) ->
-		static_term__functor_info_to_rval(FunctorInfo, Rval)
+		static_term__functor_info_to_rval(FunctorInfo, Rval,
+			!StaticCellInfo)
 	;
 		error("static_term__term_to_rval: unexpected kind of term")
 	).
 
 :- pred static_term__functor_info_to_rval(functor_tag_info::in,
-	maybe(rval)::out) is det.
+	rval::out, static_cell_info::in, static_cell_info::out) is det.
 
-static_term__functor_info_to_rval(FunctorInfo, MaybeRval) :-
+static_term__functor_info_to_rval(FunctorInfo, Rval, !StaticCellInfo) :-
 	(
 		FunctorInfo = functor_integer(Int),
-		MaybeRval = yes(const(int_const(Int)))
+		Rval = const(int_const(Int))
 	;
 		FunctorInfo = functor_float(Float),
-		MaybeRval = yes(const(float_const(Float)))
+		Rval = const(float_const(Float))
 	;
 		FunctorInfo = functor_string(String),
-		MaybeRval = yes(const(string_const(String)))
+		Rval = const(string_const(String))
 	;
 		FunctorInfo = functor_enum(Enum),
-		MaybeRval = yes(const(int_const(Enum)))
+		Rval = const(int_const(Enum))
 	;
 		FunctorInfo = functor_local(Ptag, Sectag),
-		MaybeRval = yes(mkword(Ptag,
-			unop(mkbody, const(int_const(Sectag)))))
+		Rval = mkword(Ptag,
+			unop(mkbody, const(int_const(Sectag))))
 	;
 		FunctorInfo = functor_remote(Ptag, Sectag, Args),
-		MaybeSectagRval = yes(const(int_const(Sectag))),
-		list__map(static_term__term_to_rval, Args, MaybeArgRvals),
-		Reuse = no,
-		MaybeRval = yes(create(Ptag, [MaybeSectagRval | MaybeArgRvals],
-			uniform(no), must_be_static, "static_term", Reuse))
+		SectagRval = const(int_const(Sectag)),
+		list__map_foldl(static_term__term_to_rval, Args, ArgRvals,
+			!StaticCellInfo),
+		add_static_cell_natural_types([SectagRval | ArgRvals],
+			DataAddr, !StaticCellInfo),
+		Rval = mkword(Ptag, const(data_addr_const(DataAddr)))
 	;
 		FunctorInfo = functor_unshared(Ptag, Args),
-		list__map(static_term__term_to_rval, Args, MaybeArgRvals),
-		Reuse = no,
-		MaybeRval = yes(create(Ptag, MaybeArgRvals,
-			uniform(no), must_be_static, "static_term", Reuse))
+		list__map_foldl(static_term__term_to_rval, Args, ArgRvals,
+			!StaticCellInfo),
+		add_static_cell_natural_types(ArgRvals, DataAddr,
+			!StaticCellInfo),
+		Rval = mkword(Ptag, const(data_addr_const(DataAddr)))
 	;
 		FunctorInfo = functor_notag(Univ),
-		static_term__term_to_rval(Univ, MaybeRval)
+		static_term__term_to_rval(Univ, Rval, !StaticCellInfo)
 	;
 		FunctorInfo = functor_equiv(Univ),
-		static_term__term_to_rval(Univ, MaybeRval)
+		static_term__term_to_rval(Univ, Rval, !StaticCellInfo)
 	).
Index: compiler/string_switch.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/string_switch.m,v
retrieving revision 1.42
diff -u -b -r1.42 string_switch.m
--- compiler/string_switch.m	1 May 2003 22:50:50 -0000	1.42
+++ compiler/string_switch.m	5 May 2003 22:48:42 -0000
@@ -45,14 +45,14 @@
 :- import_module bool, int, string, list, map, std_util, assoc_list, require.
 
 string_switch__generate(Cases, Var, CodeModel, _CanFail, SwitchGoalInfo,
-		EndLabel, MaybeEnd0, MaybeEnd, Code) -->
-	code_info__produce_variable(Var, VarCode, VarRval),
-	code_info__acquire_reg(r, SlotReg),
-	code_info__acquire_reg(r, StringReg),
-	code_info__get_next_label(LoopLabel),
-	code_info__get_next_label(FailLabel),
-	code_info__get_next_label(JumpLabel),
-	{
+		EndLabel, MaybeEnd0, MaybeEnd, Code, !CodeInfo) :-
+	code_info__produce_variable(Var, VarCode, VarRval, !CodeInfo),
+	code_info__acquire_reg(r, SlotReg, !CodeInfo),
+	code_info__acquire_reg(r, StringReg, !CodeInfo),
+	code_info__get_next_label(LoopLabel, !CodeInfo),
+	code_info__get_next_label(FailLabel, !CodeInfo),
+	code_info__get_next_label(JumpLabel, !CodeInfo),
+
 		% Determine how big to make the hash table.
 		% Currently we round the number of cases up to the nearest
 		% power of two, and then double it.  This should hopefully
@@ -61,16 +61,16 @@
 		list__length(Cases, NumCases),
 		int__log2(NumCases, LogNumCases),
 		int__pow(2, LogNumCases, RoundedNumCases),
-		TableSize is 2 * RoundedNumCases,
-		HashMask is TableSize - 1,
+	TableSize = 2 * RoundedNumCases,
+	HashMask = TableSize - 1,
 
 		% Compute the hash table
 		%
 		switch_util__string_hash_cases(Cases, HashMask, HashValsMap),
 		map__to_assoc_list(HashValsMap, HashValsList),
 		switch_util__calc_hash_slots(HashValsList, HashValsMap,
-			HashSlotsMap)
-	},
+		HashSlotsMap),
+
 		% Note that it is safe to release the registers now,
 		% even though we haven't yet generated all the code
 		% which uses them, because that code will be executed
@@ -78,30 +78,29 @@
 		% registers), and because that code is generated manually
 		% (below) so we don't need the reg info to be valid when
 		% we generate it.
-	code_info__release_reg(SlotReg),
-	code_info__release_reg(StringReg),
+	code_info__release_reg(SlotReg, !CodeInfo),
+	code_info__release_reg(StringReg, !CodeInfo),
 
 		% Generate the code for when the hash lookup fails.
 		% This must be done before gen_hash_slots, since
 		% we want to use the exprn_info corresponding to
 		% the start of the switch, not to the end of the last case.
-	code_info__generate_failure(FailCode),
+	code_info__generate_failure(FailCode, !CodeInfo),
 
 		% Generate the code etc. for the hash table
 		%
 	string_switch__gen_hash_slots(0, TableSize, HashSlotsMap, CodeModel,
 		SwitchGoalInfo, FailLabel, EndLabel, MaybeEnd0, MaybeEnd,
-		Strings, Labels, NextSlots, SlotsCode),
+		Strings, Labels, NextSlots, SlotsCode, !CodeInfo),
 
 		% Generate code which does the hash table lookup
-	{
-		Reuse = no,
-		NextSlotsTable = create(0, NextSlots, uniform(no),
-			must_be_static,
-			"string_switch_next_slots_table", Reuse),
-		StringTable = create(0, Strings, uniform(no),
-			must_be_static,
-			"string_switch_string_table", Reuse),
+	(
+		add_static_cell_natural_types(NextSlots, NextSlotsTableAddr,
+			!CodeInfo),
+		NextSlotsTable = const(data_addr_const(NextSlotsTableAddr)),
+		add_static_cell_natural_types(Strings, StringTableAddr,
+			!CodeInfo),
+		StringTable = const(data_addr_const(StringTableAddr)),
 		HashLookupCode = node([
 			comment("hashed string switch") -
 			  "",
@@ -126,28 +125,24 @@
 			label(FailLabel) -
 			  "no match, so fail"
 		])
-	},
-	{
+	),
 		JumpCode = node([
 			label(JumpLabel) -
 				"we found a match",
 			computed_goto(lval(SlotReg), Labels) -
 				"jump to the corresponding code"
-		])
-	},
+	]),
 		% Collect all the generated code fragments together
-	{ Code =
+	Code =
 		tree(VarCode,
 		tree(HashLookupCode,
 		tree(FailCode,
 		tree(JumpCode,
-		     SlotsCode))))
-	}.
+		     SlotsCode)))).
 
 :- pred string_switch__gen_hash_slots(int, int, map(int, hash_slot),
 	code_model, hlds_goal_info, label, label, branch_end, branch_end,
-	list(maybe(rval)), list(label), list(maybe(rval)), code_tree,
-	code_info, code_info).
+	list(rval), list(label), list(rval), code_tree, code_info, code_info).
 :- mode string_switch__gen_hash_slots(in, in, in, in, in, in, in,
 	in, out, out, out, out, out, in, out) is det.
 
@@ -169,7 +164,7 @@
 			CodeModel, SwitchGoalInfo, FailLabel, EndLabel,
 			MaybeEnd0, MaybeEnd1,
 			String, Label, NextSlot, SlotCode),
-		{ Slot1 is Slot + 1 },
+		{ Slot1 = Slot + 1 },
 		{ 
 			Strings = [String | Strings0],
 			Labels = [Label | Labels0],
@@ -184,14 +179,14 @@
 
 :- pred string_switch__gen_hash_slot(int, int, map(int, hash_slot),
 	code_model, hlds_goal_info, label, label, branch_end, branch_end,
-	maybe(rval), label, maybe(rval), code_tree,
+	rval, label, rval, code_tree,
 	code_info, code_info).
 :- mode string_switch__gen_hash_slot(in, in, in, in, in, in, in,
 	in, out, out, out, out, out, in, out) is det.
 
 string_switch__gen_hash_slot(Slot, TblSize, HashSlotMap, CodeModel,
 		SwitchGoalInfo, FailLabel, EndLabel, MaybeEnd0, MaybeEnd,
-		yes(StringRval), Label, yes(NextSlotRval), Code) -->
+		StringRval, Label, NextSlotRval, Code) -->
 	( { map__search(HashSlotMap, Slot, hash_slot(Case, Next)) } ->
 		{ NextSlotRval = const(int_const(Next)) },
 		{ Case = case(_, ConsTag, _, Goal) },
@@ -243,7 +238,7 @@
 :- mode string_switch__this_is_last_case(in, in, in) is semidet.
 
 string_switch__this_is_last_case(Slot, TableSize, Table) :-
-	Slot1 is Slot + 1,
+	Slot1 = Slot + 1,
 	( Slot1 >= TableSize ->
 		true
 	;
Index: compiler/unify_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/unify_gen.m,v
retrieving revision 1.126
diff -u -b -r1.126 unify_gen.m
--- compiler/unify_gen.m	1 May 2003 22:50:50 -0000	1.126
+++ compiler/unify_gen.m	6 May 2003 05:05:28 -0000
@@ -620,7 +620,7 @@
 			ProcLabel) },
 		(
 			{ EvalMethod = normal },
-			{ AddrConst = const(code_addr_const(CodeAddr)) }
+			{ CallArgsRval = const(code_addr_const(CodeAddr)) }
 		;
 			{ EvalMethod = (aditi_bottom_up) },
 			{ rl__get_c_interface_rl_proc_name(ModuleInfo,
@@ -631,12 +631,13 @@
 			{ rl__schema_to_string(ModuleInfo,
 				InputTypes, InputSchemaStr) },
 			{ AditiCallArgs = [
-				yes(const(string_const(RLProcNameStr))),
-				yes(const(string_const(InputSchemaStr)))
+				const(string_const(RLProcNameStr)),
+				const(string_const(InputSchemaStr))
 			] },
-			{ Reuse = no },
-			{ AddrConst = create(0, AditiCallArgs, uniform(no),
-				must_be_static, "aditi_call_info", Reuse) }
+			code_info__add_static_cell_natural_types(AditiCallArgs,
+				CallArgsDataAddr),
+			{ CallArgsRval =
+				const(data_addr_const(CallArgsDataAddr)) }
 		;
 			{ EvalMethod = (aditi_top_down) },
 			% XXX Need to work out how to encode the procedure
@@ -655,22 +656,24 @@
 		{ goal_path_to_string(GoalPath, GoalPathStr) },
 		code_info__get_cur_proc_label(CallerProcLabel),
 		code_info__get_next_closure_seq_no(SeqNo),
+		code_info__get_static_cell_info(StaticCellInfo0),
 		{ stack_layout__construct_closure_layout(CallerProcLabel,
 			SeqNo, ClosureInfo, ProcLabel, ModuleName,
 			FileName, LineNumber, GoalPathStr,
-			ClosureLayoutMaybeRvals, ClosureLayoutArgTypes,
-			Data) },
+			StaticCellInfo0, StaticCellInfo,
+			ClosureLayoutRvalsTypes, Data) },
+		code_info__set_static_cell_info(StaticCellInfo),
 		code_info__add_closure_layout(Data),
-		{ Reuse = no },
-		{ ClosureLayout = create(0, ClosureLayoutMaybeRvals,
-			ClosureLayoutArgTypes, must_be_static,
-			"closure_layout", Reuse) },
+		code_info__add_static_cell(ClosureLayoutRvalsTypes,
+			ClosureDataAddr),
+		{ ClosureLayoutRval =
+			const(data_addr_const(ClosureDataAddr)) },
 		{ list__length(Args, NumArgs) },
 		{ proc_info_arg_info(ProcInfo, ArgInfo) },
 		{ unify_gen__generate_pred_args(Args, ArgInfo, PredArgs) },
 		{ Vector = [
-			yes(ClosureLayout),
-			yes(AddrConst),
+			yes(ClosureLayoutRval),
+			yes(CallArgsRval),
 			yes(const(int_const(NumArgs)))
 			| PredArgs
 		] },
@@ -717,8 +720,10 @@
 	list(uni_mode)::in, module_info::in, list(maybe(rval))::out) is det.
 
 unify_gen__generate_cons_args(Vars, Types, Modes, ModuleInfo, Args) :-
-	( unify_gen__generate_cons_args_2(Vars, Types, Modes, ModuleInfo,
-			Args0) ->
+	(
+		unify_gen__generate_cons_args_2(Vars, Types, Modes,
+			ModuleInfo, Args0)
+	->
 		Args = Args0
 	;
 		error("unify_gen__generate_cons_args: length mismatch")
@@ -736,12 +741,12 @@
 
 unify_gen__generate_cons_args_2([], [], [], _, []).
 unify_gen__generate_cons_args_2([Var | Vars], [Type | Types],
-		[UniMode | UniModes], ModuleInfo, [Arg | RVals]) :-
+		[UniMode | UniModes], ModuleInfo, [Rval | RVals]) :-
 	UniMode = ((_LI - RI) -> (_LF - RF)),
 	( mode_to_arg_mode(ModuleInfo, (RI -> RF), Type, top_in) ->
-		Arg = yes(var(Var))
+		Rval = yes(var(Var))
 	;
-		Arg = no
+		Rval = no
 	),
 	unify_gen__generate_cons_args_2(Vars, Types, UniModes, ModuleInfo,
 		RVals).
Index: compiler/var_locn.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/var_locn.m,v
retrieving revision 1.9
diff -u -b -r1.9 var_locn.m
--- compiler/var_locn.m	7 May 2003 00:50:22 -0000	1.9
+++ compiler/var_locn.m	7 May 2003 00:50:55 -0000
@@ -1,4 +1,4 @@
-
+%---------------------------------------------------------------------------%
 % Copyright (C) 2000-2003 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -21,6 +21,7 @@
 
 :- import_module parse_tree__prog_data.
 :- import_module hlds__hlds_llds.
+:- import_module ll_backend__global_data.
 :- import_module ll_backend__llds.
 :- import_module libs__options.
 
@@ -120,12 +121,14 @@
 :- pred var_locn__assign_var_to_var(prog_var::in, prog_var::in,
 	var_locn_info::in, var_locn_info::out) is det.
 
-%	var_locn__assign_lval_to_var(Var, Lval, Code, VarLocnInfo0, VarLocnInfo)
+%	var_locn__assign_lval_to_var(Var, Lval, StaticCellInfo, Code,
+%			VarLocnInfo0, VarLocnInfo)
 %		Reflects the effect of the assignment Var := lval(Lval) in the
 %		state of VarLocnInfo0 to yield VarLocnInfo; any code required
 %		to effect the assignment will be returned in Code.
 
-:- pred var_locn__assign_lval_to_var(prog_var::in, lval::in, code_tree::out,
+:- pred var_locn__assign_lval_to_var(prog_var::in, lval::in,
+	static_cell_info::in, code_tree::out,
 	var_locn_info::in, var_locn_info::out) is det.
 
 %	var_locn__assign_const_to_var(Var, ConstRval,
@@ -149,6 +152,7 @@
 	var_locn_info::in, var_locn_info::out) is det.
 
 %	var_locn__assign_cell_to_var(Var, Ptag, Vector, TypeMsg, Code,
+%			StaticCellInfo0, StaticCellInfo,
 %			VarLocnInfo0, VarLocnInfo)
 %		Generates code to assign to Var a pointer, tagged by Ptag, to
 %		the cell whose contents are given by the other arguments,
@@ -156,6 +160,7 @@
 
 :- pred var_locn__assign_cell_to_var(prog_var::in, tag::in,
 	list(maybe(rval))::in, string::in, code_tree::out,
+	static_cell_info::in, static_cell_info::out,
 	var_locn_info::in, var_locn_info::out) is det.
 
 %	var_locn__place_var(Var, Lval, Code, VarLocnInfo0, VarLocnInfo)
@@ -660,9 +665,8 @@
 
 %----------------------------------------------------------------------------%
 
-var_locn__assign_lval_to_var(Var, Lval0, Code) -->
+var_locn__assign_lval_to_var(Var, Lval0, StaticCellInfo, Code) -->
 	var_locn__check_var_is_unknown(Var),
-
 	(
 		{ Lval0 = field(yes(Ptag), var(BaseVar),
 			const(int_const(Offset))) }
@@ -673,11 +677,14 @@
 			_MaybeExprRval, _UsingVars, _DeadOrAlive) },
 		(
 			{ MaybeConstBaseVarRval = yes(BaseVarRval) },
-			{ BaseVarRval = create(Ptag, BaseVarArgs, _,_,_,_) }
-		->
-			{ list__index0_det(BaseVarArgs, Offset,
-				SelectedArg) },
-			{ MaybeConstRval = SelectedArg },
+			{ BaseVarRval = mkword(Ptag, BaseConst) },
+			{ BaseConst = const(data_addr_const(DataAddr)) },
+			{ search_static_cell(StaticCellInfo, DataAddr,
+				StaticCellArgsTypes) }
+		->
+			{ list__index0_det(StaticCellArgsTypes, Offset,
+				SelectedArgRval - _SelectedArgType) },
+			{ MaybeConstRval = yes(SelectedArgRval) },
 			{ Lvals = set__map(var_locn__add_field_offset(
 				yes(Ptag), const(int_const(Offset))),
 				BaseVarLvals) },
@@ -732,8 +739,8 @@
 	var_locn__get_var_state_map(VarStateMap0),
 	var_locn__get_exprn_opts(ExprnOpts),
 	(
-		{ var_locn__expr_is_constant(ConstRval0, VarStateMap0,
-			ExprnOpts, ConstRval) }
+		{ var_locn__expr_is_constant(VarStateMap0, ExprnOpts,
+			ConstRval0, ConstRval) }
 	->
 		{ State = state(set__init, yes(ConstRval), no,
 			set__init, alive) },
@@ -783,21 +790,21 @@
 
 %----------------------------------------------------------------------------%
 
-var_locn__assign_cell_to_var(Var, Ptag, Vector, TypeMsg, Code) -->
-	{ Reuse = no },
-	{ CellRval0 = create(Ptag, Vector, uniform(no), can_be_either,
-		TypeMsg, Reuse) },
-	(
-		var_locn__get_var_state_map(VarStateMap),
-		var_locn__get_exprn_opts(ExprnOpts),
-		{ var_locn__expr_is_constant(CellRval0, VarStateMap, ExprnOpts,
-			CellRval) }
-	->
-		var_locn__assign_const_to_var(Var, CellRval),
-		{ Code = empty }
+var_locn__assign_cell_to_var(Var, Ptag, MaybeRvals, TypeMsg, Code,
+		!StaticCellInfo, !VarLocn) :-
+	var_locn__get_var_state_map(VarStateMap, !VarLocn),
+	var_locn__get_exprn_opts(ExprnOpts, !VarLocn),
+	(
+		var_locn__cell_is_constant(VarStateMap, ExprnOpts,
+			MaybeRvals, RvalsTypes)
+	->
+		add_static_cell(RvalsTypes, DataAddr, !StaticCellInfo),
+		CellRval = mkword(Ptag, const(data_addr_const(DataAddr))),
+		var_locn__assign_const_to_var(Var, CellRval, !VarLocn),
+		Code = empty
 	;
-		var_locn__assign_dynamic_cell_to_var(Var, Ptag, Vector,
-			TypeMsg, Code)
+		var_locn__assign_dynamic_cell_to_var(Var, Ptag, MaybeRvals,
+			TypeMsg, Code, !VarLocn)
 	).
 
 :- pred var_locn__assign_dynamic_cell_to_var(prog_var::in, tag::in,
@@ -845,10 +852,6 @@
 			{ Rval = Rval0 },
 			{ EvalCode = empty },
 			{ Comment = "assigning field from const" }
-		; { Rval0 = create(_, _, _, _, _, _) } ->
-			{ Rval = Rval0 },
-			{ EvalCode = empty },
-			{ Comment = "assigning field from const struct" }
 		;
 			{ error("var_locn__assign_cell_args: unknown rval") }
 		),
@@ -1820,63 +1823,48 @@
 
 %----------------------------------------------------------------------------%
 
-% var_locn__expr_is_constant(Rval0, VarStateMap, ExprnOpts, Rval)
+:- pred var_locn__cell_is_constant(var_state_map::in, exprn_opts::in,
+	list(maybe(rval))::in, assoc_list(rval, llds_type)::out) is semidet.
+
+var_locn__cell_is_constant(_VarStateMap, _ExprnOpts, [], []).
+var_locn__cell_is_constant(VarStateMap, ExprnOpts, [yes(Rval0) | MaybeRvals],
+		[Rval - LldsType | RvalsTypes]) :-
+	var_locn__expr_is_constant(VarStateMap, ExprnOpts, Rval0, Rval),
+	rval_type_as_arg(Rval, ExprnOpts, LldsType),
+	var_locn__cell_is_constant(VarStateMap, ExprnOpts, MaybeRvals,
+		RvalsTypes).
+
+% var_locn__expr_is_constant(VarStateMap, ExprnOpts, Rval0, Rval)
 % Check if Rval0 is a constant rval, after substituting the values of the
 % variables inside it. Returns the substituted, ground rval in Rval.
 % Note that this predicate is similar to code_exprn__expr_is_constant,
 % but of courses its own version of the variable state data structure.
 
-:- pred var_locn__expr_is_constant(rval::in, var_state_map::in, exprn_opts::in,
-	rval::out) is semidet.
+:- pred var_locn__expr_is_constant(var_state_map::in, exprn_opts::in,
+	rval::in, rval::out) is semidet.
 
-var_locn__expr_is_constant(const(Const), _, ExprnOpts, const(Const)) :-
+var_locn__expr_is_constant(_, ExprnOpts, const(Const), const(Const)) :-
 	exprn_aux__const_is_constant(Const, ExprnOpts, yes).
 
-var_locn__expr_is_constant(unop(Op, Expr0), VarStateMap, ExprnOpts,
-		unop(Op, Expr)) :-
-	var_locn__expr_is_constant(Expr0, VarStateMap, ExprnOpts, Expr).
-
-var_locn__expr_is_constant(binop(Op, Expr1, Expr2), VarStateMap, ExprnOpts,
-		binop(Op, Expr3, Expr4)) :-
-	var_locn__expr_is_constant(Expr1, VarStateMap, ExprnOpts, Expr3),
-	var_locn__expr_is_constant(Expr2, VarStateMap, ExprnOpts, Expr4).
-
-var_locn__expr_is_constant(mkword(Tag, Expr0), VarStateMap, ExprnOpts,
-		mkword(Tag, Expr)) :-
-	var_locn__expr_is_constant(Expr0, VarStateMap, ExprnOpts, Expr).
-
-var_locn__expr_is_constant(create(Tag, Args0, ArgTypes, StatDyn, Msg, Reuse),
-		VarStateMap, ExprnOpts, NewRval) :-
-	Reuse = no,
-	( StatDyn = must_be_static ->
-		Args = Args0
-	;
-		ExprnOpts = nlg_asm_sgt_ubf(_, _, StaticGroundTerms, _),
-		StaticGroundTerms = yes,
-		var_locn__args_are_constant(Args0, VarStateMap, ExprnOpts,
-			Args)
-	),
-	NewRval = create(Tag, Args, ArgTypes, StatDyn, Msg, Reuse).
+var_locn__expr_is_constant(VarStateMap, ExprnOpts,
+		unop(Op, Expr0), unop(Op, Expr)) :-
+	var_locn__expr_is_constant(VarStateMap, ExprnOpts, Expr0, Expr).
+
+var_locn__expr_is_constant(VarStateMap, ExprnOpts,
+		binop(Op, Expr1, Expr2), binop(Op, Expr3, Expr4)) :-
+	var_locn__expr_is_constant(VarStateMap, ExprnOpts, Expr1, Expr3),
+	var_locn__expr_is_constant(VarStateMap, ExprnOpts, Expr2, Expr4).
+
+var_locn__expr_is_constant(VarStateMap, ExprnOpts,
+		mkword(Tag, Expr0), mkword(Tag, Expr)) :-
+	var_locn__expr_is_constant(VarStateMap, ExprnOpts, Expr0, Expr).
 
-var_locn__expr_is_constant(var(Var), VarStateMap, ExprnOpts, Rval) :-
+var_locn__expr_is_constant(VarStateMap, ExprnOpts, var(Var), Rval) :-
 	map__search(VarStateMap, Var, State),
 	State = state(_, yes(Rval), _, _, _),
-	require(var_locn__expr_is_constant(Rval, VarStateMap, ExprnOpts, _),
+	require(var_locn__expr_is_constant(VarStateMap, ExprnOpts, Rval, _),
 		"non-constant rval in variable state").
 
-:- pred var_locn__args_are_constant(list(maybe(rval))::in, var_state_map::in,
-	exprn_opts::in, list(maybe(rval))::out) is semidet.
-
-var_locn__args_are_constant([], _VarStateMap, _ExprnOpts, []).
-var_locn__args_are_constant([Arg0 | Args0], VarStateMap, ExprnOpts,
-		[Arg | Args]) :-
-	% if any of the fields are 'no' then we cannot treat the
-	% term as a constant.
-	Arg0 = yes(Rval0),
-	var_locn__expr_is_constant(Rval0, VarStateMap, ExprnOpts, Rval),
-	Arg = yes(Rval),
-	var_locn__args_are_constant(Args0, VarStateMap, ExprnOpts, Args).
-
 %----------------------------------------------------------------------------%
 
 % Lval is Lval0 with all variables in Lval0 replaced by their values.
@@ -2005,11 +1993,6 @@
 		{ Rval = Rval0 },
 		{ Code = empty }
 	;
-			% If we get here, the cell must be a constant.
-		{ Rval0 = create(_, _, _, _, _, _) },
-		{ Rval = Rval0 },
-		{ Code = empty }
-	;
 		{ Rval0 = var(Var) },
 		var_locn__find_var_availability(Var, MaybePrefer, Avail),
 		(
@@ -2161,9 +2144,6 @@
 	var_locn__lval_depends_on_search_lval(Lval, SearchLval).
 var_locn__rval_depends_on_search_lval(var(_Var), _SearchLval) :-
 	error("var_locn__rval_depends_on_search_lval: var").
-var_locn__rval_depends_on_search_lval(create(_, Rvals, _, _, _, Reuse),
-		SearchLval) :-
-	var_locn__args_depend_on_search_lval([Reuse | Rvals], SearchLval).
 var_locn__rval_depends_on_search_lval(mkword(_Tag, Rval), SearchLval) :-
 	var_locn__rval_depends_on_search_lval(Rval, SearchLval).
 var_locn__rval_depends_on_search_lval(const(_Const), _SearchLval) :-
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
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