[m-dev.] for review: generating C layout structures

Zoltan Somogyi zs at cs.mu.OZ.AU
Mon Jan 8 14:37:51 AEDT 2001


For review by Tyson.

Estimated hours taken: 30

Instead of generating the layout structures of labels, procs and modules
as rvals, generate them almost entirely as C structures. This will make
future modifications much easier, since mismatches between what the runtime
expects and what the compiler generates will now be pointed out by the C
compiler. (It also reduces the size of the C source files generated with
debugging enabled by about 5%.) Layout structures contain a few components
that are not well-typed in C; we continue to generate these as rvals.

Closure layout structures used to have a well-typed part and a non-well-typed
part. We now generate the well-typed part as a separate structure, pointed to
from the other. We also extend the well-typed part, so that instead of
just giving the name the called procedure, it also identifies the source
location where the closure was constructed. This could be useful for
the debugger and for deep profiling.

runtime/mercury_stack_layout.h:
	Reorganize the definitions of layout structures. Rename
	Stack_Layout_Entry structures as Proc_Layout structures,
	and Stack_Layout_Label structures as Label_Layout structures.
	(The debugger paper refers to the structures by the new names.)
	Fold the Stack_Layout_Vars structure into the structure that contains
	it, the Label_Layout structure. Add a Closure_Id structure that
	contains a Proc_Id structure as well as extra information identifying
	the source location where the closure was created.

	Create "short" versions of the Proc_Layout structures, which contain
	only the first one or two of the three groups of fields. Previously,
	the Mercury compiler would define new C types when it generated such
	short structures. Since we are not defining new C types anymore, there
	must be a C type for every kind of structure the Mercury compiler can
	generate. We now also have separate variants for the layouts of
	user-defined and compiler-generated procedures, since the format
	of their procedure id information is different. While the runtime
	system refers to their procedure id information through a union,
	the C types of the structures generated by the Mercury compiler
	do not use a union, since a union cannot be initialized through
	its second member.

	Make the constant fields of structures const, since we now generate
	values of those structure types, and initialize them with constant
	data.

	Move the documentation of layout structures here from stack_layout.m.

runtime/mercury_ho_call.h:
	Instead of bodily including an MR_Proc_Id structure in closures,
	include a pointer to the more detailed MR_Closure_Id structure.

runtime/mercury_accurate_gc.c:
runtime/mercury_agc_debug.c:
runtime/mercury_init.h:
runtime/mercury_label.[ch]:
runtime/mercury_layout_util.[ch]:
	Minor updates to conform to changes in mercury_stack_layout.h.

runtime/mercury_goto.h:
	Use separate naming schemes for label layout structures and proc layout
	structures.

library/exception.m:
	Minor updates to conform to changes in mercury_stack_layout.h.

compiler/layout.m:
	A new module that defines data structures for label, proc and module
	layout structures and for closure id structures.

compiler/layout_out.m:
	A new module that converts the Mercury data structures of layout.m into
	declarations and definitions of C data structures.

compiler/stack_layout.m:
	Generate the new layout structures instead of rvals.

	Move the documentation of layout structures from here to
	runtime/mercury_stack_layout.h, since this module is no longer
	aware of some of their details.

compiler/llds.m:
	Make layout structures a separate kind of compiler-generated data.

compiler/llds_out.m:
	Remove the code for the output of layout structures; call layout_out.m
	instead.

compiler/code_gen.m:
compiler/code_info.m:
compiler/llds.m:
compiler/mercury_compile.m:
compiler/unify_gen.m:
	Instead of handling closure layouts like other static data, handle
	them separately. Add a counter to the code_info structure in order
	to allow closure id structures to be identified uniquely by a pair
	consisting of the id of the procedure that generates them and a closure
	sequence number within that procedure.

compiler/llds_common.m:
	Look for common rvals among the rvals in layout structures.

compiler/opt_debug.m:
	Generate developer-friendly names for layout structure references.

browser/dl.m:
	Update the code for constructing closure layouts.

Zoltan.

cvs diff: Diffing .
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/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing browser
Index: browser/dl.m
===================================================================
RCS file: /home/mercury1/repository/mercury/browser/dl.m,v
retrieving revision 1.5
diff -u -b -r1.5 dl.m
--- browser/dl.m	2000/10/16 01:33:23	1.5
+++ browser/dl.m	2001/01/07 11:32:57
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% Copyright (C) 1998-2000 The University of Melbourne.
+% Copyright (C) 1998-2001 The University of Melbourne.
 % This file may only be copied under the terms of the GNU Library General
 % Public License - see the file COPYING.LIB in the Mercury distribution.
 %-----------------------------------------------------------------------------%
@@ -103,20 +103,9 @@
 #endif
 }").
 
-:- type closure_layout
-	--->	closure_layout(
-			int,
-			string,
-			string,
-			string,
-			int,
-			int,
-			int
-		).
-
 :- type closure
 	--->	closure(
-			closure_layout,
+			int,		% really MR_Closure_Layout
 			c_pointer,
 			int
 		).
@@ -135,13 +124,51 @@
 		% convert the procedure address to a closure
 		%
 		NumCurriedInputArgs = 0,
-		ClosureLayout = closure_layout(0, "unknown", "unknown",
-			"unknown", -1, -1, -1),
+		ClosureLayout = make_closure_layout,
 		Closure = closure(ClosureLayout, Address, NumCurriedInputArgs),
 		private_builtin__unsafe_type_cast(Closure, Value),
 		Result = ok(Value)
 	}.
 	 
+:- pragma foreign_decl("C",
+"
+#include ""mercury_ho_call.h""
+").
+
+:- pragma foreign_code("C",
+"
+static	int	MR_dl_closure_counter = 0;
+").
+
+:- func make_closure_layout = int.
+
+:- pragma foreign_code("C", make_closure_layout = (ClosureLayout::out),
+	[will_not_call_mercury, thread_safe],
+"
+	extern	int			MR_dl_closure_counter;
+	MR_Closure_Id			*closure_id;
+	MR_Closure_Dyn_Link_Layout	*closure_layout;
+
+	closure_id = MR_GC_NEW(MR_Closure_Id);
+	closure_id->proc_id.MR_proc_user.MR_user_pred_or_func = MR_PREDICATE;
+	closure_id->proc_id.MR_proc_user.MR_user_decl_module = ""unknown"";
+	closure_id->proc_id.MR_proc_user.MR_user_def_module = ""unknown"";
+	closure_id->proc_id.MR_proc_user.MR_user_name = ""unknown"";
+	closure_id->proc_id.MR_proc_user.MR_user_arity = -1;
+	closure_id->proc_id.MR_proc_user.MR_user_mode = -1;
+	closure_id->module_name = ""dl"";
+	closure_id->file_name = ""dl.m"";
+	closure_id->line_number = ++MR_dl_closure_counter;
+	closure_id->goal_path = """";
+
+	closure_layout = MR_GC_NEW(MR_Closure_Dyn_Link_Layout);
+	closure_layout->closure_id = closure_id;
+	closure_layout->type_params = NULL;
+	closure_layout->num_all_args = 0;
+
+	ClosureLayout = (Word) closure_layout;
+").
+
 %
 % Check that the result type matches the information
 % in the procedure specification.
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.91
diff -u -b -r1.91 code_gen.m
--- compiler/code_gen.m	2000/12/13 00:57:15	1.91
+++ compiler/code_gen.m	2001/01/02 07:41:05
@@ -1,5 +1,5 @@
 %---------------------------------------------------------------------------%
-% Copyright (C) 1994-2000 The University of Melbourne.
+% Copyright (C) 1994-2001 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.
 %---------------------------------------------------------------------------%
@@ -332,9 +332,9 @@
 		GlobalData1 = GlobalData0
 	),
 
-	code_info__get_non_common_static_data(NonCommonStatics, CodeInfo, _),
-	global_data_add_new_non_common_static_datas(GlobalData1,
-		NonCommonStatics, GlobalData2),
+	code_info__get_closure_layouts(ClosureLayouts, CodeInfo, _),
+	global_data_add_new_closure_layouts(GlobalData1, ClosureLayouts,
+		GlobalData2),
 	code_util__make_proc_label(ModuleInfo, PredId, ProcId, ProcLabel),
 	maybe_add_tabling_pointer_var(ModuleInfo, PredId, ProcId, ProcInfo,
 		ProcLabel, GlobalData2, GlobalData),
@@ -1086,8 +1086,9 @@
 :- pred code_gen__generate_goal_2(hlds_goal_expr::in, hlds_goal_info::in,
 	code_model::in, code_tree::out, code_info::in, code_info::out) is det.
 
-code_gen__generate_goal_2(unify(_, _, _, Uni, _), _, CodeModel, Code) -->
-	unify_gen__generate_unification(CodeModel, Uni, Code).
+code_gen__generate_goal_2(unify(_, _, _, Uni, _), GoalInfo, CodeModel, Code)
+		-->
+	unify_gen__generate_unification(CodeModel, Uni, GoalInfo, Code).
 code_gen__generate_goal_2(conj(Goals), _GoalInfo, CodeModel, Code) -->
 	code_gen__generate_goals(Goals, CodeModel, Code).
 code_gen__generate_goal_2(par_conj(Goals, _SM), GoalInfo, CodeModel, Code) -->
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.261
diff -u -b -r1.261 code_info.m
--- compiler/code_info.m	2001/01/02 06:23:11	1.261
+++ compiler/code_info.m	2001/01/07 08:01:13
@@ -146,7 +146,7 @@
 		% been created during code generation and which do
 		% not have to be scanned by llds_common, since they
 		% have no common parts by construction.
-:- pred code_info__get_non_common_static_data(list(comp_gen_c_data)::out,
+:- pred code_info__get_closure_layouts(list(comp_gen_c_data)::out,
 	code_info::in, code_info::out) is det.
 
 :- pred code_info__get_max_reg_in_use_at_trace(int::out,
@@ -215,9 +215,15 @@
 :- pred code_info__set_temp_content_map(map(lval, slot_contents)::in,
 	code_info::in, code_info::out) is det.
 
-:- pred code_info__set_non_common_static_data(list(comp_gen_c_data)::in,
+:- pred code_info__set_closure_layouts(list(comp_gen_c_data)::in,
 	code_info::in, code_info::out) is det.
 
+:- pred code_info__get_closure_seq_counter(counter::out,
+	code_info::in, code_info::out) is det.
+
+:- pred code_info__set_closure_seq_counter(counter::in,
+	code_info::in, code_info::out) is det.
+
 :- pred code_info__set_created_temp_frame(bool::in,
 	code_info::in, code_info::out) is det.
 
@@ -326,10 +332,10 @@
 				% which would make it impossible to describe
 				% to gc what the slot contains after the end
 				% of the branched control structure.
-		comp_gen_c_data :: list(comp_gen_c_data),
-				% Static data structures created for this
-				% procedure which do not need to be scanned
-				% by llds_common.
+		closure_layout_seq :: counter,
+		closure_layouts :: list(comp_gen_c_data),
+				% Closure layout structures generated by this
+				% procedure.
 		max_reg_used :: int,
 				% At each call to MR_trace, we compute the
 				% highest rN register number that contains
@@ -432,6 +438,7 @@
 			LayoutMap,
 			0,
 			TempContentMap,
+			counter__init(1),
 			[],
 			-1,
 			no
@@ -480,7 +487,9 @@
 code_info__get_max_temp_slot_count(CI^code_info_persistent^stackslot_max,
 	CI, CI).
 code_info__get_temp_content_map(CI^code_info_persistent^temp_contents, CI, CI).
-code_info__get_non_common_static_data(CI^code_info_persistent^comp_gen_c_data,
+code_info__get_closure_seq_counter(CI^code_info_persistent^closure_layout_seq,
+	CI, CI).
+code_info__get_closure_layouts(CI^code_info_persistent^closure_layouts,
 	CI, CI).
 code_info__get_max_reg_in_use_at_trace(CI^code_info_persistent^max_reg_used,
 	CI, CI).
@@ -509,8 +518,10 @@
 	CI^code_info_persistent^stackslot_max := TM).
 code_info__set_temp_content_map(CM, CI,
 	CI^code_info_persistent^temp_contents := CM).
-code_info__set_non_common_static_data(CG, CI,
-	CI^code_info_persistent^comp_gen_c_data := CG).
+code_info__set_closure_seq_counter(CLS, CI,
+	CI^code_info_persistent^closure_layout_seq := CLS).
+code_info__set_closure_layouts(CG, CI,
+	CI^code_info_persistent^closure_layouts := CG).
 code_info__set_max_reg_in_use_at_trace(MR, CI,
 	CI^code_info_persistent^max_reg_used := MR).
 code_info__set_created_temp_frame(MR, CI,
@@ -635,10 +646,15 @@
 :- mode code_info__add_trace_layout_for_label(in, in, in,in,  in, in, out)
 	is det.
 
-:- pred code_info__add_non_common_static_data(comp_gen_c_data,
-	code_info, code_info).
-:- mode code_info__add_non_common_static_data(in, in, out) is det.
+:- pred code_info__get_cur_proc_label(proc_label, code_info, code_info).
+:- mode code_info__get_cur_proc_label(out, in, out) is det.
+
+:- pred code_info__get_next_closure_seq_no(int, code_info, code_info).
+:- mode code_info__get_next_closure_seq_no(out, in, out) is det.
 
+:- 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.
+
 %---------------------------------------------------------------------------%
 
 :- implementation.
@@ -890,11 +906,21 @@
 	code_info__get_temp_content_map(TempContentMap),
 	{ map__select(TempContentMap, TempsInUse, TempsInUseContentMap) },
 	{ map__to_assoc_list(TempsInUseContentMap, Temps) }.
+
+code_info__get_cur_proc_label(ProcLabel) -->
+	code_info__get_module_info(ModuleInfo),
+	code_info__get_pred_id(PredId),
+	code_info__get_proc_id(ProcId),
+	{ code_util__make_proc_label(ModuleInfo, PredId, ProcId, ProcLabel) }.
 
-code_info__add_non_common_static_data(NonCommonData) -->
-	code_info__get_non_common_static_data(NonCommonDatas0),
-	code_info__set_non_common_static_data(
-		[NonCommonData | NonCommonDatas0]).
+code_info__get_next_closure_seq_no(SeqNo) -->
+	code_info__get_closure_seq_counter(C0),
+	{ counter__allocate(SeqNo, C0, C) },
+	code_info__set_closure_seq_counter(C).
+
+code_info__add_closure_layout(ClosureLayout) -->
+	code_info__get_closure_layouts(ClosureLayouts),
+	code_info__set_closure_layouts([ClosureLayout | ClosureLayouts]).
 
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
Index: compiler/layout.m
===================================================================
RCS file: layout.m
diff -N layout.m
--- /dev/null	Thu Sep  2 15:00:04 1999
+++ layout.m	Tue Jan  2 18:41:10 2001
@@ -0,0 +1,131 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2001 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.
+%-----------------------------------------------------------------------------%
+%
+% Definitions of data structures for representing procedure layout structures
+% within the compiler. When output by layout_out.m, values of most these types
+% will correspond to the types defined in runtime/mercury_stack_layout.h;
+% the documentation of those types can be found there.
+% The code to generate the structures is in stack_layout.m.
+%
+% This module is should be, but as yet isn't, independent of whether we are
+% compiling to LLDS or MLDS.
+%
+% Author: zs.
+
+%-----------------------------------------------------------------------------%
+
+:- module layout.
+
+:- interface.
+
+:- import_module prog_data, trace_params, llds.
+:- import_module std_util, list, assoc_list.
+
+:- type proc_layout_stack_traversal
+	--->	proc_layout_stack_traversal(
+			entry_label		:: maybe(label),
+						% The proc entry label; will be
+						% `no' if we don't have static
+						% code addresses.
+			succip_slot		:: maybe(int),
+			stack_slot_count	:: int,
+			detism			:: determinism
+		).
+
+:- type proc_layout_exec_trace
+	--->	proc_layout_exec_trace(
+			call_label_layout	:: layout_name,
+			proc_body		:: maybe(rval),
+			var_names		:: list(int), % offsets
+			max_var_num		:: int,
+			max_r_num		:: int,
+			maybe_from_full_slot	:: maybe(int),
+			maybe_io_seq_slot	:: maybe(int),
+			maybe_trail_slot	:: maybe(int),
+			maybe_maxfr_slot	:: maybe(int),
+			eval_method		:: eval_method,
+			maybe_call_table_slot	:: maybe(int),
+			maybe_decl_debug_slot	:: maybe(int)
+		).
+
+:- type maybe_proc_id_and_exec_trace
+	--->	no_proc_id
+	;	proc_id_only
+	;	proc_id_and_exec_trace(proc_layout_exec_trace).
+
+:- type file_layout_data
+	--->	file_layout_data(
+			file_name		:: string,
+			line_no_label_list	:: assoc_list(int, layout_name)
+		).
+
+:- type label_var_info
+	--->	label_var_info(
+			encoded_var_count	:: int,
+			locns_types		:: rval,
+			var_nums		:: rval,
+			type_params		:: rval
+		).
+
+:- type layout_data
+	--->	label_layout_data(
+			label			:: label,
+			proc_layout_name	:: layout_name,
+			maybe_port		:: maybe(trace_port),
+			maybe_goal_path		:: maybe(int), % offset
+			maybe_var_info		:: maybe(label_var_info)
+		)
+	;	proc_layout_data(
+			proc_label,
+			proc_layout_stack_traversal,
+			maybe_proc_id_and_exec_trace
+		)
+	;	closure_proc_id_data(
+			caller_proc_label	:: proc_label,
+			caller_closure_seq_no	:: int,
+			closure_proc_label	:: proc_label,
+			closure_module_name	:: module_name,
+			closure_file_name	:: string,
+			closure_line_number	:: int,
+			closure_goal_path	:: string
+		)
+	;	module_layout_data(
+			module_name		:: module_name,
+			string_table_size	:: int,
+			string_table		:: string,
+			proc_layout_names	:: list(layout_name),
+			file_layouts		:: list(file_layout_data),
+			trace_level		:: trace_level
+		).
+
+:- type label_vars
+	--->	label_has_var_info
+	;	label_has_no_var_info.
+
+:- type proc_layout_user_or_compiler
+	--->	user
+	;	compiler.
+
+:- type proc_layout_kind
+	--->	proc_layout_traversal
+	;	proc_layout_proc_id(proc_layout_user_or_compiler)
+	;	proc_layout_exec_trace(proc_layout_user_or_compiler).
+
+:- type layout_name
+	--->	label_layout(label, label_vars)
+	;	proc_layout(proc_label, proc_layout_kind)
+		% A proc layout structure for stack tracing, accurate gc
+		% and/or execution tracing.
+	;	proc_layout_var_names(proc_label)
+		% A vector of variable names (represented as offsets into
+		% the string table) for a procedure layout structure.
+	;	closure_proc_id(proc_label, int, proc_label)
+	;	file_layout(module_name, int)
+	;	file_layout_line_number_vector(module_name, int)
+	;	file_layout_label_layout_vector(module_name, int)
+	;	module_layout_file_vector(module_name)
+	;	module_layout_proc_vector(module_name)
+	;	module_layout(module_name).
Index: compiler/layout_out.m
===================================================================
RCS file: layout_out.m
diff -N layout_out.m
--- /dev/null	Thu Sep  2 15:00:04 1999
+++ layout_out.m	Tue Jan  2 18:41:13 2001
@@ -0,0 +1,881 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2001 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.
+%-----------------------------------------------------------------------------%
+%
+% Author: zs.
+
+%-----------------------------------------------------------------------------%
+
+:- module layout_out.
+
+:- interface.
+
+:- import_module layout, llds, llds_out.
+:- import_module bool, io.
+
+:- pred output_layout_data_defn(layout_data::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+:- pred output_layout_data_decl(layout_data::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+:- pred output_layout_addr_storage_type_name(layout_name::in, bool::in,
+	io__state::di, io__state::uo) is det.
+
+:- pred output_layout_addr(layout_name::in,
+	io__state::di, io__state::uo) is det.
+
+:- pred layout_name_would_include_code_addr(layout_name::in, bool::out) is det.
+
+:- pred make_label_layout_name(label::in, string::out) is det.
+
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module prog_data, prog_out, hlds_pred, trace_params, c_util.
+:- import_module int, string, require, std_util, list.
+
+output_layout_data_defn(label_layout_data(Label, ProcLayoutAddr,
+		MaybePort, MaybeGoalPath, MaybeVarInfo), DeclSet0, DeclSet) -->
+	output_label_layout_data_defn(Label, ProcLayoutAddr,
+		MaybePort, MaybeGoalPath, MaybeVarInfo, DeclSet0, DeclSet).
+output_layout_data_defn(proc_layout_data(ProcLabel, Traversal, MaybeRest),
+		DeclSet0, DeclSet) -->
+	output_proc_layout_data_defn(ProcLabel, Traversal, MaybeRest,
+		DeclSet0, DeclSet).
+output_layout_data_defn(closure_proc_id_data(CallerProcLabel, SeqNo,
+		ProcLabel, ModuleName, FileName, LineNumber, GoalPath),
+		DeclSet0, DeclSet) -->
+	output_closure_proc_id_data_defn(CallerProcLabel, SeqNo, ProcLabel,
+		ModuleName, FileName, LineNumber, GoalPath, DeclSet0, DeclSet).
+output_layout_data_defn(module_layout_data(ModuleName, StringTableSize,
+		StringTable, ProcLayoutNames, FileLayouts, TraceLevel),
+		DeclSet0, DeclSet) -->
+	output_module_layout_data_defn(ModuleName, StringTableSize,
+		StringTable, ProcLayoutNames, FileLayouts, TraceLevel,
+		DeclSet0, DeclSet).
+
+:- pred extract_layout_name(layout_data::in, layout_name::out) is det.
+
+extract_layout_name(label_layout_data(Label, _, _, _, yes(_)), LayoutName) :-
+	LayoutName = label_layout(Label, label_has_var_info).
+extract_layout_name(label_layout_data(Label, _, _, _, no), LayoutName) :-
+	LayoutName = label_layout(Label, label_has_no_var_info).
+extract_layout_name(proc_layout_data(ProcLabel, _, MaybeRest), LayoutName) :-
+	maybe_proc_layout_and_exec_trace_kind(MaybeRest, ProcLabel, Kind),
+	LayoutName = proc_layout(ProcLabel, Kind).
+extract_layout_name(closure_proc_id_data(CallerProcLabel, SeqNo,
+		ClosureProcLabel, _, _, _, _),
+		closure_proc_id(CallerProcLabel, SeqNo, ClosureProcLabel)).
+extract_layout_name(module_layout_data(ModuleName, _,_,_,_,_), LayoutName) :-
+	LayoutName = module_layout(ModuleName).
+
+%-----------------------------------------------------------------------------%
+
+output_layout_data_decl(LayoutData, DeclSet0, DeclSet) -->
+	output_layout_addr_storage_type_name(LayoutName, no),
+	io__write_string(";\n"),
+	{ extract_layout_name(LayoutData, LayoutName) },
+	{ decl_set_insert(DeclSet0, data_addr(layout_addr(LayoutName)),
+		DeclSet) }.
+
+:- pred output_layout_decls(list(layout_name)::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+output_layout_decls([], DeclSet, DeclSet) --> [].
+output_layout_decls([LayoutName | LayoutNames], DeclSet0, DeclSet) -->
+	output_layout_decl(LayoutName, DeclSet0, DeclSet1),
+	output_layout_decls(LayoutNames, DeclSet1, DeclSet).
+
+:- pred output_layout_decl(layout_name::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+output_layout_decl(LayoutName, DeclSet0, DeclSet) -->
+	(
+		{ decl_set_is_member(data_addr(layout_addr(LayoutName)),
+			DeclSet0) }
+	->
+		{ DeclSet = DeclSet0 }
+	;
+		output_layout_addr_storage_type_name(LayoutName, no),
+		io__write_string(";\n"),
+		{ decl_set_insert(DeclSet0, data_addr(layout_addr(LayoutName)),
+			DeclSet) }
+	).
+
+	% This code should be kept in sync with output_layout_addr/2 below.
+make_label_layout_name(Label, Name) :-
+	llds_out__get_label(Label, yes, LabelName),
+	string__append_list([
+		mercury_data_prefix,
+		"_label_layout__",
+		LabelName
+	], Name).
+
+output_layout_addr(label_layout(Label, _)) -->
+	% This code should be kept in sync with make_label_layout_name/2 above.
+	io__write_string(mercury_data_prefix),
+	io__write_string("_label_layout__"),
+	{ llds_out__get_label(Label, yes, LabelName) },
+	io__write_string(LabelName).
+output_layout_addr(proc_layout(ProcLabel, _)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_proc_layout__"),
+	output_proc_label(ProcLabel).
+output_layout_addr(proc_layout_var_names(ProcLabel)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_var_names__"),
+	output_proc_label(ProcLabel).
+output_layout_addr(closure_proc_id(CallerProcLabel, SeqNo, _)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_closure_layout__"),
+	output_proc_label(CallerProcLabel),
+	io__write_string("_"),
+	io__write_int(SeqNo).
+output_layout_addr(file_layout(ModuleName, FileNum)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_file_layout__"),
+	{ llds_out__sym_name_mangle(ModuleName, ModuleNameStr) },
+	io__write_string(ModuleNameStr),
+	io__write_string("_"),
+	io__write_int(FileNum).
+output_layout_addr(file_layout_line_number_vector(ModuleName, FileNum)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_file_lines__"),
+	{ llds_out__sym_name_mangle(ModuleName, ModuleNameStr) },
+	io__write_string(ModuleNameStr),
+	io__write_string("_"),
+	io__write_int(FileNum).
+output_layout_addr(file_layout_label_layout_vector(ModuleName, FileNum)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_file_label_layouts__"),
+	{ llds_out__sym_name_mangle(ModuleName, ModuleNameStr) },
+	io__write_string(ModuleNameStr),
+	io__write_string("_"),
+	io__write_int(FileNum).
+output_layout_addr(module_layout_file_vector(ModuleName)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_module_files__"),
+	{ llds_out__sym_name_mangle(ModuleName, ModuleNameStr) },
+	io__write_string(ModuleNameStr).
+output_layout_addr(module_layout_proc_vector(ModuleName)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_module_procs__"),
+	{ llds_out__sym_name_mangle(ModuleName, ModuleNameStr) },
+	io__write_string(ModuleNameStr).
+output_layout_addr(module_layout(ModuleName)) -->
+	io__write_string(mercury_data_prefix),
+	io__write_string("_module_layout__"),
+	{ llds_out__sym_name_mangle(ModuleName, ModuleNameStr) },
+	io__write_string(ModuleNameStr).
+
+output_layout_addr_storage_type_name(label_layout(Label, LabelVars),
+		_BeingDefined) -->
+	io__write_string("static const "),
+	io__write_string(label_vars_to_type(LabelVars)),
+	io__write_string(" "),
+	output_layout_addr(label_layout(Label, LabelVars)).
+output_layout_addr_storage_type_name(proc_layout(ProcLabel, Kind),
+		_BeingDefined) -->
+	io__write_string("static MR_STATIC_CODE_CONST "),
+	io__write_string(kind_to_type(Kind)),
+	io__write_string(" "),
+	output_layout_addr(proc_layout(ProcLabel, Kind)).
+output_layout_addr_storage_type_name(proc_layout_var_names(ProcLabel),
+		_BeingDefined) -->
+	io__write_string("static const "),
+	io__write_string("MR_int_least16_t "),
+	output_layout_addr(proc_layout_var_names(ProcLabel)),
+	io__write_string("[]").
+output_layout_addr_storage_type_name(closure_proc_id(CallerProcLabel, SeqNo,
+		ClosureProcLabel), _BeingDefined) -->
+	io__write_string("static const "),
+	(
+		{ ClosureProcLabel = proc(_, _, _, _, _, _) },
+		io__write_string("MR_User_Closure_Id\n")
+	;
+		{ ClosureProcLabel = special_proc(_, _, _, _, _, _) },
+		io__write_string("MR_Compiler_Closure_Id\n")
+	),
+	output_layout_addr(closure_proc_id(CallerProcLabel, SeqNo,
+		ClosureProcLabel)).
+output_layout_addr_storage_type_name(file_layout(ModuleName, FileNum),
+		_BeingDefined) -->
+	io__write_string("static const MR_Module_File_Layout "),
+	output_layout_addr(file_layout(ModuleName, FileNum)).
+output_layout_addr_storage_type_name(file_layout_line_number_vector(
+		ModuleName, FileNum), _BeingDefined) -->
+	io__write_string("static const MR_int_least16_t "),
+	output_layout_addr(
+		file_layout_line_number_vector(ModuleName, FileNum)),
+	io__write_string("[]").
+output_layout_addr_storage_type_name(file_layout_label_layout_vector(
+		ModuleName, FileNum), _BeingDefined) -->
+	io__write_string("static const MR_Label_Layout *"),
+	output_layout_addr(
+		file_layout_label_layout_vector(ModuleName, FileNum)),
+	io__write_string("[]").
+output_layout_addr_storage_type_name(module_layout_file_vector(ModuleName),
+		_BeingDefined) -->
+	io__write_string("static const MR_Module_File_Layout *"),
+	output_layout_addr(module_layout_file_vector(ModuleName)),
+	io__write_string("[]").
+output_layout_addr_storage_type_name(module_layout_proc_vector(ModuleName),
+		_BeingDefined) -->
+	io__write_string("static const MR_Proc_Layout *"),
+	output_layout_addr(module_layout_proc_vector(ModuleName)),
+	io__write_string("[]").
+output_layout_addr_storage_type_name(module_layout(ModuleName),
+		_BeingDefined) -->
+	io__write_string("static const MR_Module_Layout "),
+	output_layout_addr(module_layout(ModuleName)).
+
+layout_name_would_include_code_addr(label_layout(_, _), no).
+layout_name_would_include_code_addr(proc_layout(_, _), yes).
+layout_name_would_include_code_addr(proc_layout_var_names(_), no).
+layout_name_would_include_code_addr(closure_proc_id(_, _, _), no).
+layout_name_would_include_code_addr(file_layout(_, _), no).
+layout_name_would_include_code_addr(file_layout_line_number_vector(_, _), no).
+layout_name_would_include_code_addr(file_layout_label_layout_vector(_, _), no).
+layout_name_would_include_code_addr(module_layout_file_vector(_), no).
+layout_name_would_include_code_addr(module_layout_proc_vector(_), no).
+layout_name_would_include_code_addr(module_layout(_), no).
+
+:- func label_vars_to_type(label_vars) = string.
+
+label_vars_to_type(label_has_var_info) =    "MR_Label_Layout".
+label_vars_to_type(label_has_no_var_info) = "MR_Label_Layout_No_Var_Info".
+
+:- func kind_to_type(proc_layout_kind) = string.
+
+kind_to_type(proc_layout_traversal) =            "MR_Proc_Layout_Traversal".
+kind_to_type(proc_layout_proc_id(user)) =        "MR_Proc_Layout_User".
+kind_to_type(proc_layout_proc_id(compiler)) =    "MR_Proc_Layout_Compiler".
+kind_to_type(proc_layout_exec_trace(user)) =     "MR_Proc_Layout_User_Exec".
+kind_to_type(proc_layout_exec_trace(compiler)) = "MR_Proc_Layout_Compiler_Exec".
+
+%-----------------------------------------------------------------------------%
+
+:- pred output_label_layout_data_defn(label::in, layout_name::in,
+	maybe(trace_port)::in, maybe(int)::in, maybe(label_var_info)::in,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
+
+output_label_layout_data_defn(Label, ProcLayoutAddr, MaybePort, MaybeGoalPath,
+		MaybeVarInfo, DeclSet0, DeclSet) -->
+	output_layout_decl(ProcLayoutAddr, DeclSet0, DeclSet1),
+	(
+		{ MaybeVarInfo = yes(VarInfo0) },
+		{ VarInfo0 = label_var_info(_,
+			LocnsTypes0, VarNums0, TypeParams0) },
+		output_rval_decls(LocnsTypes0, "", "", 0, _,
+			DeclSet1, DeclSet2),
+		output_rval_decls(VarNums0, "", "", 0, _,
+			DeclSet2, DeclSet3),
+		output_rval_decls(TypeParams0, "", "", 0, _,
+			DeclSet3, DeclSet4),
+		{ LabelVars = label_has_var_info }
+	;
+		{ MaybeVarInfo = no },
+		{ DeclSet4 = DeclSet0 },
+		{ LabelVars = label_has_no_var_info }
+	),
+	io__write_string("\n"),
+	{ LayoutName = label_layout(Label, LabelVars) },
+	output_layout_addr_storage_type_name(LayoutName, yes),
+	io__write_string(" = {\n"),
+	io__write_string("\t(const MR_Proc_Layout *) &"),
+	output_layout_addr(ProcLayoutAddr),
+	io__write_string(",\n\t"),
+	(
+		{ MaybePort = yes(Port) },
+		io__write_string(trace_port_to_string(Port))
+	;
+		{ MaybePort = no },
+		io__write_string("(MR_Trace_Port) -1")
+	),
+	io__write_string(",\n\t"),
+	(
+		{ MaybeGoalPath = yes(GoalPath) },
+		io__write_int(GoalPath)
+	;
+		{ MaybeGoalPath = no },
+		io__write_string("0")
+	),
+	io__write_string(",\n\t"),
+	(
+		{ MaybeVarInfo = yes(VarInfo) },
+		{ VarInfo = label_var_info(EncodedVarCount,
+			LocnsTypes, VarNums, TypeParams) },
+		io__write_int(EncodedVarCount),
+		io__write_string(",\n\t(const void *) "),
+		output_rval(LocnsTypes),
+		io__write_string(",\n\t(const MR_uint_least16_t *) "),
+		output_rval(VarNums),
+		io__write_string(",\n\t(const MR_Type_Param_Locns *) "),
+		output_rval(TypeParams)
+	;
+		{ MaybeVarInfo = no },
+		io__write_int(-1)
+	),
+	io__write_string("\n};\n"),
+	{ decl_set_insert(DeclSet4, data_addr(layout_addr(LayoutName)),
+		DeclSet) }.
+
+:- func trace_port_to_string(trace_port) = string.
+
+trace_port_to_string(call) =	 	    "MR_PORT_CALL".
+trace_port_to_string(exit) = 		    "MR_PORT_EXIT".
+trace_port_to_string(redo) = 		    "MR_PORT_REDO".
+trace_port_to_string(fail) = 		    "MR_PORT_FAIL".
+trace_port_to_string(exception) = 	    "MR_PORT_EXCEPTION".
+trace_port_to_string(ite_cond) = 	    "MR_PORT_COND".
+trace_port_to_string(ite_then) = 	    "MR_PORT_THEN".
+trace_port_to_string(ite_else) = 	    "MR_PORT_ELSE".
+trace_port_to_string(neg_enter) =   	    "MR_PORT_NEG_ENTER".
+trace_port_to_string(neg_success) = 	    "MR_PORT_NEG_SUCCESS".
+trace_port_to_string(neg_failure) = 	    "MR_PORT_NEG_FAILURE".
+trace_port_to_string(disj) =   	            "MR_PORT_DISJ".
+trace_port_to_string(switch) = 	            "MR_PORT_SWITCH".
+trace_port_to_string(nondet_pragma_first) = "MR_PORT_PRAGMA_FIRST".
+trace_port_to_string(nondet_pragma_later) = "MR_PORT_PRAGMA_LATER".
+
+%-----------------------------------------------------------------------------%
+
+:- pred output_proc_layout_data_defn(proc_label::in,
+	proc_layout_stack_traversal::in, maybe_proc_id_and_exec_trace::in,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
+
+output_proc_layout_data_defn(ProcLabel, Traversal, MaybeRest,
+		DeclSet0, DeclSet) -->
+	{ maybe_proc_layout_and_exec_trace_kind(MaybeRest, ProcLabel, Kind) },
+	(
+		{ MaybeRest = no_proc_id },
+		output_layout_traversal_decls(Traversal, DeclSet0, DeclSet3),
+		output_proc_layout_data_defn_start(ProcLabel, Kind, Traversal),
+		output_layout_no_proc_id_group,
+		output_proc_layout_data_defn_end
+	;
+		{ MaybeRest = proc_id_only },
+		output_layout_traversal_decls(Traversal, DeclSet0, DeclSet3),
+		output_proc_layout_data_defn_start(ProcLabel, Kind, Traversal),
+		output_layout_proc_id_group(ProcLabel),
+		output_layout_no_exec_trace_group,
+		output_proc_layout_data_defn_end
+	;
+		{ MaybeRest = proc_id_and_exec_trace(ExecTrace) },
+		{ VarNames = ExecTrace ^ var_names },
+		{ MaxVarNum = ExecTrace ^ max_var_num },
+		output_proc_layout_var_names(ProcLabel, VarNames, MaxVarNum,
+			DeclSet0, DeclSet1),
+		output_layout_traversal_decls(Traversal, DeclSet1, DeclSet2),
+		output_layout_exec_trace_decls(ProcLabel, ExecTrace,
+			DeclSet2, DeclSet3),
+
+		output_proc_layout_data_defn_start(ProcLabel, Kind, Traversal),
+		output_layout_proc_id_group(ProcLabel),
+		output_layout_exec_trace_group(ProcLabel, ExecTrace),
+		output_proc_layout_data_defn_end
+	),
+	{ decl_set_insert(DeclSet3, data_addr(
+		layout_addr(proc_layout(ProcLabel, Kind))), DeclSet) }.
+
+:- pred maybe_proc_layout_and_exec_trace_kind(maybe_proc_id_and_exec_trace::in,
+	proc_label::in, proc_layout_kind::out) is det.
+
+maybe_proc_layout_and_exec_trace_kind(MaybeRest, ProcLabel, Kind) :-
+	(
+		MaybeRest = no_proc_id,
+		Kind = proc_layout_traversal
+	;
+		MaybeRest = proc_id_only,
+		proc_label_user_or_compiler(ProcLabel, UserOrCompiler),
+		Kind = proc_layout_proc_id(UserOrCompiler)
+	;
+		MaybeRest = proc_id_and_exec_trace(_),
+		proc_label_user_or_compiler(ProcLabel, UserOrCompiler),
+		Kind = proc_layout_exec_trace(UserOrCompiler)
+	).
+
+:- pred proc_label_user_or_compiler(proc_label::in,
+	proc_layout_user_or_compiler::out) is det.
+
+proc_label_user_or_compiler(proc(_, _, _, _, _, _), user).
+proc_label_user_or_compiler(special_proc(_, _, _, _, _, _), compiler).
+
+:- pred output_proc_layout_data_defn_start(proc_label::in,
+	proc_layout_kind::in, proc_layout_stack_traversal::in,
+	io__state::di, io__state::uo) is det.
+
+output_proc_layout_data_defn_start(ProcLabel, Kind, Traversal) -->
+	io__write_string("\n"),
+	output_layout_addr_storage_type_name(proc_layout(ProcLabel, Kind),
+		yes),
+	io__write_string(" = {\n"),
+	output_layout_traversal_group(Traversal).
+
+:- pred output_proc_layout_data_defn_end(io__state::di, io__state::uo) is det.
+
+output_proc_layout_data_defn_end -->
+	io__write_string("};\n").
+
+:- pred output_layout_traversal_decls(proc_layout_stack_traversal::in,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
+
+output_layout_traversal_decls(Traversal, DeclSet0, DeclSet) -->
+	{ Traversal = proc_layout_stack_traversal(MaybeEntryLabel,
+		_MaybeSuccipSlot, _StackSlotCount, _Detism) },
+	(
+		{ MaybeEntryLabel = yes(EntryLabel) },
+		output_code_addr_decls(label(EntryLabel), "", "", 0, _,
+			DeclSet0, DeclSet)
+	;
+		{ MaybeEntryLabel = no },
+		{ DeclSet = DeclSet0 }
+	).
+
+:- pred output_layout_traversal_group(proc_layout_stack_traversal::in,
+	io__state::di, io__state::uo) is det.
+
+output_layout_traversal_group(Traversal) -->
+	{ Traversal = proc_layout_stack_traversal(MaybeEntryLabel,
+		MaybeSuccipSlot, StackSlotCount, Detism) },
+	io__write_string("\t{\n\t"),
+	(
+		{ MaybeEntryLabel = yes(EntryLabel) },
+		output_code_addr(label(EntryLabel))
+	;
+		{ MaybeEntryLabel = no },
+		% The actual code address will be put into the structure
+		% by module initialization code.
+		io__write_string("NULL")
+	),
+	io__write_string(",\n\t"),
+	(
+		{ MaybeSuccipSlot = yes(SuccipSlot) },
+		io__write_int(SuccipSlot)
+	;
+		{ MaybeSuccipSlot = no },
+		io__write_int(-1)
+	),
+	io__write_string(",\n\t"),
+	io__write_int(StackSlotCount),
+	io__write_string(",\n\t"),
+	io__write_string(detism_to_c_detism(Detism)),
+	io__write_string("\n\t},\n").
+
+:- func detism_to_c_detism(determinism) = string.
+
+detism_to_c_detism(det) =	  "MR_DETISM_DET".
+detism_to_c_detism(semidet) =	  "MR_DETISM_SEMI".
+detism_to_c_detism(nondet) =	  "MR_DETISM_NON".
+detism_to_c_detism(multidet) =	  "MR_DETISM_MULTI".
+detism_to_c_detism(erroneous) =	  "MR_DETISM_ERRONEOUS".
+detism_to_c_detism(failure) =	  "MR_DETISM_FAILURE".
+detism_to_c_detism(cc_nondet) =	  "MR_DETISM_CCNON".
+detism_to_c_detism(cc_multidet) = "MR_DETISM_CCMULTI".
+
+:- pred output_layout_proc_id_group(proc_label::in,
+	io__state::di, io__state::uo) is det.
+
+output_layout_proc_id_group(ProcLabel) -->
+	io__write_string("\t{\n"),
+	output_proc_id(ProcLabel),
+	io__write_string("\t},\n").
+
+:- pred output_layout_no_proc_id_group(io__state::di, io__state::uo) is det.
+
+output_layout_no_proc_id_group -->
+	io__write_string("\t-1\n").
+
+:- pred output_layout_exec_trace_decls(proc_label::in,
+	proc_layout_exec_trace::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+output_layout_exec_trace_decls(ProcLabel, ExecTrace, DeclSet0, DeclSet) -->
+	{ ExecTrace = proc_layout_exec_trace(CallLabelLayout, MaybeProcBody,
+		_VarNames, _MaxVarNum, _MaxRegNum, _MaybeFromFullSlot,
+		_MaybeIoSeqSlot, _MaybeTrailSlot, _MaybeMaxfrSlot, _EvalMethod,
+		_MaybeCallTableSlot, _MaybeDeclDebugSlot) },
+	{ ModuleName = get_defining_module_name(ProcLabel) },
+	output_layout_decl(CallLabelLayout, DeclSet0, DeclSet1),
+	output_layout_decl(module_layout(ModuleName), DeclSet1, DeclSet2),
+	(
+		{ MaybeProcBody = yes(ProcBody) },
+		output_rval_decls(ProcBody, "", "", 0, _, DeclSet2, DeclSet)
+	;
+		{ MaybeProcBody = no },
+		{ DeclSet = DeclSet2 }
+	).
+
+:- pred output_layout_exec_trace_group(proc_label::in,
+	proc_layout_exec_trace::in, io__state::di, io__state::uo) is det.
+
+output_layout_exec_trace_group(ProcLabel, ExecTrace) -->
+	{ ExecTrace = proc_layout_exec_trace(CallLabelLayout, MaybeProcBody,
+		_VarNames, MaxVarNum, MaxRegNum, MaybeFromFullSlot,
+		MaybeIoSeqSlot, MaybeTrailSlot, MaybeMaxfrSlot, EvalMethod,
+		MaybeCallTableSlot, MaybeDeclDebugSlot) },
+	io__write_string("\t{\n\t(const MR_Label_Layout *) &"),
+	output_layout_addr(CallLabelLayout),
+	io__write_string(",\n\t(const MR_Module_Layout *) &"),
+	{ ModuleName = get_defining_module_name(ProcLabel) },
+	output_layout_addr(module_layout(ModuleName)),
+	io__write_string(",\n\t"),
+	(
+		{ MaybeProcBody = yes(ProcBody) },
+		output_rval(ProcBody)
+	;
+		{ MaybeProcBody = no },
+		io__write_int(0)
+	),
+	io__write_string(",\n\t"),
+	output_layout_addr(proc_layout_var_names(ProcLabel)),
+	io__write_string(",\n\t"),
+	io__write_int(MaxVarNum),
+	io__write_string(",\n\t"),
+	io__write_int(MaxRegNum),
+	io__write_string(",\n\t"),
+	write_maybe_slot_num(MaybeFromFullSlot),
+	io__write_string(",\n\t"),
+	write_maybe_slot_num(MaybeIoSeqSlot),
+	io__write_string(",\n\t"),
+	write_maybe_slot_num(MaybeTrailSlot),
+	io__write_string(",\n\t"),
+	write_maybe_slot_num(MaybeMaxfrSlot),
+	io__write_string(",\n\t"),
+	io__write_string(eval_method_to_c_string(EvalMethod)),
+	io__write_string(",\n\t"),
+	write_maybe_slot_num(MaybeCallTableSlot),
+	io__write_string(",\n\t"),
+	write_maybe_slot_num(MaybeDeclDebugSlot),
+	io__write_string("\n\t}\n").
+
+:- pred write_maybe_slot_num(maybe(int)::in, io__state::di, io__state::uo)
+	is det.
+
+write_maybe_slot_num(yes(SlotNum)) -->
+	io__write_int(SlotNum).
+write_maybe_slot_num(no) -->
+	io__write_int(-1).
+
+:- func eval_method_to_c_string(eval_method) = string.
+
+eval_method_to_c_string(eval_normal) =	   "MR_EVAL_METHOD_NORMAL".
+eval_method_to_c_string(eval_loop_check) = "MR_EVAL_METHOD_LOOP_CHECK".
+eval_method_to_c_string(eval_memo) =       "MR_EVAL_METHOD_MEMO".
+eval_method_to_c_string(eval_table_io) =   "MR_EVAL_METHOD_TABLE_IO".
+eval_method_to_c_string(eval_minimal) =	   "MR_EVAL_METHOD_MINIMAL".
+
+:- pred output_proc_layout_var_names(proc_label::in, list(int)::in, int::in,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
+
+output_proc_layout_var_names(ProcLabel, VarNames, MaxVarNum,
+		DeclSet0, DeclSet) -->
+	{ list__length(VarNames, VarNameCount) },
+	{ require(unify(VarNameCount, MaxVarNum),
+		"output_proc_layout_var_names: VarNameCount != MaxVarNum") },
+	io__write_string("\n"),
+	output_layout_addr_storage_type_name(proc_layout_var_names(ProcLabel),
+		yes),
+	io__write_string(" = {\n"),
+	list__foldl(output_number_in_vector, VarNames),
+	io__write_string("};\n"),
+	{ decl_set_insert(DeclSet0, data_addr(
+		layout_addr(proc_layout_var_names(ProcLabel))), DeclSet) }.
+
+:- pred output_layout_no_exec_trace_group(io__state::di, io__state::uo) is det.
+
+output_layout_no_exec_trace_group -->
+	io__write_string("\t0\n").
+
+%-----------------------------------------------------------------------------%
+
+:- pred output_closure_proc_id_data_defn(proc_label::in, int::in,
+	proc_label::in, module_name::in, string::in, int::in, string::in,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
+
+output_closure_proc_id_data_defn(CallerProcLabel, SeqNo, ClosureProcLabel,
+		ModuleName, FileName, LineNumber, GoalPath,
+		DeclSet0, DeclSet) -->
+	io__write_string("\n"),
+	{ LayoutName = closure_proc_id(CallerProcLabel, SeqNo,
+		ClosureProcLabel) },
+	output_layout_addr_storage_type_name(LayoutName, yes),
+	io__write_string(" = {\n\t{\n"),
+	output_proc_id(ClosureProcLabel),
+	io__write_string("\t},\n\t"),
+	{ prog_out__sym_name_to_string(ModuleName, ModuleNameStr) },
+	quote_and_write_string(ModuleNameStr),
+	io__write_string(",\n\t"),
+	quote_and_write_string(FileName),
+	io__write_string(",\n\t"),
+	io__write_int(LineNumber),
+	io__write_string(",\n\t"),
+	quote_and_write_string(GoalPath),
+	io__write_string("\n};\n"),
+	{ decl_set_insert(DeclSet0,
+		data_addr(layout_addr(LayoutName)), DeclSet) }.
+
+:- pred output_proc_id(proc_label::in, io__state::di, io__state::uo) is det.
+
+output_proc_id(ProcLabel) -->
+	(
+		{ ProcLabel = proc(DefiningModule, PredOrFunc, DeclaringModule,
+			Name, Arity, Mode) },
+		{ prog_out__sym_name_to_string(DefiningModule,
+			DefiningModuleStr) },
+		{ prog_out__sym_name_to_string(DeclaringModule,
+			DeclaringModuleStr) },
+		{ proc_id_to_int(Mode, ModeInt) },
+		(
+			{ PredOrFunc = predicate },
+			io__write_string("\tMR_PREDICATE,\n\t")
+		;
+			{ PredOrFunc = function },
+			io__write_string("\tMR_FUNCTION,\n\t")
+		),
+		quote_and_write_string(DeclaringModuleStr),
+		io__write_string(",\n\t"),
+		quote_and_write_string(DefiningModuleStr),
+		io__write_string(",\n\t"),
+		quote_and_write_string(Name),
+		io__write_string(",\n\t"),
+		io__write_int(Arity),
+		io__write_string(",\n\t"),
+		io__write_int(ModeInt),
+		io__write_string("\n")
+	;
+		{ ProcLabel = special_proc(DefiningModule, PredName,
+			TypeModule, TypeName, TypeArity, Mode) },
+		{ prog_out__sym_name_to_string(DefiningModule,
+			DefiningModuleStr) },
+		{ prog_out__sym_name_to_string(TypeModule, TypeModuleStr) },
+		{ proc_id_to_int(Mode, ModeInt) },
+		io__write_string("\t"),
+		quote_and_write_string(TypeName),
+		io__write_string(",\n\t"),
+		quote_and_write_string(TypeModuleStr),
+		io__write_string(",\n\t"),
+		quote_and_write_string(DefiningModuleStr),
+		io__write_string(",\n\t"),
+		quote_and_write_string(PredName),
+		io__write_string(",\n\t"),
+		io__write_int(TypeArity),
+		io__write_string(",\n\t"),
+		io__write_int(ModeInt),
+		io__write_string("\n")
+	).
+
+%-----------------------------------------------------------------------------%
+
+:- pred output_module_layout_data_defn(module_name::in, int::in,
+	string::in, list(layout_name)::in, list(file_layout_data)::in,
+	trace_level::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+output_module_layout_data_defn(ModuleName, StringTableSize, StringTable,
+		ProcLayoutNames, FileLayouts, TraceLevel, DeclSet0, DeclSet)
+		-->
+	output_module_layout_proc_vector_defn(ModuleName, ProcLayoutNames,
+		ProcVectorName, DeclSet0, DeclSet1),
+	output_file_layout_data_defns(ModuleName, 0, FileLayouts,
+		FileLayoutNames, DeclSet1, DeclSet2),
+	output_file_layout_vector_data_defn(ModuleName, FileLayoutNames,
+		FileVectorName, DeclSet2, DeclSet3),
+
+	{ ModuleLayoutName = module_layout(ModuleName) },
+	io__write_string("\n"),
+	output_layout_addr_storage_type_name(ModuleLayoutName, yes),
+	io__write_string(" = {\n\t"),
+	{ prog_out__sym_name_to_string(ModuleName, ModuleNameStr) },
+	quote_and_write_string(ModuleNameStr),
+	io__write_string(",\n\t"),
+	io__write_int(StringTableSize),
+	io__write_string(",\n\t"""),
+	output_c_quoted_multi_string(StringTableSize, StringTable),
+	io__write_string(""",\n\t"),
+	{ list__length(ProcLayoutNames, ProcLayoutVectorLength) },
+	io__write_int(ProcLayoutVectorLength),
+	io__write_string(",\n\t"),
+	output_layout_addr(ProcVectorName),
+	io__write_string(",\n\t"),
+	{ list__length(FileLayouts, FileLayoutVectorLength) },
+	io__write_int(FileLayoutVectorLength),
+	io__write_string(",\n\t"),
+	output_layout_addr(FileVectorName),
+	io__write_string(",\n\t"),
+	io__write_string(trace_level_rep(TraceLevel)),
+	io__write_string("\n};\n"),
+	{ decl_set_insert(DeclSet3, data_addr(layout_addr(ModuleLayoutName)),
+		DeclSet) }.
+
+:- pred output_module_layout_proc_vector_defn(module_name::in,
+	list(layout_name)::in, layout_name::out, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+output_module_layout_proc_vector_defn(ModuleName, ProcLayoutNames,
+		VectorName, DeclSet0, DeclSet) -->
+	output_layout_decls(ProcLayoutNames, DeclSet0, DeclSet1),
+	{ VectorName = module_layout_proc_vector(ModuleName) },
+	io__write_string("\n"),
+	output_layout_addr_storage_type_name(VectorName, yes),
+	io__write_string(" = {\n"),
+	list__foldl(
+		output_layout_name_in_vector("(const MR_Proc_Layout *)\n\t&"),
+		ProcLayoutNames),
+	io__write_string("};\n"),
+	{ decl_set_insert(DeclSet1, data_addr(layout_addr(VectorName)),
+		DeclSet) }.
+
+%-----------------------------------------------------------------------------%
+
+:- pred output_file_layout_vector_data_defn(module_name::in,
+	list(layout_name)::in, layout_name::out, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+output_file_layout_vector_data_defn(ModuleName, FileLayoutNames, VectorName,
+		DeclSet0, DeclSet) -->
+	output_layout_decls(FileLayoutNames, DeclSet0, DeclSet1),
+	{ VectorName = module_layout_file_vector(ModuleName) },
+	io__write_string("\n"),
+	output_layout_addr_storage_type_name(VectorName, yes),
+	io__write_string(" = {\n"),
+	list__foldl(output_layout_name_in_vector("&"), FileLayoutNames),
+	io__write_string("};\n"),
+	{ decl_set_insert(DeclSet1, data_addr(layout_addr(VectorName)),
+		DeclSet) }.
+
+:- pred output_file_layout_data_defns(module_name::in, int::in,
+	list(file_layout_data)::in, list(layout_name)::out,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
+
+output_file_layout_data_defns(_, _, [], [], DeclSet, DeclSet) --> [].
+output_file_layout_data_defns(ModuleName, FileNum, [FileLayout | FileLayouts],
+		[FileLayoutName | FileLayoutNames], DeclSet0, DeclSet) -->
+	output_file_layout_data_defn(ModuleName, FileNum, FileLayout,
+		FileLayoutName, DeclSet0, DeclSet1),
+	output_file_layout_data_defns(ModuleName, FileNum + 1, FileLayouts,
+		FileLayoutNames, DeclSet1, DeclSet).
+
+:- pred output_file_layout_data_defn(module_name::in, int::in,
+	file_layout_data::in, layout_name::out,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
+
+output_file_layout_data_defn(ModuleName, FileNum, FileLayout, FileLayoutName,
+		DeclSet0, DeclSet) -->
+	{ FileLayout = file_layout_data(FileName, LineNoLabelList) },
+	{ list__map2(line_no_label_to_label_layout_addr, LineNoLabelList,
+		LineNos, LabelLayoutAddrs) },
+	output_data_addrs_decls(LabelLayoutAddrs, "", "", 0, _,
+		DeclSet0, DeclSet1),
+
+	{ list__length(LineNoLabelList, VectorLengths) },
+	output_file_layout_line_number_vector_defn(ModuleName, FileNum,
+		LineNos, LineNumberVectorName, DeclSet1, DeclSet2),
+	output_file_layout_label_layout_vector_defn(ModuleName, FileNum,
+		LabelLayoutAddrs, LabelVectorName, DeclSet2, DeclSet3),
+
+	{ FileLayoutName = file_layout(ModuleName, FileNum) },
+	io__write_string("\n"),
+	output_layout_addr_storage_type_name(FileLayoutName, yes),
+	io__write_string(" = {\n\t"),
+	quote_and_write_string(FileName),
+	io__write_string(",\n\t"),
+	io__write_int(VectorLengths),
+	io__write_string(",\n\t"),
+	output_layout_addr(LineNumberVectorName),
+	io__write_string(",\n\t"),
+	output_layout_addr(LabelVectorName),
+	io__write_string("\n};\n"),
+	{ decl_set_insert(DeclSet3, data_addr(layout_addr(FileLayoutName)),
+		DeclSet) }.
+
+:- pred output_file_layout_line_number_vector_defn(module_name::in, int::in,
+	list(int)::in, layout_name::out, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+output_file_layout_line_number_vector_defn(ModuleName, FileNum, LineNumbers,
+		LayoutName, DeclSet0, DeclSet) -->
+	{ LayoutName = file_layout_line_number_vector(ModuleName, FileNum) },
+	io__write_string("\n"),
+	output_layout_addr_storage_type_name(LayoutName, yes),
+	io__write_string(" = {\n"),
+	list__foldl(output_number_in_vector, LineNumbers),
+	io__write_string("};\n"),
+	{ decl_set_insert(DeclSet0, data_addr(layout_addr(LayoutName)),
+		DeclSet) }.
+
+:- pred output_file_layout_label_layout_vector_defn(module_name::in, int::in,
+	list(data_addr)::in, layout_name::out, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
+output_file_layout_label_layout_vector_defn(ModuleName, FileNum, LabelAddrs,
+		LayoutName, DeclSet0, DeclSet) -->
+	{ LayoutName = file_layout_label_layout_vector(ModuleName, FileNum) },
+	io__write_string("\n"),
+	output_layout_addr_storage_type_name(LayoutName, yes),
+	io__write_string(" = {\n"),
+	list__foldl(
+		output_data_addr_in_vector("(const MR_Label_Layout *)\n\t&"),
+		LabelAddrs),
+	io__write_string("};\n"),
+	{ decl_set_insert(DeclSet0, data_addr(layout_addr(LayoutName)),
+		DeclSet) }.
+
+%-----------------------------------------------------------------------------%
+
+:- pred line_no_label_to_label_layout_addr(pair(int, layout_name)::in,
+	int::out, data_addr::out) is det.
+
+line_no_label_to_label_layout_addr(LineNo - LabelLayout, LineNo, DataAddr) :-
+	DataAddr = layout_addr(LabelLayout).
+
+:- pred quote_and_write_string(string::in, io__state::di, io__state::uo)
+	is det.
+
+quote_and_write_string(String) -->
+	io__write_string(""""),
+	c_util__output_quoted_string(String),
+	io__write_string("""").
+
+:- pred file_name_mangle(string::in, string::out) is det.
+
+file_name_mangle(FileName, MangledFileName) :-
+	(
+		string__remove_suffix(FileName, ".m", BaseName),
+		string__is_alnum_or_underscore(BaseName)
+	->
+		string__append(BaseName, "_dot_m", MangledFileName)
+	;
+		llds_out__name_mangle(FileName, MangledFileName)
+	).
+
+:- pred output_number_in_vector(int::in, io__state::di, io__state::uo) is det.
+
+output_number_in_vector(Num) -->
+	io__write_string("\t"),
+	io__write_int(Num),
+	io__write_string(",\n").
+
+:- pred output_layout_name_in_vector(string::in, layout_name::in,
+	io__state::di, io__state::uo) is det.
+
+output_layout_name_in_vector(Prefix, Name) -->
+	io__write_string("\t"),
+	io__write_string(Prefix),
+	output_layout_addr(Name),
+	io__write_string(",\n").
+
+:- pred output_data_addr_in_vector(string::in, data_addr::in,
+	io__state::di, io__state::uo) is det.
+
+output_data_addr_in_vector(Prefix, DataAddr) -->
+	io__write_string("\t"),
+	io__write_string(Prefix),
+	output_data_addr(DataAddr),
+	io__write_string(",\n").
+
+%-----------------------------------------------------------------------------%
Index: compiler/llds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds.m,v
retrieving revision 1.271
diff -u -b -r1.271 llds.m
--- compiler/llds.m	2000/11/23 04:32:24	1.271
+++ compiler/llds.m	2001/01/02 07:41:15
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% Copyright (C) 1993-2000 The University of Melbourne.
+% Copyright (C) 1993-2001 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.
 %-----------------------------------------------------------------------------%
@@ -18,7 +18,7 @@
 
 :- import_module prog_data, (inst).
 :- import_module hlds_pred, hlds_goal, hlds_data.
-:- import_module code_model, rtti, builtin_ops.
+:- import_module code_model, rtti, layout, builtin_ops.
 :- import_module tree.
 
 :- import_module bool, assoc_list, list, map, set, std_util, counter.
@@ -80,6 +80,9 @@
 :- 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_add_new_non_common_static_datas(global_data::in,
 	list(comp_gen_c_data)::in, global_data::out) is det.
 
@@ -95,6 +98,9 @@
 :- 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.
 
@@ -154,6 +160,9 @@
 		)
 	;	rtti_data(
 			rtti_data
+		)
+	;	layout_data(
+			layout_data
 		).
 
 :- type comp_gen_c_module
@@ -895,21 +904,15 @@
 :- type data_addr
 	--->	data_addr(module_name, data_name)
 			% module name; which var
-	;	rtti_addr(rtti_type_id, rtti_name).
+	;	rtti_addr(rtti_type_id, rtti_name)
 			% type id; which var
+	;	layout_addr(layout_name).
 
 :- type data_name
 	--->	common(int)
 	;	base_typeclass_info(class_id, string)
 			% class name & class arity, names and arities of the
 			% types
-	;	module_layout
-			% Layout information for the current module.
-	;	proc_layout(label)
-			% Layout structure for the procedure with the given
-			% entry label.
-	;	internal_layout(label)
-			% Layout structure for the given internal label.
 	;	tabling_pointer(proc_label).
 			% A variable that contains a pointer that points to
 			% the table used to implement memoization, loopcheck
@@ -1077,6 +1080,10 @@
 	% (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.
+
 :- implementation.
 
 :- import_module require.
@@ -1237,6 +1244,14 @@
 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.
+get_proc_label(local(_, ProcLabel)) = ProcLabel.
+
+get_defining_module_name(proc(ModuleName, _, _, _, _, _)) = ModuleName.
+get_defining_module_name(special_proc(ModuleName, _, _, _, _, _)) = ModuleName.
+
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
@@ -1245,105 +1260,85 @@
 
 :- type global_data
 	--->	global_data(
-			proc_var_map,		% Information about the global
+			proc_var_map		:: proc_var_map,
+						% Information about the global
 						% variables defined by each
 						% procedure.
-			proc_layout_map,	% Information about the
+			proc_layout_map		:: proc_layout_map,
+						% Information about the
 						% layout structures defined
 						% by each procedure.
-			list(comp_gen_c_data)	% The list of global data
+			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.
 		).
 
-global_data_init(global_data(EmptyDataMap, EmptyLayoutMap, [])) :-
+global_data_init(global_data(EmptyDataMap, EmptyLayoutMap, [], [])) :-
 	map__init(EmptyDataMap),
 	map__init(EmptyLayoutMap).
 
-global_data_add_new_proc_var(GlobalData0, PredProcId, ProcVar,
-		GlobalData) :-
-	global_data_get_proc_var_map(GlobalData0, ProcVarMap0),
+global_data_add_new_proc_var(GlobalData0, PredProcId, ProcVar, GlobalData) :-
+	ProcVarMap0 = GlobalData0 ^ proc_var_map,
 	map__det_insert(ProcVarMap0, PredProcId, ProcVar, ProcVarMap),
-	global_data_set_proc_var_map(GlobalData0, ProcVarMap,
-		GlobalData).
+	GlobalData = GlobalData0 ^ proc_var_map := ProcVarMap.
 
 global_data_add_new_proc_layout(GlobalData0, PredProcId, ProcLayout,
 		GlobalData) :-
-	global_data_get_proc_layout_map(GlobalData0, ProcLayoutMap0),
+	ProcLayoutMap0 = GlobalData0 ^ proc_layout_map,
 	map__det_insert(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
-	global_data_set_proc_layout_map(GlobalData0, ProcLayoutMap,
-		GlobalData).
+	GlobalData = GlobalData0 ^ proc_layout_map := ProcLayoutMap.
 
 global_data_update_proc_layout(GlobalData0, PredProcId, ProcLayout,
 		GlobalData) :-
-	global_data_get_proc_layout_map(GlobalData0, ProcLayoutMap0),
+	ProcLayoutMap0 = GlobalData0 ^ proc_layout_map,
 	map__det_update(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
-	global_data_set_proc_layout_map(GlobalData0, ProcLayoutMap,
-		GlobalData).
+	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_add_new_non_common_static_datas(GlobalData0, NewNonCommonStatics,
 		GlobalData) :-
-	global_data_get_non_common_static_data(GlobalData0, NonCommonStatics0),
+	NonCommonStatics0 = GlobalData0 ^ non_common_data,
 	list__append(NewNonCommonStatics, NonCommonStatics0, NonCommonStatics),
-	global_data_set_non_common_static_data(GlobalData0, NonCommonStatics,
-		GlobalData).
+	GlobalData = GlobalData0 ^ non_common_data := NonCommonStatics.
 
-global_data_maybe_get_proc_layout(GlobalData0, PredProcId, ProcLayout) :-
-	global_data_get_proc_layout_map(GlobalData0, ProcLayoutMap),
+global_data_maybe_get_proc_layout(GlobalData, PredProcId, ProcLayout) :-
+	ProcLayoutMap = GlobalData ^ proc_layout_map,
 	map__search(ProcLayoutMap, PredProcId, ProcLayout).
 
-global_data_get_proc_layout(GlobalData0, PredProcId, ProcLayout) :-
-	global_data_get_proc_layout_map(GlobalData0, ProcLayoutMap),
+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) :-
-	global_data_get_proc_var_map(GlobalData, ProcVarMap),
+	ProcVarMap = GlobalData ^ proc_var_map,
 	map__values(ProcVarMap, ProcVars).
 
 global_data_get_all_proc_layouts(GlobalData, ProcLayouts) :-
-	global_data_get_proc_layout_map(GlobalData, ProcLayoutMap),
+	ProcLayoutMap = GlobalData ^ proc_layout_map,
 	map__values(ProcLayoutMap, ProcLayouts).
-
-global_data_get_all_non_common_static_data(GlobalData, NonCommonStatics) :-
-	global_data_get_non_common_static_data(GlobalData, NonCommonStatics).
 
-%-----------------------------------------------------------------------------%
+global_data_get_all_closure_layouts(GlobalData, ClosureLayouts) :-
+	ClosureLayouts = GlobalData ^ closure_layouts.
 
-:- pred global_data_get_proc_var_map(global_data::in, proc_var_map::out)
-	is det.
-:- pred global_data_get_proc_layout_map(global_data::in, proc_layout_map::out)
-	is det.
-:- pred global_data_get_non_common_static_data(global_data::in,
-	list(comp_gen_c_data)::out) is det.
-:- pred global_data_set_proc_var_map(global_data::in, proc_var_map::in,
-	global_data::out) is det.
-:- pred global_data_set_proc_layout_map(global_data::in, proc_layout_map::in,
-	global_data::out) is det.
-:- pred global_data_set_non_common_static_data(global_data::in,
-	list(comp_gen_c_data)::in, global_data::out) is det.
-
-global_data_get_proc_var_map(GD, A) :-
-	GD = global_data(A, _, _).
-
-global_data_get_proc_layout_map(GD, B) :-
-	GD = global_data(_, B, _).
-
-global_data_get_non_common_static_data(GD, C) :-
-	GD = global_data(_, _, C).
-
-global_data_set_proc_var_map(GD0, A, GD) :-
-	GD0 = global_data(_, B, C),
-	GD  = global_data(A, B, C).
-
-global_data_set_proc_layout_map(GD0, B, GD) :-
-	GD0 = global_data(A, _, C),
-	GD  = global_data(A, B, C).
-
-global_data_set_non_common_static_data(GD0, C, GD) :-
-	GD0 = global_data(A, B, _),
-	GD  = global_data(A, B, C).
+global_data_get_all_non_common_static_data(GlobalData, NonCommonStatics) :-
+	NonCommonStatics = GlobalData ^ non_common_data.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
Index: compiler/llds_common.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds_common.m,v
retrieving revision 1.35
diff -u -b -r1.35 llds_common.m
--- compiler/llds_common.m	2000/11/21 10:18:55	1.35
+++ compiler/llds_common.m	2001/01/02 07:41:19
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% Copyright (C) 1996-2000 The University of Melbourne.
+% Copyright (C) 1996-2001 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.
 %-----------------------------------------------------------------------------%
@@ -30,7 +30,7 @@
 
 :- implementation.
 
-:- import_module rtti, llds_out.
+:- import_module rtti, layout, llds_out.
 :- import_module bool, int, assoc_list, map, std_util, require.
 
 :- type cell_info
@@ -136,6 +136,73 @@
 	llds_common__process_maybe_rvals(Args0, Args, Info0, Info).
 llds_common__process_data(rtti_data(RttiData), rtti_data(RttiData),
 		Info, Info).
+llds_common__process_data(layout_data(LayoutData0), layout_data(LayoutData),
+		Info0, Info) :-
+	llds_common__process_layout_data(LayoutData0, LayoutData, Info0, Info).
+
+:- pred llds_common__process_layout_data(layout_data::in, layout_data::out,
+	common_info::in, common_info::out) is det.
+
+llds_common__process_layout_data(LayoutData0, LayoutData, Info0, Info) :-
+	LayoutData0 = label_layout_data(Label, ProcLayoutName,
+		MaybePort, MaybeGoalPath, MaybeVarInfo0),
+	(
+		MaybeVarInfo0 = no,
+		LayoutData = LayoutData0,
+		Info = Info0
+	;
+		MaybeVarInfo0 = yes(VarInfo0),
+		VarInfo0 = label_var_info(EncodedCount,
+			LocnsTypes0, VarNums0, TypeParams0),
+		llds_common__process_rval(LocnsTypes0, LocnsTypes,
+			Info0, Info1),
+		llds_common__process_rval(VarNums0, VarNums,
+			Info1, Info2),
+		llds_common__process_rval(TypeParams0, TypeParams,
+			Info2, Info),
+		VarInfo = label_var_info(EncodedCount,
+			LocnsTypes, VarNums, TypeParams),
+		MaybeVarInfo = yes(VarInfo),
+		LayoutData = label_layout_data(Label, ProcLayoutName,
+			MaybePort, MaybeGoalPath, MaybeVarInfo)
+	).
+llds_common__process_layout_data(LayoutData0, LayoutData, Info0, Info) :-
+	LayoutData0 = proc_layout_data(ProcLabel, Traversal, MaybeRest0),
+	(
+		MaybeRest0 = no_proc_id,
+		LayoutData = LayoutData0,
+		Info = Info0
+	;
+		MaybeRest0 = proc_id_only,
+		LayoutData = LayoutData0,
+		Info = Info0
+	;
+		MaybeRest0 = proc_id_and_exec_trace(Exec0),
+		llds_common__process_exec_trace(Exec0, Exec, Info0, Info),
+		MaybeRest = proc_id_and_exec_trace(Exec),
+		LayoutData = proc_layout_data(ProcLabel, Traversal, MaybeRest)
+	).
+llds_common__process_layout_data(LayoutData0, LayoutData, Info, Info) :-
+	LayoutData0 = closure_proc_id_data(_, _, _, _, _, _, _),
+	LayoutData = LayoutData0.
+llds_common__process_layout_data(LayoutData0, LayoutData, Info, Info) :-
+	LayoutData0 = module_layout_data(_, _, _, _, _, _),
+	LayoutData = LayoutData0.
+
+:- pred llds_common__process_exec_trace(proc_layout_exec_trace::in,
+	proc_layout_exec_trace::out, common_info::in, common_info::out) is det.
+
+llds_common__process_exec_trace(ExecTrace0, ExecTrace, Info0, Info) :-
+	ExecTrace0 = proc_layout_exec_trace(CallLabel, MaybeProcBody0,
+		VarNames, MaxVarNum, MaxReg, MaybeFromFullSlot, MaybeIoSeqSlot,
+		MaybeTrailSlot, MaybeMaxfrSlot, EvalMethod, MaybeCallTableSlot,
+		MaybeDeclDebugSlot),
+	llds_common__process_maybe_rval(MaybeProcBody0, MaybeProcBody,
+		Info0, Info),
+	ExecTrace = proc_layout_exec_trace(CallLabel, MaybeProcBody,
+		VarNames, MaxVarNum, MaxReg, MaybeFromFullSlot, MaybeIoSeqSlot,
+		MaybeTrailSlot, MaybeMaxfrSlot, EvalMethod, MaybeCallTableSlot,
+		MaybeDeclDebugSlot).
 
 :- pred llds_common__process_procs(list(c_procedure)::in,
 	list(c_procedure)::out, common_info::in, common_info::out) is det.
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.168
diff -u -b -r1.168 llds_out.m
--- compiler/llds_out.m	2000/12/04 18:28:18	1.168
+++ compiler/llds_out.m	2001/01/02 07:41:21
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% Copyright (C) 1996-2000 The University of Melbourne.
+% Copyright (C) 1996-2001 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.
 %-----------------------------------------------------------------------------%
@@ -19,7 +19,7 @@
 
 :- import_module llds, builtin_ops, prog_data, hlds_data, rl_file.
 :- import_module globals.
-:- import_module list, set_bbbtree, bool, io, std_util.
+:- import_module bool, std_util, list, map, io.
 
 	% Given a 'c_file' structure, output the LLDS code inside it
 	% into one or more .c files, depending on the setting of the
@@ -27,9 +27,8 @@
 	% labels that have layout structures. The third gives the Aditi-RL
 	% code for the module.
 
-:- pred output_llds(c_file, set_bbbtree(label), maybe(rl_file),
-		io__state, io__state).
-:- mode output_llds(in, in, in, di, uo) is det.
+:- pred output_llds(c_file::in, map(label, data_addr)::in, maybe(rl_file)::in,
+	io__state::di, io__state::uo) is det.
 
 	% output_c_file_intro_and_grade(SourceFileName, Version)
 	% outputs a comment which includes the settings used to generate
@@ -87,6 +86,10 @@
 	int::in, int::out, decl_set::in, decl_set::out,
 	io__state::di, io__state::uo) is det.
 
+:- pred output_data_addrs_decls(list(data_addr)::in, string::in, string::in,
+	int::in, int::out, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
+
 :- pred output_data_addr(data_addr::in, io__state::di, io__state::uo) is det.
 
 	% All the C data structures we generate which are either fully static
@@ -201,9 +204,6 @@
 	% Convert a label to a string description of the stack layout
 	% structure of that label.
 
-:- pred llds_out__make_stack_layout_name(label, string).
-:- mode llds_out__make_stack_layout_name(in, out) is det.
-
 	% Returns the name of the initialization function
 	% for a given module.
 
@@ -216,12 +216,6 @@
 :- pred llds_out__make_rl_data_name(module_name, string).
 :- mode llds_out__make_rl_data_name(in, out) is det.
 
-:- pred llds_out__trace_port_to_string(trace_port, string).
-:- mode llds_out__trace_port_to_string(in, out) is det.
-
-:- pred llds_out__trace_port_to_num(trace_port, int).
-:- mode llds_out__trace_port_to_num(in, out) is det.
-
 	% The following are exported to rtti_out. It may be worthwhile
 	% to put these in a new module (maybe llds_out_util).
 
@@ -262,13 +256,13 @@
 
 :- implementation.
 
-:- import_module rtti, rtti_out, options, trace_params.
+:- import_module rtti, rtti_out, layout, layout_out, options, trace_params.
 :- import_module exprn_aux, prog_util, prog_out, hlds_pred.
 :- import_module export, mercury_to_mercury, modules.
 :- import_module c_util.
 
 :- import_module int, char, string, std_util.
-:- import_module map, set, bintree_set, assoc_list, require.
+:- import_module set, bintree_set, assoc_list, require.
 :- import_module varset, term.
 :- import_module library.	% for the version number.
 
@@ -312,7 +306,7 @@
 	).
 
 :- pred output_split_user_foreign_codes(list(user_foreign_code)::in,
-	module_name::in, list(foreign_decl_code)::in, set_bbbtree(label)::in,
+	module_name::in, list(foreign_decl_code)::in, map(label, data_addr)::in,
 	int::in, int::out, io__state::di, io__state::uo) is det.
 
 output_split_user_foreign_codes([], _, _, _, Num, Num) --> [].
@@ -326,7 +320,7 @@
 		C_HeaderLines, StackLayoutLabels, Num1, Num).
 
 :- pred output_split_c_exports(list(foreign_export)::in,
-	module_name::in, list(foreign_decl_code)::in, set_bbbtree(label)::in,
+	module_name::in, list(foreign_decl_code)::in, map(label, data_addr)::in,
 	int::in, int::out, io__state::di, io__state::uo) is det.
 
 output_split_c_exports([], _, _, _, Num, Num) --> [].
@@ -340,7 +334,7 @@
 		StackLayoutLabels, Num1, Num).
 
 :- pred output_split_comp_gen_c_vars(list(comp_gen_c_var)::in,
-	module_name::in, list(foreign_decl_code)::in, set_bbbtree(label)::in,
+	module_name::in, list(foreign_decl_code)::in, map(label, data_addr)::in,
 	int::in, int::out, io__state::di, io__state::uo) is det.
 
 output_split_comp_gen_c_vars([], _, _, _, Num, Num) --> [].
@@ -353,7 +347,7 @@
 		StackLayoutLabels, Num1, Num).
 
 :- pred output_split_comp_gen_c_datas(list(comp_gen_c_data)::in,
-	module_name::in, list(foreign_decl_code)::in, set_bbbtree(label)::in,
+	module_name::in, list(foreign_decl_code)::in, map(label, data_addr)::in,
 	int::in, int::out, io__state::di, io__state::uo) is det.
 
 output_split_comp_gen_c_datas([], _, _, _, Num, Num) --> [].
@@ -366,7 +360,7 @@
 		StackLayoutLabels, Num1, Num).
 
 :- pred output_split_comp_gen_c_modules(list(comp_gen_c_module)::in,
-	module_name::in, list(foreign_decl_code)::in, set_bbbtree(label)::in,
+	module_name::in, list(foreign_decl_code)::in, map(label, data_addr)::in,
 	int::in, int::out, io__state::di, io__state::uo) is det.
 
 output_split_comp_gen_c_modules([], _, _, _, Num, Num) --> [].
@@ -380,7 +374,7 @@
 		StackLayoutLabels, Num1, Num).
 
 :- pred output_split_c_file_init(module_name, list(comp_gen_c_module),
-	list(comp_gen_c_data), set_bbbtree(label), maybe(rl_file),
+	list(comp_gen_c_data), map(label, data_addr), maybe(rl_file),
 	io__state, io__state).
 :- mode output_split_c_file_init(in, in, in, in, in, di, uo) is det.
 
@@ -454,7 +448,7 @@
 convert_bool_to_string(no, "no").
 convert_bool_to_string(yes, "yes").
 
-:- pred output_single_c_file(c_file, maybe(int), set_bbbtree(label),
+:- pred output_single_c_file(c_file, maybe(int), map(label, data_addr),
 	maybe(rl_file), io__state, io__state).
 :- mode output_single_c_file(in, in, in, in, di, uo) is det.
 
@@ -516,7 +510,7 @@
 	).
 
 :- pred output_c_module_init_list(module_name::in, list(comp_gen_c_module)::in,
-	list(comp_gen_c_data)::in, set_bbbtree(label)::in,
+	list(comp_gen_c_data)::in, map(label, data_addr)::in,
 	io__state::di, io__state::uo) is det.
 
 output_c_module_init_list(ModuleName, Modules, Datas, StackLayoutLabels) -->
@@ -616,16 +610,16 @@
 		"static const void *const MR_grade = &MR_GRADE_VAR;\n").
 
 :- pred module_defines_label_with_layout(comp_gen_c_module::in,
-	set_bbbtree(label)::in) is semidet.
+	map(label, data_addr)::in) is semidet.
 
 module_defines_label_with_layout(Module, StackLayoutLabels) :-
 		% Checking whether the set is empty or not
 		% allows us to avoid calling gather_c_module_labels.
-	\+ set_bbbtree__empty(StackLayoutLabels),
+	\+ map__is_empty(StackLayoutLabels),
 	Module = comp_gen_c_module(_, Procedures),
 	gather_c_module_labels(Procedures, Labels),
 	list__member(Label, Labels),
-	set_bbbtree__member(Label, StackLayoutLabels).
+	map__search(StackLayoutLabels, Label, _).
 
 :- pred output_init_bunch_defs(list(list(comp_gen_c_module))::in,
 	module_name::in, string::in, int::in, bool::in,
@@ -715,12 +709,12 @@
 output_debugger_init_list_decls([]) --> [].
 output_debugger_init_list_decls([Data | Datas]) -->
 	(
-		{ Data = comp_gen_c_data(ModuleName, DataName, _, _, _, _) },
-		{ DataName = module_layout }
+		{ Data = layout_data(LayoutData) },
+		{ LayoutData = module_layout_data(ModuleName, _, _, _, _, _) }
 	->
 		{ decl_set_init(DeclSet0) },
-		output_data_addr_decls(data_addr(ModuleName, DataName), "", "",
-			0, _, DeclSet0, _DeclSet)
+		output_data_addr_decls(layout_addr(module_layout(ModuleName)),
+			"", "", 0, _, DeclSet0, _DeclSet)
 	;
 		[]
 	),
@@ -736,13 +730,13 @@
 output_debugger_init_list([]) --> [].
 output_debugger_init_list([Data | Datas]) -->
 	(
-		{ Data = comp_gen_c_data(ModuleName, DataName, _, _, _, _) },
-		{ DataName = module_layout }
+		{ Data = layout_data(LayoutData) },
+		{ LayoutData = module_layout_data(ModuleName, _, _, _, _, _) }
 	->
 		io__write_string("\t\tif (MR_register_module_layout != NULL) {\n"),
 		io__write_string("\t\t\t(*MR_register_module_layout)("),
-		io__write_string("(MR_Module_Layout *)\n\t\t\t\t&"),
-		output_data_addr(ModuleName, DataName),
+		io__write_string("\n\t\t\t\t&"),
+		output_layout_addr(module_layout(ModuleName)),
 		io__write_string(");\n\t\t}\n")
 	;
 		[]
@@ -851,9 +845,11 @@
 	{ decl_set_insert(DeclSet0, DeclId, DeclSet) }.
 output_c_data_type_def(rtti_data(RttiData), DeclSet0, DeclSet) -->
 	output_rtti_data_decl(RttiData, DeclSet0, DeclSet).
+output_c_data_type_def(layout_data(LayoutData), DeclSet0, DeclSet) -->
+	output_layout_data_decl(LayoutData, DeclSet0, DeclSet).
 
 :- pred output_comp_gen_c_module_list(list(comp_gen_c_module)::in,
-	set_bbbtree(label)::in, decl_set::in, decl_set::out,
+	map(label, data_addr)::in, decl_set::in, decl_set::out,
 	io__state::di, io__state::uo) is det.
 
 output_comp_gen_c_module_list([], _, DeclSet, DeclSet) --> [].
@@ -864,13 +860,14 @@
 	output_comp_gen_c_module_list(Modules, StackLayoutLabels,
 		DeclSet1, DeclSet).
 
-:- pred output_comp_gen_c_module(comp_gen_c_module::in, set_bbbtree(label)::in,
+:- pred output_comp_gen_c_module(comp_gen_c_module::in, map(label, data_addr)::in,
 	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
 
 output_comp_gen_c_module(comp_gen_c_module(ModuleName, Procedures),
 		StackLayoutLabels, DeclSet0, DeclSet) -->
 	io__write_string("\n"),
-	output_c_procedure_list_decls(Procedures, DeclSet0, DeclSet),
+	output_c_procedure_list_decls(Procedures, StackLayoutLabels,
+		DeclSet0, DeclSet),
 	io__write_string("\n"),
 	io__write_string("MR_BEGIN_MODULE("),
 	io__write_string(ModuleName),
@@ -953,38 +950,8 @@
 	{ decl_set_insert(DeclSet1, DeclId, DeclSet) }.
 output_comp_gen_c_data(rtti_data(RttiData), DeclSet0, DeclSet) -->
 	output_rtti_data_defn(RttiData, DeclSet0, DeclSet).
-
-llds_out__trace_port_to_string(call, "MR_PORT_CALL").
-llds_out__trace_port_to_string(exit, "MR_PORT_EXIT").
-llds_out__trace_port_to_string(redo, "MR_PORT_REDO").
-llds_out__trace_port_to_string(fail, "MR_PORT_FAIL").
-llds_out__trace_port_to_string(exception, "MR_PORT_EXCEPTION").
-llds_out__trace_port_to_string(ite_cond, "MR_PORT_COND").
-llds_out__trace_port_to_string(ite_then, "MR_PORT_THEN").
-llds_out__trace_port_to_string(ite_else, "MR_PORT_ELSE").
-llds_out__trace_port_to_string(neg_enter,   "MR_PORT_NEG_ENTER").
-llds_out__trace_port_to_string(neg_success, "MR_PORT_NEG_SUCCESS").
-llds_out__trace_port_to_string(neg_failure, "MR_PORT_NEG_FAILURE").
-llds_out__trace_port_to_string(disj,   "MR_PORT_DISJ").
-llds_out__trace_port_to_string(switch, "MR_PORT_SWITCH").
-llds_out__trace_port_to_string(nondet_pragma_first, "MR_PORT_PRAGMA_FIRST").
-llds_out__trace_port_to_string(nondet_pragma_later, "MR_PORT_PRAGMA_LATER").
-
-llds_out__trace_port_to_num(call, 0).
-llds_out__trace_port_to_num(exit, 1).
-llds_out__trace_port_to_num(redo, 2).
-llds_out__trace_port_to_num(fail, 3).
-llds_out__trace_port_to_num(exception, 4).
-llds_out__trace_port_to_num(ite_cond, 5).
-llds_out__trace_port_to_num(ite_then, 6).
-llds_out__trace_port_to_num(ite_else, 7).
-llds_out__trace_port_to_num(neg_enter,   8).
-llds_out__trace_port_to_num(neg_success, 9).
-llds_out__trace_port_to_num(neg_failure, 10).
-llds_out__trace_port_to_num(disj,   11).
-llds_out__trace_port_to_num(switch, 12).
-llds_out__trace_port_to_num(nondet_pragma_first, 13).
-llds_out__trace_port_to_num(nondet_pragma_later, 14).
+output_comp_gen_c_data(layout_data(LayoutData), DeclSet0, DeclSet) -->
+	output_layout_data_defn(LayoutData, DeclSet0, DeclSet).
 
 :- pred output_user_foreign_code_list(list(user_foreign_code)::in,
 	io__state::di, io__state::uo) is det.
@@ -1060,7 +1027,7 @@
 	io__write_string(F),
 	output_exported_c_functions(Fs).
 
-:- pred output_c_label_decl_list(list(label), set_bbbtree(label),
+:- pred output_c_label_decl_list(list(label), map(label, data_addr),
 		decl_set, decl_set, io__state, io__state).
 :- mode output_c_label_decl_list(in, in, in, out, di, uo) is det.
 
@@ -1070,16 +1037,15 @@
 	output_c_label_decl(Label, StackLayoutLabels, DeclSet0, DeclSet1),
 	output_c_label_decl_list(Labels, StackLayoutLabels, DeclSet1, DeclSet).
 
-:- pred output_c_label_decl(label, set_bbbtree(label), decl_set, decl_set,
-		io__state, io__state).
-:- mode output_c_label_decl(in, in, in, out, di, uo) is det.
+:- pred output_c_label_decl(label::in, map(label, data_addr)::in,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
 
 output_c_label_decl(Label, StackLayoutLabels, DeclSet0, DeclSet) -->
 	%
 	% Declare the stack layout entry for this label, if needed.
 	%
-	( { set_bbbtree__member(Label, StackLayoutLabels) } ->
-		output_stack_layout_decl(Label, DeclSet0, DeclSet1)
+	( { map__search(StackLayoutLabels, Label, DataAddr) } ->
+		output_stack_layout_decl(DataAddr, DeclSet0, DeclSet1)
 	;
 		{ DeclSet1 = DeclSet0 }
 	),
@@ -1114,32 +1080,13 @@
 	output_label(Label),
 	io__write_string(");\n").
 
-:- pred output_stack_layout_decl(label, decl_set, decl_set,
-		io__state, io__state).
-:- mode output_stack_layout_decl(in, in, out, di, uo) is det.
+:- pred output_stack_layout_decl(data_addr::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
 
-output_stack_layout_decl(Label, DeclSet0, DeclSet) -->
-	{ Label = local(_, _) ->
-		DataName = internal_layout(Label)
-	;
-		DataName = proc_layout(Label)
-	},
-	{ ProcLabel = get_proc_label(Label) },
-	{ ModuleName = get_defining_module_name(ProcLabel) },
-	{ DataAddr = data_addr(ModuleName, DataName) },
+output_stack_layout_decl(DataAddr, DeclSet0, DeclSet) -->
 	output_data_addr_decls(DataAddr, "", "", 0, _, DeclSet0, DeclSet).
 
-:- func get_proc_label(label) = proc_label.
-get_proc_label(exported(ProcLabel)) = ProcLabel.
-get_proc_label(local(ProcLabel)) = ProcLabel.
-get_proc_label(c_local(ProcLabel)) = ProcLabel.
-get_proc_label(local(_, ProcLabel)) = ProcLabel.
-
-:- func get_defining_module_name(proc_label) = module_name.
-get_defining_module_name(proc(ModuleName, _, _, _, _, _)) = ModuleName.
-get_defining_module_name(special_proc(ModuleName, _, _, _, _, _)) = ModuleName.
-
-:- pred output_c_label_init_list(list(label), set_bbbtree(label),
+:- pred output_c_label_init_list(list(label), map(label, data_addr),
 	io__state, io__state).
 :- mode output_c_label_init_list(in, in, di, uo) is det.
 
@@ -1148,13 +1095,13 @@
 	output_c_label_init(Label, StackLayoutLabels),
 	output_c_label_init_list(Labels, StackLayoutLabels).
 
-:- pred output_c_label_init(label, set_bbbtree(label), io__state, io__state).
+:- pred output_c_label_init(label, map(label, data_addr), io__state, io__state).
 :- mode output_c_label_init(in, in, di, uo) is det.
 
 output_c_label_init(Label, StackLayoutLabels) -->
-	{ set_bbbtree__member(Label, StackLayoutLabels) ->
+	{ map__search(StackLayoutLabels, Label, DataAddr) ->
 		SuffixOpen = "_sl(",
-		( label_is_proc_entry(Label, yes) ->
+		( DataAddr = layout_addr(proc_layout(_, _)) ->
 			% Labels whose stack layouts are proc layouts may need
 			% to have the code address in that layout initialized
 			% at run time (if code addresses are not static).
@@ -1201,35 +1148,35 @@
 label_is_proc_entry(local(_), yes).
 label_is_proc_entry(exported(_), yes).
 
-:- pred output_c_procedure_list_decls(list(c_procedure), decl_set, decl_set,
-	io__state, io__state).
-:- mode output_c_procedure_list_decls(in, in, out, di, uo) is det.
+:- pred output_c_procedure_list_decls(list(c_procedure)::in,
+	map(label, data_addr)::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
 
-output_c_procedure_list_decls([], DeclSet, DeclSet) --> [].
-output_c_procedure_list_decls([Proc | Procs], DeclSet0, DeclSet) -->
-	output_c_procedure_decls(Proc, DeclSet0, DeclSet1),
-	output_c_procedure_list_decls(Procs, DeclSet1, DeclSet).
+output_c_procedure_list_decls([], _, DeclSet, DeclSet) --> [].
+output_c_procedure_list_decls([Proc | Procs], StackLayoutLabels,
+		DeclSet0, DeclSet) -->
+	output_c_procedure_decls(Proc, StackLayoutLabels, DeclSet0, DeclSet1),
+	output_c_procedure_list_decls(Procs, StackLayoutLabels,
+		DeclSet1, DeclSet).
 
-:- pred output_c_procedure_list(list(c_procedure), bool, bool,
-				io__state, io__state).
-:- mode output_c_procedure_list(in, in, in, di, uo) is det.
+:- pred output_c_procedure_list(list(c_procedure)::in, bool::in, bool::in,
+	io__state::di, io__state::uo) is det.
 
 output_c_procedure_list([], _, _) --> [].
 output_c_procedure_list([Proc | Procs], PrintComments, EmitCLoops) -->
 	output_c_procedure(Proc, PrintComments, EmitCLoops),
 	output_c_procedure_list(Procs, PrintComments, EmitCLoops).
 
-:- pred output_c_procedure_decls(c_procedure, decl_set, decl_set,
-				io__state, io__state).
-:- mode output_c_procedure_decls(in, in, out, di, uo) is det.
+:- pred output_c_procedure_decls(c_procedure::in, map(label, data_addr)::in,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
 
-output_c_procedure_decls(Proc, DeclSet0, DeclSet) -->
+output_c_procedure_decls(Proc, StackLayoutLabels, DeclSet0, DeclSet) -->
 	{ Proc = c_procedure(_Name, _Arity, _PredProcId, Instrs, _, _, _) },
-	output_instruction_list_decls(Instrs, DeclSet0, DeclSet).
+	output_instruction_list_decls(Instrs, StackLayoutLabels,
+		DeclSet0, DeclSet).
 
-:- pred output_c_procedure(c_procedure, bool, bool,
-	io__state, io__state).
-:- mode output_c_procedure(in, in, in, di, uo) is det.
+:- pred output_c_procedure(c_procedure::in, bool::in, bool::in,
+	io__state::di, io__state::uo) is det.
 
 output_c_procedure(Proc, PrintComments, EmitCLoops) -->
 	{ Proc = c_procedure(Name, Arity, proc(_, ProcId), Instrs, _, _, _) },
@@ -1375,34 +1322,36 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred output_instruction_list_decls(list(instruction), decl_set, decl_set,
-					io__state, io__state).
-:- mode output_instruction_list_decls(in, in, out, di, uo) is det.
+:- pred output_instruction_list_decls(list(instruction)::in,
+	map(label, data_addr)::in, decl_set::in, decl_set::out,
+	io__state::di, io__state::uo) is det.
 
-output_instruction_list_decls([], DeclSet, DeclSet) --> [].
-output_instruction_list_decls([Instr0 - _Comment0 | Instrs],
+output_instruction_list_decls([], _, DeclSet, DeclSet) --> [].
+output_instruction_list_decls([Instr0 - _Comment0 | Instrs], StackLayoutLabels,
 		DeclSet0, DeclSet) -->
-	output_instruction_decls(Instr0, DeclSet0, DeclSet1),
-	output_instruction_list_decls(Instrs, DeclSet1, DeclSet).
+	output_instruction_decls(Instr0, StackLayoutLabels,
+		DeclSet0, DeclSet1),
+	output_instruction_list_decls(Instrs, StackLayoutLabels,
+		DeclSet1, DeclSet).
 
-:- pred output_instruction_decls(instr, decl_set, decl_set,
-	io__state, io__state).
-:- mode output_instruction_decls(in, in, out, di, uo) is det.
+:- pred output_instruction_decls(instr::in, map(label, data_addr)::in,
+	decl_set::in, decl_set::out, io__state::di, io__state::uo) is det.
 
-output_instruction_decls(comment(_), DeclSet, DeclSet) --> [].
-output_instruction_decls(livevals(_), DeclSet, DeclSet) --> [].
-output_instruction_decls(block(_TempR, _TempF, Instrs),
+output_instruction_decls(comment(_), _, DeclSet, DeclSet) --> [].
+output_instruction_decls(livevals(_), _, DeclSet, DeclSet) --> [].
+output_instruction_decls(block(_TempR, _TempF, Instrs), StackLayoutLabels,
 		DeclSet0, DeclSet) -->
-	output_instruction_list_decls(Instrs, DeclSet0, DeclSet).
-output_instruction_decls(assign(Lval, Rval), DeclSet0, DeclSet) -->
+	output_instruction_list_decls(Instrs, StackLayoutLabels,
+		DeclSet0, DeclSet).
+output_instruction_decls(assign(Lval, Rval), _, DeclSet0, DeclSet) -->
 	output_lval_decls(Lval, "", "", 0, _, DeclSet0, DeclSet1),
 	output_rval_decls(Rval, "", "", 0, _, DeclSet1, DeclSet).
-output_instruction_decls(call(Target, ContLabel, _, _, _, _),
+output_instruction_decls(call(Target, ContLabel, _, _, _, _), _,
 		DeclSet0, DeclSet) -->
 	output_code_addr_decls(Target, "", "", 0, _, DeclSet0, DeclSet1),
 	output_code_addr_decls(ContLabel, "", "", 0, _, DeclSet1, DeclSet).
-output_instruction_decls(c_code(_), DeclSet, DeclSet) --> [].
-output_instruction_decls(mkframe(FrameInfo, FailureContinuation),
+output_instruction_decls(c_code(_), _, DeclSet, DeclSet) --> [].
+output_instruction_decls(mkframe(FrameInfo, FailureContinuation), _,
 		DeclSet0, DeclSet) -->
 	(
 		{ FrameInfo = ordinary_frame(_, _, yes(Struct)) },
@@ -1437,51 +1386,55 @@
 	),
 	output_code_addr_decls(FailureContinuation, "", "", 0, _,
 		DeclSet1, DeclSet).
-output_instruction_decls(label(_), DeclSet, DeclSet) --> [].
-output_instruction_decls(goto(CodeAddr), DeclSet0, DeclSet) -->
+output_instruction_decls(label(_), _, DeclSet, DeclSet) --> [].
+output_instruction_decls(goto(CodeAddr), _, DeclSet0, DeclSet) -->
 	output_code_addr_decls(CodeAddr, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(computed_goto(Rval, _Labels), DeclSet0, DeclSet) -->
+output_instruction_decls(computed_goto(Rval, _Labels), _,
+		DeclSet0, DeclSet) -->
 	output_rval_decls(Rval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(if_val(Rval, Target), DeclSet0, DeclSet) -->
+output_instruction_decls(if_val(Rval, Target), _, DeclSet0, DeclSet) -->
 	output_rval_decls(Rval, "", "", 0, _, DeclSet0, DeclSet1),
 	output_code_addr_decls(Target, "", "", 0, _, DeclSet1, DeclSet).
-output_instruction_decls(incr_hp(Lval, _Tag, Rval, _), DeclSet0, DeclSet) -->
+output_instruction_decls(incr_hp(Lval, _Tag, Rval, _), _,
+		DeclSet0, DeclSet) -->
 	output_lval_decls(Lval, "", "", 0, _, DeclSet0, DeclSet1),
 	output_rval_decls(Rval, "", "", 0, _, DeclSet1, DeclSet).
-output_instruction_decls(mark_hp(Lval), DeclSet0, DeclSet) -->
+output_instruction_decls(mark_hp(Lval), _, DeclSet0, DeclSet) -->
 	output_lval_decls(Lval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(restore_hp(Rval), DeclSet0, DeclSet) -->
+output_instruction_decls(restore_hp(Rval), _, DeclSet0, DeclSet) -->
 	output_rval_decls(Rval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(free_heap(Rval), DeclSet0, DeclSet) -->
+output_instruction_decls(free_heap(Rval), _, DeclSet0, DeclSet) -->
 	output_rval_decls(Rval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(store_ticket(Lval), DeclSet0, DeclSet) -->
+output_instruction_decls(store_ticket(Lval), _, DeclSet0, DeclSet) -->
 	output_lval_decls(Lval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(reset_ticket(Rval, _Reason), DeclSet0, DeclSet) -->
+output_instruction_decls(reset_ticket(Rval, _Reason), _, DeclSet0, DeclSet) -->
 	output_rval_decls(Rval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(discard_ticket, DeclSet, DeclSet) --> [].
-output_instruction_decls(prune_ticket, DeclSet, DeclSet) --> [].
-output_instruction_decls(mark_ticket_stack(Lval), DeclSet0, DeclSet) -->
+output_instruction_decls(discard_ticket, _, DeclSet, DeclSet) --> [].
+output_instruction_decls(prune_ticket, _, DeclSet, DeclSet) --> [].
+output_instruction_decls(mark_ticket_stack(Lval), _, DeclSet0, DeclSet) -->
 	output_lval_decls(Lval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(prune_tickets_to(Rval), DeclSet0, DeclSet) -->
+output_instruction_decls(prune_tickets_to(Rval), _, DeclSet0, DeclSet) -->
 	output_rval_decls(Rval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(incr_sp(_, _), DeclSet, DeclSet) --> [].
-output_instruction_decls(decr_sp(_), DeclSet, DeclSet) --> [].
+output_instruction_decls(incr_sp(_, _), _, DeclSet, DeclSet) --> [].
+output_instruction_decls(decr_sp(_), _, DeclSet, DeclSet) --> [].
 output_instruction_decls(pragma_c(_, Comps, _, _, MaybeLayoutLabel, _, _),
-		DeclSet0, DeclSet) -->
+		StackLayoutLabels, DeclSet0, DeclSet) -->
 	( { MaybeLayoutLabel = yes(Label) } ->
-		output_stack_layout_decl(Label, DeclSet0, DeclSet1)
+		{ map__lookup(StackLayoutLabels, Label, DataAddr) },
+		output_stack_layout_decl(DataAddr, DeclSet0, DeclSet1)
 	;
 		{ DeclSet1 = DeclSet0 }
 	),
 	output_pragma_c_component_list_decls(Comps, DeclSet1, DeclSet).
-output_instruction_decls(init_sync_term(Lval, _), DeclSet0, DeclSet) -->
+output_instruction_decls(init_sync_term(Lval, _), _, DeclSet0, DeclSet) -->
 	output_lval_decls(Lval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(fork(Child, Parent, _), DeclSet0, DeclSet) -->
+output_instruction_decls(fork(Child, Parent, _), _, DeclSet0, DeclSet) -->
 	output_code_addr_decls(label(Child), "", "", 0, _, DeclSet0, DeclSet2),
 	output_code_addr_decls(label(Parent), "", "", 0, _, DeclSet2, DeclSet).
-output_instruction_decls(join_and_terminate(Lval), DeclSet0, DeclSet) -->
+output_instruction_decls(join_and_terminate(Lval), _, DeclSet0, DeclSet) -->
 	output_lval_decls(Lval, "", "", 0, _, DeclSet0, DeclSet).
-output_instruction_decls(join_and_continue(Lval, Label), DeclSet0, DeclSet) -->
+output_instruction_decls(join_and_continue(Lval, Label), _, DeclSet0, DeclSet)
+		-->
 	output_lval_decls(Lval, "", "", 0, _, DeclSet0, DeclSet1),
 	output_code_addr_decls(label(Label), "", "", 0, _, DeclSet1, DeclSet).
 
@@ -2465,15 +2418,14 @@
 	data_name_would_include_code_address(DataName, CodeAddr).
 data_addr_would_include_code_address(rtti_addr(_, RttiName), CodeAddr) :-
 	rtti_name_would_include_code_addr(RttiName, CodeAddr).
+data_addr_would_include_code_address(layout_addr(LayoutName), CodeAddr) :-
+	layout_name_would_include_code_addr(LayoutName, CodeAddr).
 
 :- pred data_name_would_include_code_address(data_name, bool).
 :- mode data_name_would_include_code_address(in, out) is det.
 
 data_name_would_include_code_address(common(_),                 no).
 data_name_would_include_code_address(base_typeclass_info(_, _), yes).
-data_name_would_include_code_address(module_layout,             no).
-data_name_would_include_code_address(proc_layout(_),            yes).
-data_name_would_include_code_address(internal_layout(_),        no).
 data_name_would_include_code_address(tabling_pointer(_),        no).
 
 :- pred output_decl_id(decl_id, io__state, io__state).
@@ -2966,9 +2918,20 @@
 	;
 		{ DataAddr = rtti_addr(RttiTypeId, RttiVarName) },
 		output_rtti_addr_storage_type_name(RttiTypeId, RttiVarName, no)
+	;
+		{ DataAddr = layout_addr(LayoutName) },
+		output_layout_addr_storage_type_name(LayoutName, no)
 	),
 	io__write_string(";\n").
 
+output_data_addrs_decls([], _, _, N, N, DeclSet, DeclSet) --> [].
+output_data_addrs_decls([DataAddr | DataAddrs], FirstIndent, LaterIndent,
+		N0, N, DeclSet0, DeclSet) -->
+	output_data_addr_decls(DataAddr, FirstIndent, LaterIndent, N0, N1,
+		DeclSet0, DeclSet1),
+	output_data_addrs_decls(DataAddrs, FirstIndent, LaterIndent, N1, N,
+		DeclSet1, DeclSet).
+
 c_data_linkage_string(Globals, DefaultLinkage, BeingDefined, LinkageStr) :-
 	globals__lookup_bool_option(Globals, split_c_files, SplitFiles),
 	(
@@ -3042,9 +3005,6 @@
 
 data_name_linkage(common(_),                 static).
 data_name_linkage(base_typeclass_info(_, _), extern).
-data_name_linkage(module_layout,             static).
-data_name_linkage(proc_layout(_),            static).
-data_name_linkage(internal_layout(_),        static).
 data_name_linkage(tabling_pointer(_),        static).
 
 %-----------------------------------------------------------------------------%
@@ -3316,14 +3276,6 @@
 output_code_addr(do_not_reached) -->
 	io__write_string("MR_ENTRY(do_not_reached)").
 
-	% The code should be kept in sync with output_data_addr/2 below.
-llds_out__make_stack_layout_name(Label, Name) :-
-	llds_out__get_label(Label, yes, LabelName),
-	string__append_list([
-		"mercury_data__layout__",
-		LabelName
-	], Name).
-
 	% Output a maybe data address, with a `no' meaning NULL.
 
 :- pred output_maybe_data_addr(maybe(data_addr)::in,
@@ -3368,6 +3320,8 @@
 	output_data_addr(ModuleName, DataName).
 output_data_addr(rtti_addr(RttiTypeId, RttiName)) -->
 	output_rtti_addr(RttiTypeId, RttiName).
+output_data_addr(layout_addr(LayoutAddr)) -->
+	output_layout_addr(LayoutAddr).
 
 mercury_data_prefix = "mercury_data_".
 
@@ -3391,24 +3345,6 @@
 			% module
 		{ VarName = base_typeclass_info(ClassId, TypeNames) },
 		output_base_typeclass_info_name(ClassId, TypeNames)
-	;
-		{ VarName = module_layout },
-		io__write_string(mercury_data_prefix),
-		io__write_string("_module_layout_"),
-		{ llds_out__sym_name_mangle(ModuleName, MangledModuleName) },
-		io__write_string(MangledModuleName)
-	;
-		% Keep this code in sync with make_stack_layout_name/3.
-		{ VarName = proc_layout(Label) },
-		io__write_string(mercury_data_prefix),
-		io__write_string("_layout__"),
-		output_label(Label)
-	;
-		% Keep this code in sync with make_stack_layout_name/3.
-		{ VarName = internal_layout(Label) },
-		io__write_string(mercury_data_prefix),
-		io__write_string("_layout__"),
-		output_label(Label)
 	;
 		{ VarName = tabling_pointer(ProcLabel) },
 		io__write_string("mercury_var__tabling__"),
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.186
diff -u -b -r1.186 mercury_compile.m
--- compiler/mercury_compile.m	2000/12/13 12:12:53	1.186
+++ compiler/mercury_compile.m	2000/12/29 11:42:10
@@ -2291,6 +2291,7 @@
 	{ global_data_get_all_proc_vars(GlobalData, GlobalVars) },
 	{ global_data_get_all_non_common_static_data(GlobalData,
 		NonCommonStaticData) },
+	{ global_data_get_all_closure_layouts(GlobalData, ClosureLayouts) },
 	{ CommonableData0 = StaticLayouts },
 	( { CommonData = yes } ->
 		{ llds_common(Procs0, CommonableData0, ModuleName, Procs1,
@@ -2303,7 +2304,7 @@
 	%
 	% Next we put it all together and output it to one or more C files.
 	%
-	{ list__condense([CommonableData, NonCommonStaticData,
+	{ list__condense([CommonableData, NonCommonStaticData, ClosureLayouts,
 		TypeCtorTables, TypeClassInfos, PossiblyDynamicLayouts],
 		AllData) },
 	mercury_compile__construct_c_file(C_InterfaceInfo, Procs1, GlobalVars,
@@ -2426,7 +2427,7 @@
 	mercury_compile__combine_chunks_2(Chunks, ModuleName, Num1, Modules).
 
 :- pred mercury_compile__output_llds(module_name, c_file,
-	set_bbbtree(llds__label), maybe(rl_file), bool, bool,
+	map(llds__label, llds__data_addr), maybe(rl_file), bool, bool,
 	io__state, io__state).
 :- mode mercury_compile__output_llds(in, in, in, in, in, in, di, uo) is det.
 
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.110
diff -u -b -r1.110 opt_debug.m
--- compiler/opt_debug.m	2000/11/23 04:32:45	1.110
+++ compiler/opt_debug.m	2001/01/02 07:41:24
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% Copyright (C) 1994-2000 The University of Melbourne.
+% Copyright (C) 1994-2001 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.
 %-----------------------------------------------------------------------------%
@@ -15,7 +15,7 @@
 :- interface.
 
 :- import_module llds, vn_type, vn_table, livemap.
-:- import_module code_model, rtti, builtin_ops.
+:- import_module code_model, rtti, layout, builtin_ops.
 :- import_module atsort.
 
 :- import_module io, bool, list, assoc_list, std_util.
@@ -149,6 +149,9 @@
 :- pred opt_debug__dump_rtti_name(rtti_name, string).
 :- mode opt_debug__dump_rtti_name(in, out) is det.
 
+:- pred opt_debug__dump_layout_name(layout_name, string).
+:- mode opt_debug__dump_layout_name(in, out) is det.
+
 :- pred opt_debug__dump_unop(unary_op, string).
 :- mode opt_debug__dump_unop(in, out) is det.
 
@@ -737,19 +740,15 @@
 	opt_debug__dump_rtti_name(DataName, DataName_str),
 	string__append_list(
 		["rtti_addr(", RttiTypeId_str, ", ", DataName_str, ")"], Str).
+opt_debug__dump_data_addr(layout_addr(LayoutName), Str) :-
+	opt_debug__dump_layout_name(LayoutName, LayoutName_str),
+	string__append_list(["layout_addr(", LayoutName_str, ")"], Str).
 
 opt_debug__dump_data_name(common(N), Str) :-
 	string__int_to_string(N, N_str),
 	string__append("common", N_str, Str).
 opt_debug__dump_data_name(base_typeclass_info(ClassId, InstanceNum), Str) :-
 	llds_out__make_base_typeclass_info_name(ClassId, InstanceNum, Str).
-opt_debug__dump_data_name(module_layout, "module_layout").
-opt_debug__dump_data_name(proc_layout(Label), Str) :-
-	opt_debug__dump_label(Label, LabelStr),
-	string__append_list(["proc_layout(", LabelStr, ")"], Str).
-opt_debug__dump_data_name(internal_layout(Label), Str) :-
-	opt_debug__dump_label(Label, LabelStr),
-	string__append_list(["internal_layout(", LabelStr, ")"], Str).
 opt_debug__dump_data_name(tabling_pointer(ProcLabel), Str) :-
 	opt_debug__dump_proclabel(ProcLabel, ProcLabelStr),
 	string__append_list(["tabling_pointer(", ProcLabelStr, ")"], Str).
@@ -802,6 +801,58 @@
 	Str = "pseudo_type_info".
 opt_debug__dump_rtti_name(type_hashcons_pointer, Str) :-
 	Str = "type_hashcons_pointer".
+
+opt_debug__dump_layout_name(label_layout(Label, LabelVars), Str) :-
+	opt_debug__dump_label(Label, LabelStr),
+	(
+		LabelVars = label_has_var_info,
+		LabelVarsStr = "label_has_var_info"
+	;
+		LabelVars = label_has_no_var_info,
+		LabelVarsStr = "label_has_no_var_info"
+	),
+	string__append_list(["label_layout(", LabelStr, ", ",
+		LabelVarsStr, ")"], Str).
+opt_debug__dump_layout_name(proc_layout(ProcLabel, _), Str) :-
+	opt_debug__dump_proclabel(ProcLabel, ProcLabelStr),
+	string__append_list(["proc_layout(", ProcLabelStr, ")"], Str).
+opt_debug__dump_layout_name(proc_layout_var_names(ProcLabel), Str) :-
+	opt_debug__dump_proclabel(ProcLabel, ProcLabelStr),
+	string__append_list(["proc_layout_var_names(", ProcLabelStr, ")"],
+		Str).
+opt_debug__dump_layout_name(closure_proc_id(ProcLabel, SeqNo, _), Str) :-
+	opt_debug__dump_proclabel(ProcLabel, ProcLabelStr),
+	string__int_to_string(SeqNo, SeqNoStr),
+	string__append_list(["closure_proc_id(", ProcLabelStr, ", ",
+		SeqNoStr, ")"], Str).
+opt_debug__dump_layout_name(file_layout(ModuleName, FileNum), Str) :-
+	llds_out__sym_name_mangle(ModuleName, ModuleNameStr),
+	string__int_to_string(FileNum, FileNumStr),
+	string__append_list(["file_layout(", ModuleNameStr, ", ",
+		FileNumStr, ")"], Str).
+opt_debug__dump_layout_name(file_layout_line_number_vector(ModuleName,
+		FileNum), Str) :-
+	llds_out__sym_name_mangle(ModuleName, ModuleNameStr),
+	string__int_to_string(FileNum, FileNumStr),
+	string__append_list(["file_layout_line_number_vector(", ModuleNameStr,
+		", ", FileNumStr, ")"], Str).
+opt_debug__dump_layout_name(file_layout_label_layout_vector(ModuleName,
+		FileNum), Str) :-
+	llds_out__sym_name_mangle(ModuleName, ModuleNameStr),
+	string__int_to_string(FileNum, FileNumStr),
+	string__append_list(["file_layout_label_layout_vector(", ModuleNameStr,
+		", ", FileNumStr, ")"], Str).
+opt_debug__dump_layout_name(module_layout_file_vector(ModuleName), Str) :-
+	llds_out__sym_name_mangle(ModuleName, ModuleNameStr),
+	string__append_list(["module_layout_file_vector(", ModuleNameStr, ")"],
+		Str).
+opt_debug__dump_layout_name(module_layout_proc_vector(ModuleName), Str) :-
+	llds_out__sym_name_mangle(ModuleName, ModuleNameStr),
+	string__append_list(["module_layout_proc_vector(", ModuleNameStr, ")"],
+		Str).
+opt_debug__dump_layout_name(module_layout(ModuleName), Str) :-
+	llds_out__sym_name_mangle(ModuleName, ModuleNameStr),
+	string__append_list(["module_layout(", ModuleNameStr, ")"], Str).
 
 opt_debug__dump_unop(mktag, "mktag").
 opt_debug__dump_unop(tag, "tag").
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.58
diff -u -b -r1.58 stack_layout.m
--- compiler/stack_layout.m	2000/12/06 06:05:16	1.58
+++ compiler/stack_layout.m	2001/01/07 09:50:07
@@ -1,292 +1,23 @@
 %---------------------------------------------------------------------------%
-% Copyright (C) 1997-2000 University of Melbourne.
+% Copyright (C) 1997-2001 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.
 %---------------------------------------------------------------------------%
 %
-% This module generates the LLDS code that defines global constants to
-% hold the `stack_layout' structures of the stack frames defined by the
-% current module.
-%
-% The tables generated have a number of `create' rvals within them.
-% llds_common.m converts these into static data structures.
-%
-% We can create several types of stack layouts. Which kind we generate
-% depends on the values of several options.
-%
+% File: stacK_layout.m.
 % Main authors: trd, zs.
-%
-% NOTE: If you make changes in this file, you may also need to modify
-% runtime/mercury_stack_layout.h.
-%
-%---------------------------------------------------------------------------%
-%
-% Data Structure: procedure layouts
-%
-% If the option basic_stack_layout is set, we generate a MR_Stack_Layout_Entry
-% for each procedure. This will be stored in the global variable whose name is
-%	mercury_data__layout__mercury__<proc_label>.
-%
-% This structure contains up to three groups of fields. The first group,
-% which contains information that enables the stack to be traversed, is always
-% present. The second group, which identifies the procedure in terms that are
-% meaningful to both humans and machines, will be generated only if the option
-% procid_stack_layout is set, i.e. if we are doing stack tracing, execution
-% tracing or profiling. The third group, which contains information
-% specifically intended for the debugger, will be generated only if the option
-% trace_stack_layout is set.
-%
-% The distinguished value -1 in the first field of the second group
-% indicates that the later fields are not present.
-%
-% The distinguished value NULL in the first field of the third group
-% indicates that the later fields are not present.
-%
-%---------------------------------------------------------------------------%
-%
-% The first group contains the following fields:
-%
-%	MR_Code			*MR_sle_code_addr;
-%	MR_Long_Lval		MR_sle_succip_locn;
-%	MR_int_least16_t	MR_sle_stack_slots;
-%	MR_Determinism		MR_sle_detism;
-%
-% The code_addr field points to the start of the procedure's code.
-%
-% The succip_locn field encoded the location of the saved succip if it is saved
-% in a general purpose stack slot. If the succip is saved in a specal purpose
-% stack slot (as it is for model_non procedures) or if the procedure never
-% saves the succip (as in leaf procedures), this field will contain -1.
-%
-% The stack_slots field gives the number of general purpose stack slots
-% in the procedure.
-%
-% The detism field encodes the determinism of the procedure.
-%
-%---------------------------------------------------------------------------%
-%
-% The second group contains one field:
-%
-%	MR_Stack_Layout_Proc_Id	MR_sle_proc_id;
-%
-% This field is a union. The usual alternative of which identifies ordinary
-% procedures, while the other alternative identifies automatically generated 
-% unification, comparison and index functions. The meanings of the fields
-% in both forms are the same as in procedure labels. The runtime system can
-% figure out which form is present by testing the value of the first slot,
-% as the acceptable ranges of values of the first fields (which are the same
-% size) are disjoint.
-%
-%---------------------------------------------------------------------------%
-%
-% The third group contains the following fields:
-%
-%	struct MR_Stack_Layout_Label_Struct	*MR_sle_call_label;
-%	struct MR_Module_Layout_Struct		*MR_sle_module_layout;
-%	MR_Word					MR_sle_proc_rep;
-%	MR_int_least16_t			*MR_sle_used_var_names;
-%	MR_int_least16_t			MR_sle_max_var_num;
-%	MR_int_least16_t			MR_sle_max_r_num;
-%	MR_int_least8_t				MR_sle_maybe_from_full;
-%	MR_int_least8_t				MR_sle_maybe_io_seq;
-%	MR_int_least8_t				MR_sle_maybe_trail;
-%	MR_int_least8_t				MR_sle_maybe_maxfr;
-%	MR_EvalMethod				MR_sle_eval_method:8;
-%	MR_int_least8_t				MR_sle_maybe_call_table;
-%	MR_int_least8_t				MR_sle_maybe_decl_debug;
-%
-% The call_label field points to the label layout structure for the label
-% associated with the call event at the entry to the procedure. The purpose
-% of this field is to allow the runtime debugger to find out which variables
-% are where on entry, so it can reexecute the procedure if asked to do so
-% and if the values of the required variables are still available.
-%
-% The module_layout field points to the module info structure of the module
-% containing the procedure. This allows the debugger access to the string table
-% stored there, as well the table associating source-file contexts with labels.
-%
-% The proc_rep field contains a representation of the body of the procedure
-% as a Mercury term of type goal_rep, defined in program_representation.m.
-% If will be 0 if no such representation is available.
-%
-% The used_var_names field points to an array that contains offsets
-% into the string table, with the offset at index i-1 giving the name of
-% variable i (since variable numbers start at one). If a variable has no name
-% or cannot be referred to from an event, the offset will be zero, at which
-% offset the string table will contain an empty string. The string table
-% is restricted to be small enough to be addressed with 16 bits;
-% a string is reserved near the start for a string that says "too many
-% variables". Stack_layout.m will generate a reference to this string
-% instead of generating an offset that does not fit into 16 bits.
-% Therefore using the stored offset to index into the string table
-% is always safe.
-%
-% The max_var_num field gives the number of elements in the used_var_names
-% table.
-%
-% The max_r_num field tells the debugger which Mercury abstract machine
-% registers need saving in MR_trace: besides the special registers, it is
-% the general-purpose registers rN for values of N up to and including the
-% value of this field. Note that this field contains an upper bound; in
-% general, there will be calls to MR_trace at which the number of the highest
-% numbered general purpose (i.e. rN) registers is less than this. However,
-% storing the upper bound gets us almost all the benefit (of not saving and
-% restoring all the thousand rN registers) for a small fraction of the static
-% space cost of storing the actual number in label layout structures.
-%
-% If the procedure is compiled with deep tracing, the maybe_from_full field
-% will contain a negative number. If it is compiled with shallow tracing,
-% it will contain the number of the stack slot that holds the flag that says
-% whether this incarnation of the procedure was called from deeply traced code
-% or not. (The determinism of the procedure decides whether the stack slot
-% refers to a stackvar or a framevar.)
-%
-% If the procedure has an I/O state argument, the maybe_io_seq field will
-% contain the number of the stack slot that holds the value the I/O action
-% counter had on entry to this procedure.
-%
-% If trailing is not enabled, the maybe_trail field will contain a negative
-% number. If it is enabled, it will contain number of the first of two stack
-% slots used for checkpointing the state of the trail on entry to the
-% procedure. The first contains the trail pointer, the second the ticket.
-%
-% If the procedure lives on the nondet stack, or if it cannot create any
-% temporary nondet stack frames, the maybe_maxfr field will contain a negative
-% number. If it lives on the det stack, and can create temporary nondet stack
-% frames, it will contain the number number of the stack slot that contains the
-% value of maxfr on entry, for use in executing the retry debugger command
-% from the middle of the procedure.
-%
-% The eval_method field contains a representation of the evaluation method
-% used by the procedure. The retry command needs this information if it is
-% to reset the call tables of the procedure invocations being retried.
-%
-% If --trace-decl is not set, the maybe_decl field will contain a negative
-% number. If it is set, it will contain the number of the first of two stack
-% slots used by the declarative debugger; the other slot is the next higher
-% numbered one. (The determinism of the procedure decides whether the stack
-% slot refers to a stackvar or a framevar.)
-%
-%---------------------------------------------------------------------------%
-%
-% Data Structure: label layouts
-%
-% If the option basic_stack_layout is set, we generate stack layout tables
-% for some labels internal to the procedure. This table will be stored in the
-% global variable whose name is
-%	mercury_data__layout__mercury__<proc_label>_i<label_number>.
-% This table has the following format:
-%
-%	proc layout		(Word *) - pointer to the layout structure of
-%				the procedure containing this label
-% 	trace port		(int_least16) - a representation of the trace
-%				port associated with the label, or -1
-% 	goal path		(int_least16) - an index into the module's
-%				string table giving the goal path associated
-%				with the trace port of the label, or -1
-% 	# of live data items	(Integer) - an encoded representation of
-%				the number of live data items at the label
-% 	live data types locns 	(void *) - pointer to an area of memory
-%				containing information about where the live
-%				data items are and what their types are
-% 	live data var nums	(int_least16 *) - pointer to vector of ints
-%				giving the HLDS var numbers (if any) of live
-%				data items
-%	type parameters		(MR_Long_Lval *) - pointer to vector of
-%			 	MR_Long_Lval giving the locations of the
-%				typeinfos for the type parameters that may
-%				be referred to by the types of the live data
-%				items; the first word of the vector is an
-%				integer giving the number of entries in the
-%				vector; a NULL pointer means no type parameters
-%
-% The layout of the memory area containing information about the locations
-% and types of live data items is somewhat complicated, due to our desire
-% to make this information compact. We can represent a location in one of
-% two ways, as an 8-bit MR_Short_Lval or as a 32-bit MR_Long_Lval.
-% We prefer representing a location as an MR_Short_Lval, but of course
-% not all locations can be represented in this way, so those other locations
-% are represented as MR_Long_Lvals.
-%
-% The field containing the number of live data items is encoded by the
-% formula (#Long << short_count_bits + #Short), where #Short is the number
-% data items whose descriptions fit into an MR_Short_Lval and #Long is the
-% number of data items whose descriptions do not. (The field is not an integer
-% so that people who attempt to use it without going through the decoding
-% macros in runtime/mercury_stack_layout.h get an error from the C compiler.
-% The number of distinct values that fit into a uint_least_t also fits into
-% 8 bits, but since some locations hold the value of more than one variable
-% at a time, not all the values need to be distinct; this is why
-% short_count_bits is more than 8.)
-%
-% The memory area contains three vectors back to back. The first vector
-% has #Long + #Short word-sized elements, each of which is a pointer to a
-% MR_PseudoTypeInfo giving the type of a live data item, with a small
-% integer instead of a pointer representing a special kind of live data item
-% (e.g. a saved succip or hp). The second vector is an array of #Long
-% MR_Long_Lvals, and the third is an array of #Short MR_Short_Lvals,
-% each of which describes a location. The pseudotypeinfo pointed to by
-% the slot at subscript i in the first vector describes the type of
-% the data stored in slot i in the second vector if i < #Long, and
-% the type of the data stored in slot i - #Long in the third vector
-% otherwise.
-%
-% The live data pair vector will have an entry for each live variable.
-% The entry will give the location of the variable and its type.
-%
-% The live data var nums vector pointer may be NULL. If it is not, the vector
-% will have an entry consisting of a 16-bit number for each live data item.
-% This is either the live data item's HLDS variable number, or one of two
-% special values. Zero means that the live data item is not a variable
-% (e.g. it is a saved copy of succip). The largest possible 16-bit number
-% on the other hand means "the number of this variable does not fit into
-% 16 bits". With the exception of these special values, the value in this
-% slot uniquely identifies the variable.
-%
-% If the number of type parameters is not zero, we store the number,
-% so that the code that needs the type parameters can materialize
-% all the type parameters from their location descriptions in one go.
-% This is an optimization, since the type parameter vector could simply
-% be indexed on demand by the type variable's variable number stored within
-% pseudo-typeinfos inside the elements of the live data pairs vectors.
-%
-% Since we allocate type variable numbers sequentially, the type parameter
-% vector will usually be dense. However, after all variables whose types
-% include e.g. type variable 2 have gone out of scope, variables whose
-% types include type variable 3 may still be around. In cases like this,
-% the entry for type variable 2 will be zero; this signals to the code
-% in the internal debugger that materializes typeinfo structures that
-% this typeinfo structure need not be materialized.
 %
-% We need detailed information about the variables that are live at an
-% internal label in two kinds of circumstances. Stack layout information
-% will be present only for labels that fall into one or both of these
-% circumstances.
+% This module generates label, procedure, module and closure layout structures
+% for code in the current module for the LLDS backend.
 %
-% -	The option trace_stack_layout is set, and the label represents
-%	a traced event at which variable info is needed (call, exit,
-%	or entrance to one branch of a branched control structure;
-%	fail events have no variable information).
+% 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.
 %
-% -	The option agc_stack_layout is set or the trace level specifies
-%	a capability for uplevel printing, and the label represents
-% 	a point where execution can resume after a procedure call or
-%	after backtracking.
-%
-% For labels that do not fall into one of these two categories, the
-% "# of live vars" field will be negative to indicate the absence of
-% information about the variables live at this label, and the last
-% four fields will not be present.
-%
-% For labels that do fall into one of these two categories, the
-% "# of live vars" field will hold the number of live variables, which
-% will not be negative. If it is zero, the last four fields will not be
-% present. Even if it is not zero, however, the pointer to the live data
-% names vector will be NULL unless the label is used in execution tracing.
-%
-% XXX: Presently, inst information is ignored. We also do not yet enable
-% procid stack layouts for profiling, since profiling does not yet use
-% stack layouts.
+% The C types of the structures we generate are defined and documented in
+% runtime/mercury_stack_layout.h. 
 %
 %---------------------------------------------------------------------------%
 
@@ -294,25 +25,26 @@
 
 :- interface.
 
-:- import_module continuation_info, hlds_module, llds.
-:- import_module std_util, list, set_bbbtree, counter.
+:- import_module prog_data, continuation_info, hlds_module, llds.
+:- import_module std_util, list, map, counter.
 
 :- pred stack_layout__generate_llds(module_info::in, module_info::out,
-	global_data::in,
-	list(comp_gen_c_data)::out, list(comp_gen_c_data)::out,
-	set_bbbtree(label)::out) is det.
-
-:- pred stack_layout__construct_closure_layout(proc_label::in,
-	closure_layout_info::in, list(maybe(rval))::out,
-	create_arg_types::out, counter::in, counter::out) is det.
+	global_data::in, list(comp_gen_c_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,
+	counter::in, counter::out) is det.
 
 :- implementation.
 
 :- import_module globals, options, llds_out, trace_params, trace.
 :- import_module hlds_data, hlds_goal, hlds_pred.
-:- import_module prog_data, prog_util, prog_out, instmap.
+:- import_module prog_util, prog_out, instmap.
 :- import_module prog_rep, static_term.
-:- import_module rtti, ll_pseudo_type_info, (inst), code_util.
+:- import_module rtti, layout, ll_pseudo_type_info, (inst), code_util.
 :- import_module assoc_list, bool, string, int, require.
 :- import_module map, term, set, varset.
 
@@ -335,7 +67,7 @@
 	globals__get_trace_level(Globals, TraceLevel),
 	globals__get_trace_suppress(Globals, TraceSuppress),
 	globals__have_static_code_addresses(Globals, StaticCodeAddr),
-	set_bbbtree__init(LayoutLabels0),
+	map__init(LayoutLabels0),
 
 	map__init(StringMap0),
 	map__init(LabelTables0),
@@ -349,59 +81,40 @@
 	stack_layout__lookup_string_in_table("<too many variables>", _,
 		LayoutInfo1, LayoutInfo2),
 	list__foldl(stack_layout__construct_layouts, ProcLayoutList,
-		LayoutInfo2, LayoutInfo3),
-		% This version of the layout info structure is final in all
-		% respects except the cell count.
-	ProcLayouts = LayoutInfo3 ^ proc_layouts,
-	InternalLayouts = LayoutInfo3 ^ internal_layouts,
-	LayoutLabels = LayoutInfo3 ^ label_set,
-	ProcLayoutArgs = LayoutInfo3 ^ proc_layout_args,
-	StringTable = LayoutInfo3 ^ string_table,
-	LabelTables = LayoutInfo3 ^ label_tables,
+		LayoutInfo2, LayoutInfo),
+	ModuleInfo = LayoutInfo ^ module_info,
+	ProcLayouts = LayoutInfo ^ proc_layouts,
+	InternalLayouts = LayoutInfo ^ internal_layouts,
+	LayoutLabels = LayoutInfo ^ label_set,
+	ProcLayoutNames = LayoutInfo ^ proc_layout_name_list,
+	StringTable = LayoutInfo ^ string_table,
+	LabelTables = LayoutInfo ^ label_tables,
 	StringTable = string_table(_, RevStringList, StringOffset),
 	list__reverse(RevStringList, StringList),
 	stack_layout__concat_string_list(StringList, StringOffset,
 		ConcatStrings),
 
+	PossiblyDynamicLayouts = ProcLayouts,
 	( TraceLayout = yes ->
-		Exported = no,	% ignored; see linkage/2 in llds_out.m
-		list__length(ProcLayoutList, NumProcLayouts),
 		module_info_name(ModuleInfo0, ModuleName),
-		llds_out__sym_name_mangle(ModuleName, ModuleNameStr),
-		stack_layout__get_next_cell_number(ProcVectorCellNum,
-			LayoutInfo3, LayoutInfo4),
-		Reuse = no,
-		ProcLayoutVector = create(0, ProcLayoutArgs,
-			uniform(yes(data_ptr)), must_be_static, 
-			ProcVectorCellNum, "proc_layout_vector", Reuse),
 		globals__lookup_bool_option(Globals, rtti_line_numbers,
 			LineNumbers),
-		( LineNumbers = yes ->
+		(
+			LineNumbers = yes,
 			EffLabelTables = LabelTables
 		;
+			LineNumbers = no,
 			map__init(EffLabelTables)
 		),
 		stack_layout__format_label_tables(EffLabelTables,
-			NumSourceFiles, SourceFileVectors,
-			LayoutInfo4, LayoutInfo),
-		Rvals = [yes(const(string_const(ModuleNameStr))),
-			yes(const(int_const(StringOffset))),
-			yes(const(multi_string_const(StringOffset,
-				ConcatStrings))),
-			yes(const(int_const(NumProcLayouts))),
-			yes(ProcLayoutVector),
-			yes(const(int_const(NumSourceFiles))),
-			yes(SourceFileVectors),
-			yes(const(int_const(trace_level_rep(TraceLevel))))],
-		ModuleLayouts = comp_gen_c_data(ModuleName, module_layout,
-			Exported, Rvals, uniform(no), []),
-		StaticLayouts = [ModuleLayouts | InternalLayouts]
+			SourceFileLayouts),
+		ModuleLayout = layout_data(module_layout_data(ModuleName,
+			StringOffset, ConcatStrings, ProcLayoutNames,
+			SourceFileLayouts, TraceLevel)),
+		StaticLayouts = [ModuleLayout | InternalLayouts]
 	;
-		StaticLayouts = InternalLayouts,
-		LayoutInfo = LayoutInfo3
-	),
-	PossiblyDynamicLayouts = ProcLayouts,
-	stack_layout__get_module_info(ModuleInfo, LayoutInfo, _).
+		StaticLayouts = InternalLayouts
+	).
 
 :- pred stack_layout__valid_proc_layout(proc_layout_info::in) is semidet.
 
@@ -415,6 +128,12 @@
 		ProcLabel = special_proc(_, _, _, _, _, _)
 	).
 
+:- pred stack_layout__data_addr_to_maybe_rval(data_addr::in, maybe(rval)::out)
+	is det.
+
+stack_layout__data_addr_to_maybe_rval(DataAddr, yes(Rval)) :-
+	Rval = const(data_addr_const(DataAddr)).
+
 %---------------------------------------------------------------------------%
 
 :- pred stack_layout__concat_string_list(list(string)::in, int::in,
@@ -454,119 +173,28 @@
 %---------------------------------------------------------------------------%
 
 :- pred stack_layout__format_label_tables(map(string, label_table)::in,
-	int::out, rval::out, stack_layout_info::in, stack_layout_info::out)
-	is det.
+	list(file_layout_data)::out) is det.
 
-stack_layout__format_label_tables(LabelTableMap, NumSourceFiles,
-		SourceFilesVector, LayoutInfo0, LayoutInfo) :-
+stack_layout__format_label_tables(LabelTableMap, SourceFileLayouts) :-
 	map__to_assoc_list(LabelTableMap, LabelTableList),
-	list__length(LabelTableList, NumSourceFiles),
-	list__map_foldl(stack_layout__format_label_table, LabelTableList,
-		SourceFileRvals, LayoutInfo0, LayoutInfo1),
-	stack_layout__get_next_cell_number(SourceFileVectorCellNum,
-		LayoutInfo1, LayoutInfo),
-	Reuse = no,
-	SourceFilesVector = create(0, SourceFileRvals,
-		uniform(yes(data_ptr)), must_be_static, 
-		SourceFileVectorCellNum, "source_files_vector", Reuse).
+	list__map(stack_layout__format_label_table, LabelTableList,
+		SourceFileLayouts).
 
 :- pred stack_layout__format_label_table(pair(string, label_table)::in,
-	maybe(rval)::out, stack_layout_info::in, stack_layout_info::out) is det.
+	file_layout_data::out) is det.
 
-stack_layout__format_label_table(FileName - LineNoMap, yes(SourceFileVector),
-		LayoutInfo0, LayoutInfo) :-
+stack_layout__format_label_table(FileName - LineNoMap,
+		file_layout_data(FileName, FilteredList)) :-
 		% This step should produce a list ordered on line numbers.
 	map__to_assoc_list(LineNoMap, LineNoList),
 		% And this step should preserve that order.
 	stack_layout__flatten_label_table(LineNoList, [], FlatLineNoList),
-	list__length(FlatLineNoList, VectorLength),
-	stack_layout__get_module_name(CurrentModule, LayoutInfo0, LayoutInfo1),
-
-	ProjectLineNos = (pred(LabelInfo::in, LineNoRval::out) is det :-
-		LabelInfo = LineNo - (_Label - _IsReturn),
-		LineNoRval = yes(const(int_const(LineNo)))
-	),
-	ProjectLabels = (pred(LabelInfo::in, LabelRval::out) is det :-
-		LabelInfo = _LineNo - (Label - _IsReturn),
-		DataAddr = data_addr(CurrentModule, internal_layout(Label)),
-		LabelRval = yes(const(data_addr_const(DataAddr)))
+	Filter = (pred(LineNoInfo::in, FilteredLineNoInfo::out) is det :-
+		LineNoInfo = LineNo - (Label - _IsReturn),
+		FilteredLineNoInfo = LineNo - Label
 	),
-% See the comment below.
-%	ProjectCallees = lambda([LabelInfo::in, CalleeRval::out] is det, (
-%		LabelInfo = _LineNo - (_Label - IsReturn),
-%		(
-%			IsReturn = not_a_return,
-%			CalleeRval = yes(const(int_const(0)))
-%		;
-%			IsReturn = unknown_callee,
-%			CalleeRval = yes(const(int_const(1)))
-%		;
-%			IsReturn = known_callee(Label),
-%			code_util__extract_proc_label_from_label(Label,
-%				ProcLabel),
-%			(
-%				ProcLabel = proc(ModuleName, _, _, _, _, _)
-%			;
-%				ProcLabel = special_proc(ModuleName, _, _,
-%					_, _, _)
-%			),
-%			DataAddr = data_addr(ModuleName, proc_layout(Label)),
-%			CalleeRval = yes(const(data_addr_const(DataAddr)))
-%		)
-%	)),
+	list__map(Filter, FlatLineNoList, FilteredList).
 
-	list__map(ProjectLineNos, FlatLineNoList, LineNoRvals),
-	stack_layout__get_next_cell_number(LineNoVectorCellNum,
-		LayoutInfo1, LayoutInfo2),
-	Reuse = no,
-	LineNoVector = create(0, LineNoRvals,
-		uniform(yes(int_least16)), must_be_static, 
-		LineNoVectorCellNum, "line_number_vector", Reuse),
-
-	list__map(ProjectLabels, FlatLineNoList, LabelRvals),
-	stack_layout__get_next_cell_number(LabelsVectorCellNum,
-		LayoutInfo2, LayoutInfo3),
-	LabelsVector = create(0, LabelRvals,
-		uniform(yes(data_ptr)), must_be_static, 
-		LabelsVectorCellNum, "label_vector", Reuse),
-
-% We do not include the callees vector in the table because it makes references
-% to the proc layouts of procedures from other modules without knowing whether
-% those modules were compiled with debugging. This works only if all procedures
-% always have a proc layout structure, which we don't want to require yet.
-%
-% Callees vectors would allow us to use faster code to check at every event
-% whether a breakpoint applies to that event, in the usual case that no context
-% breakpoint is on a line contains a higher order call. Instead of always
-% searching a separate data structure, as we now do, to check for the
-% applicability of context breakpoints, the code could search this data
-% structure only if the proc layout matched the proc layout of the caller
-% Since we already search a table of proc layouts in order to check for plain,
-% non-context breakpoints on procedures, this would incur no extra cost
-% in most cases.
-%
-%	list__map(ProjectCallees, FlatLineNoList, CalleeRvals),
-%	stack_layout__get_next_cell_number(CalleesVectorCellNum,
-%		LayoutInfo3, LayoutInfo4),
-%	CalleesVector = create(0, CalleeRvals,
-%		uniform(no), must_be_static, 
-%		CalleesVectorCellNum, "callee_vector", Reuse),
-
-	SourceFileRvals = [
-		yes(const(string_const(FileName))),
-		yes(const(int_const(VectorLength))),
-		yes(LineNoVector),
-		yes(LabelsVector)
-%		yes(CalleesVector)
-	],
-	stack_layout__get_next_cell_number(SourceFileVectorCellNum,
-		LayoutInfo3, LayoutInfo),
-	SourceFileVector = create(0, SourceFileRvals,
-		initial([1 - yes(string), 1 - yes(integer),
-			2 - yes(data_ptr)], none),
-		must_be_static, 
-		SourceFileVectorCellNum, "source_file_vector", Reuse).
-
 :- pred stack_layout__flatten_label_table(
 	assoc_list(int, list(line_no_info))::in,
 	assoc_list(int, line_no_info)::in,
@@ -604,26 +232,53 @@
 		VarSet, VarTypes, InternalMap) },
 	{ map__to_assoc_list(InternalMap, Internals) },
 	stack_layout__set_cur_proc_named_vars(map__init),
-	list__foldl(stack_layout__construct_internal_layout(EntryLabel),
-		Internals),
+
+	{ code_util__extract_proc_label_from_label(EntryLabel, ProcLabel) },
+	stack_layout__get_procid_stack_layout(ProcIdLayout0),
+	{ bool__or(ProcIdLayout0, ForceProcIdLayout, ProcIdLayout) },
+	( { ProcIdLayout = yes } ->
+		{
+			ProcLabel = proc(_, _, _, _, _, _),
+			UserOrCompiler = user
+		;
+			ProcLabel = special_proc(_, _, _, _, _, _),
+			UserOrCompiler = compiler
+		},
+		stack_layout__get_trace_stack_layout(TraceLayout),
+		{
+			TraceLayout = yes,
+			Kind = proc_layout_exec_trace(UserOrCompiler)
+		;
+			TraceLayout = no,
+			Kind = proc_layout_proc_id(UserOrCompiler)
+		}
+	;
+		{ Kind = proc_layout_traversal }
+	),
+
+	{ ProcLayoutName = proc_layout(ProcLabel, Kind) },
+
+	list__foldl2(stack_layout__construct_internal_layout(ProcLayoutName),
+		Internals, [], InternalLayouts),
 	stack_layout__get_cur_proc_named_vars(NamedVars),
 	stack_layout__get_label_tables(LabelTables0),
-	{ list__foldl(stack_layout__update_label_table, Internals,
+	{ list__foldl(stack_layout__update_label_table, InternalLayouts,
 		LabelTables0, LabelTables) },
 	stack_layout__set_label_tables(LabelTables),
-	stack_layout__construct_proc_layout(EntryLabel, Detism, StackSlots,
-		SuccipLoc, EvalMethod, MaybeCallLabel, MaxTraceReg,
-		Goal, InstMap, TraceSlotInfo, ForceProcIdLayout,
-		VarSet, VarTypes, NamedVars).
+	stack_layout__construct_proc_layout(EntryLabel, ProcLabel, Detism,
+		StackSlots, SuccipLoc, EvalMethod, MaybeCallLabel, MaxTraceReg,
+		Goal, InstMap, TraceSlotInfo, VarSet, VarTypes, NamedVars,
+		Kind).
 
 %---------------------------------------------------------------------------%
 
-	% Add the given label to the module-wide label tables.
+	% Add the given label layout to the module-wide label tables.
 
-:- pred stack_layout__update_label_table(pair(label, internal_layout_info)::in,
+:- pred stack_layout__update_label_table(
+	pair(pair(label, label_vars), internal_layout_info)::in,
 	map(string, label_table)::in, map(string, label_table)::out) is det.
 
-stack_layout__update_label_table(Label - InternalInfo,
+stack_layout__update_label_table((Label - LabelVars) - InternalInfo,
 		LabelTables0, LabelTables) :-
 	InternalInfo = internal_layout_info(Port, _, Return),
 	(
@@ -636,35 +291,36 @@
 		;
 			IsReturn = unknown_callee
 		),
-		stack_layout__update_label_table_2(Label, Context, IsReturn,
-			LabelTables0, LabelTables)
+		stack_layout__update_label_table_2(Label, LabelVars,
+			Context, IsReturn, LabelTables0, LabelTables)
 	;
 		Port = yes(trace_port_layout_info(Context, _, _, _)),
 		stack_layout__context_is_valid(Context)
 	->
-		stack_layout__update_label_table_2(Label, Context,
-			not_a_return, LabelTables0, LabelTables)
+		stack_layout__update_label_table_2(Label, LabelVars,
+			Context, not_a_return, LabelTables0, LabelTables)
 	;
 		LabelTables = LabelTables0
 	).
 
-:- pred stack_layout__update_label_table_2(label::in, context::in,
-	is_label_return::in,
+:- pred stack_layout__update_label_table_2(label::in, label_vars::in,
+	context::in, is_label_return::in,
 	map(string, label_table)::in, map(string, label_table)::out) is det.
 
-stack_layout__update_label_table_2(Label, Context, IsReturn,
+stack_layout__update_label_table_2(Label, LabelVars, Context, IsReturn,
 		LabelTables0, LabelTables) :-
 	term__context_file(Context, File),
 	term__context_line(Context, Line),
 	( map__search(LabelTables0, File, LabelTable0) ->
+		LabelLayout = label_layout(Label, LabelVars),
 		( map__search(LabelTable0, Line, LineInfo0) ->
-			LineInfo = [Label - IsReturn | LineInfo0],
+			LineInfo = [LabelLayout - IsReturn | LineInfo0],
 			map__det_update(LabelTable0, Line, LineInfo,
 				LabelTable),
 			map__det_update(LabelTables0, File, LabelTable,
 				LabelTables)
 		;
-			LineInfo = [Label - IsReturn],
+			LineInfo = [LabelLayout - IsReturn],
 			map__det_insert(LabelTable0, Line, LineInfo,
 				LabelTable),
 			map__det_update(LabelTables0, File, LabelTable,
@@ -672,7 +328,8 @@
 		)
 	; stack_layout__context_is_valid(Context) ->
 		map__init(LabelTable0),
-		LineInfo = [Label - IsReturn],
+		LabelLayout = label_layout(Label, LabelVars),
+		LineInfo = [LabelLayout - IsReturn],
 		map__det_insert(LabelTable0, Line, LineInfo, LabelTable),
 		map__det_insert(LabelTables0, File, LabelTable, LabelTables)
 	;
@@ -708,23 +365,31 @@
 
 	% Construct a procedure-specific layout.
 
-:- pred stack_layout__construct_proc_layout(label::in, determinism::in,
-	int::in, maybe(int)::in, eval_method::in, maybe(label)::in, int::in,
-	hlds_goal::in, instmap::in, trace_slot_info::in, bool::in,
-	prog_varset::in, vartypes::in, map(int, string)::in,
+:- pred stack_layout__construct_proc_layout(label::in, proc_label::in,
+	determinism::in, int::in, maybe(int)::in, eval_method::in,
+	maybe(label)::in, int::in, hlds_goal::in, instmap::in,
+	trace_slot_info::in, prog_varset::in, vartypes::in,
+	map(int, string)::in, proc_layout_kind::in,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
-stack_layout__construct_proc_layout(EntryLabel, Detism, StackSlots,
+stack_layout__construct_proc_layout(EntryLabel, ProcLabel, Detism, StackSlots,
 		MaybeSuccipLoc, EvalMethod, MaybeCallLabel, MaxTraceReg, Goal,
-		InstMap, TraceSlotInfo, ForceProcIdLayout, VarSet, VarTypes,
-		UsedVarNames) -->
+		InstMap, TraceSlotInfo, VarSet, VarTypes, UsedVarNames, Kind)
+		-->
 	{
-		MaybeSuccipLoc = yes(Location0)
+		MaybeSuccipLoc = yes(Location)
 	->
-		Location = Location0
+		( determinism_components(Detism, _, at_most_many) ->
+			SuccipLval = framevar(Location)
+		;
+			SuccipLval = stackvar(Location)
+		),
+		stack_layout__represent_locn_as_int(direct(SuccipLval),
+			SuccipInt),
+		MaybeSuccipInt = yes(SuccipInt)
 	;
-			% Use a dummy location of -1 if there is
-			% no succip on the stack.
+			% Use a dummy location 1 if there is no succip slot
+			% on the stack.
 			%
 			% This case can arise in two circumstances.
 			% First, procedures that use the nondet stack
@@ -749,169 +414,85 @@
 			%
 			% Future uses of stack layouts will have to have
 			% similar constraints.
-		Location = -1
+		MaybeSuccipInt = no
 	},
 	stack_layout__get_static_code_addresses(StaticCodeAddr),
 	{ StaticCodeAddr = yes ->
-		CodeAddrRval = const(code_addr_const(label(EntryLabel)))
+		MaybeEntryLabel = yes(EntryLabel)
 	;
-		% This is a lie; the slot will be filled in for real
-		% at initialization time.
-		CodeAddrRval = const(int_const(0))
+		MaybeEntryLabel = no
 	},
-	{ determinism_components(Detism, _, at_most_many) ->
-		SuccipLval = framevar(Location)
+	{ TraversalGroup = proc_layout_stack_traversal(MaybeEntryLabel,
+		MaybeSuccipInt, StackSlots, Detism) },
+	(
+		{ Kind = proc_layout_traversal },
+		{ MaybeRest = no_proc_id }
 	;
-		SuccipLval = stackvar(Location)
-	},
-	{ stack_layout__represent_locn_as_int(direct(SuccipLval), SuccipRval) },
-	{ StackSlotsRval = const(int_const(StackSlots)) },
-	{ stack_layout__represent_determinism(Detism, DetismRval) },
-	{ TraversalRvals = [yes(CodeAddrRval), yes(SuccipRval),
-		yes(StackSlotsRval), yes(DetismRval)] },
-	{ TraversalArgTypes = [1 - yes(code_ptr), 1 - yes(uint_least32),
-		2 - yes(uint_least16)] },
-
-	stack_layout__get_procid_stack_layout(ProcIdLayout0),
-	{ bool__or(ProcIdLayout0, ForceProcIdLayout, ProcIdLayout) },
-	( { ProcIdLayout = yes } ->
-		{ code_util__extract_proc_label_from_label(EntryLabel,
-			ProcLabel) },
-		{ stack_layout__construct_procid_rvals(ProcLabel, IdRvals,
-			IdArgTypes) },
+		{ Kind = proc_layout_proc_id(_) },
+		{ MaybeRest = proc_id_only }
+	;
+		{ Kind = proc_layout_exec_trace(_) },
 		stack_layout__construct_trace_layout(EvalMethod, MaybeCallLabel,
 			MaxTraceReg, Goal, InstMap, TraceSlotInfo, VarSet,
-			VarTypes, UsedVarNames, TraceRvals, TraceArgTypes),
-		{ list__append(IdRvals, TraceRvals, IdTraceRvals) },
-		{ IdTraceArgTypes = initial(IdArgTypes, TraceArgTypes) }
-	;
-		% Indicate the absence of the proc id and exec trace fields.
-		{ IdTraceRvals = [yes(const(int_const(-1)))] },
-		{ IdTraceArgTypes = initial([1 - yes(integer)], none) }
+			VarTypes, UsedVarNames, ExecTrace),
+		{ MaybeRest = proc_id_and_exec_trace(ExecTrace) }
 	),
 
-	{ Exported = no },	% XXX With the new profiler, we will need to
-				% set this to `yes' if the profiling option
-				% is given and if the procedure is exported.
-				% Beware however that linkage/2 in llds_out.m
-				% assumes that this is `no'.
-	{ list__append(TraversalRvals, IdTraceRvals, Rvals) },
-	{ ArgTypes = initial(TraversalArgTypes, IdTraceArgTypes) },
-	stack_layout__get_module_name(ModuleName),
-	{ CDataName = proc_layout(EntryLabel) },
-	{ CData = comp_gen_c_data(ModuleName, CDataName, Exported,
-		Rvals, ArgTypes, []) },
-	stack_layout__add_proc_layout_data(CData, CDataName, EntryLabel).
+	{ ProcLayout = proc_layout_data(ProcLabel, TraversalGroup, MaybeRest) },
+	{ Data = layout_data(ProcLayout) },
+	{ LayoutName = proc_layout(ProcLabel, Kind) },
+	stack_layout__add_proc_layout_data(Data, LayoutName, EntryLabel).
 
 :- pred stack_layout__construct_trace_layout(eval_method::in, maybe(label)::in,
 	int::in, hlds_goal::in, instmap::in, trace_slot_info::in,
 	prog_varset::in, vartypes::in, map(int, string)::in,
-	list(maybe(rval))::out, create_arg_types::out,
+	proc_layout_exec_trace::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
 stack_layout__construct_trace_layout(EvalMethod, MaybeCallLabel, MaxTraceReg,
 		Goal, InstMap, TraceSlotInfo, VarSet, VarTypes, UsedVarNameMap,
-		Rvals, ArgTypes) -->
-	stack_layout__get_trace_stack_layout(TraceLayout),
-	( { TraceLayout = yes } ->
+		ExecTrace) -->
 		stack_layout__construct_var_name_vector(VarSet, UsedVarNameMap,
-			VarNameCount, VarNameVector),
+		MaxVarNum, VarNameVector),
 		stack_layout__get_trace_level(TraceLevel),
 		stack_layout__get_trace_suppress(TraceSuppress),
 		{ trace_needs_proc_body_reps(TraceLevel, TraceSuppress)
 			= BodyReps },
 		(
 			{ BodyReps = no },
-			{ GoalRepRval = yes(const(int_const(0))) }
+		{ MaybeGoalRepRval = no }
 		;
 			{ BodyReps = yes },
-			stack_layout__get_module_info(ModuleInfo0),
+		stack_layout__get_module_info(ModuleInfo),
 			{ prog_rep__represent_goal(Goal, InstMap, VarTypes,
-				ModuleInfo0, GoalRep) },
+			ModuleInfo, GoalRep) },
 			{ type_to_univ(GoalRep, GoalRepUniv) },
 			stack_layout__get_cell_counter(CellCounter0),
-			{ static_term__term_to_rval(GoalRepUniv, GoalRepRval,
+		{ static_term__term_to_rval(GoalRepUniv, MaybeGoalRepRval,
 				CellCounter0, CellCounter) },
 			stack_layout__set_cell_counter(CellCounter)
 		),
-		stack_layout__get_module_info(ModuleInfo),
-		{
-		( MaybeCallLabel = yes(CallLabel) ->
-			module_info_name(ModuleInfo, ModuleName),
-			CallRval = yes(const(data_addr_const(
-					data_addr(ModuleName,
-						internal_layout(CallLabel)))))
+	{ MaybeCallLabel = yes(CallLabelPrime) ->
+		CallLabel = CallLabelPrime
 		;
 			error("stack_layout__construct_trace_layout: call label not present")
-		),
-		ModuleRval = yes(const(data_addr_const(
-				data_addr(ModuleName, module_layout)))),
-		MaxTraceRegRval = yes(const(int_const(MaxTraceReg))),
-		TraceSlotInfo = trace_slot_info(MaybeFromFullSlot,
+	},
+	{ TraceSlotInfo = trace_slot_info(MaybeFromFullSlot,
 			MaybeIoSeqSlot, MaybeTrailSlots, MaybeMaxfrSlot,
-			MaybeCallTableSlot, MaybeDeclSlots),
-		EvalMethodInt =
-			stack_layout__represent_eval_method(EvalMethod),
-		EvalMethodRval = yes(const(int_const(EvalMethodInt))),
-		( MaybeFromFullSlot = yes(FromFullSlot) ->
-			FromFullRval = yes(const(int_const(FromFullSlot)))
-		;
-			FromFullRval = yes(const(int_const(-1)))
-		),
-		( MaybeIoSeqSlot = yes(IoSeqSlot) ->
-			IoSeqRval = yes(const(int_const(IoSeqSlot)))
-		;
-			IoSeqRval = yes(const(int_const(-1)))
-		),
-		( MaybeTrailSlots = yes(FirstTrailSlot) ->
-			TrailRval = yes(const(int_const(FirstTrailSlot)))
-		;
-			TrailRval = yes(const(int_const(-1)))
-		),
-		( MaybeMaxfrSlot = yes(MaxfrSlot) ->
-			MaxfrRval = yes(const(int_const(MaxfrSlot)))
-		;
-			MaxfrRval = yes(const(int_const(-1)))
-		),
-		( MaybeCallTableSlot = yes(CallTableSlot) ->
-			CallTableRval = yes(const(int_const(CallTableSlot)))
-		;
-			CallTableRval = yes(const(int_const(-1)))
-		),
-		( MaybeDeclSlots = yes(DeclSlot) ->
-			DeclRval = yes(const(int_const(DeclSlot)))
-		;
-			DeclRval = yes(const(int_const(-1)))
-		),
-		Rvals = [CallRval, ModuleRval, GoalRepRval, VarNameVector,
-			VarNameCount, MaxTraceRegRval,
-			FromFullRval, IoSeqRval, TrailRval, MaxfrRval,
-			EvalMethodRval, CallTableRval, DeclRval],
-		ArgTypes = initial([
-			4 - yes(data_ptr),
-			2 - yes(int_least16),
-			7 - yes(int_least8)],
-			none)
-		}
-	;
-		% Indicate the absence of the trace layout fields.
-		{ Rvals = [yes(const(int_const(0)))] },
-		{ ArgTypes = initial([1 - yes(integer)], none) }
-	).
-
-:- func stack_layout__represent_eval_method(eval_method) = int.
-
-stack_layout__represent_eval_method(eval_normal)     = 0.
-stack_layout__represent_eval_method(eval_loop_check) = 1.
-stack_layout__represent_eval_method(eval_memo)       = 2.
-stack_layout__represent_eval_method(eval_minimal)    = 3.
-stack_layout__represent_eval_method(eval_table_io)   = 4.
+		MaybeCallTableSlot, MaybeDeclSlots) },
+		% The label associated with an event must have variable info.
+	{ CallLabelLayout = label_layout(CallLabel, label_has_var_info) },
+	{ ExecTrace = proc_layout_exec_trace(CallLabelLayout, MaybeGoalRepRval,
+		VarNameVector, MaxVarNum, MaxTraceReg,
+		MaybeFromFullSlot, MaybeIoSeqSlot, MaybeTrailSlots,
+		MaybeMaxfrSlot, EvalMethod, MaybeCallTableSlot,
+		MaybeDeclSlots) }.
 
 :- pred stack_layout__construct_var_name_vector(prog_varset::in,
-	map(int, string)::in, maybe(rval)::out, maybe(rval)::out,
+	map(int, string)::in, int::out, list(int)::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
-stack_layout__construct_var_name_vector(VarSet, UsedVarNameMap, Count, Vector)
+stack_layout__construct_var_name_vector(VarSet, UsedVarNameMap, Count, Offsets)
 		-->
 	stack_layout__get_trace_level(TraceLevel),
 	stack_layout__get_trace_suppress(TraceSuppress),
@@ -926,118 +507,47 @@
 		{ NeedsAllNames = no },
 		{ map__to_assoc_list(UsedVarNameMap, VarNames) }
 	),
-	(
-		{ VarNames = [FirstVar - _ | _] }
-	->
+	( { VarNames = [FirstVar - _ | _] } ->
 		stack_layout__construct_var_name_rvals(VarNames, 1,
-			FirstVar, MaxVar, Rvals),
-		{ Count = yes(const(int_const(MaxVar))) },
-		stack_layout__get_cell_counter(C0),
-		{ counter__allocate(CNum, C0, C) },
-		stack_layout__set_cell_counter(C),
-		{ Reuse = no },
-		{ Vector = yes(create(0, Rvals, uniform(yes(uint_least16)),
-			must_be_static, CNum,
-			"stack_layout_var_names_vector", Reuse)) }
+			FirstVar, Count, Offsets)
 	;
-		{ Count = yes(const(int_const(0))) },
-		{ Vector = yes(const(int_const(0))) }
+		{ Count = 0 },
+		{ Offsets = [] }
 	).
 
 :- pred stack_layout__construct_var_name_rvals(assoc_list(int, string)::in,
-	int::in, int::in, int::out, list(maybe(rval))::out,
+	int::in, int::in, int::out, list(int)::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
 stack_layout__construct_var_name_rvals([], _CurNum, MaxNum, MaxNum, []) --> [].
 stack_layout__construct_var_name_rvals([Var - Name | VarNames1], CurNum,
-		MaxNum0, MaxNum, MaybeRvals) -->
+		MaxNum0, MaxNum, [Offset | Offsets1]) -->
 	( { Var = CurNum } ->
 		stack_layout__lookup_string_in_table(Name, Offset),
-		{ Rval = const(int_const(Offset)) },
 		{ MaxNum1 = Var },
 		{ VarNames = VarNames1 }
 	;
-		{ Rval = const(int_const(0)) },
+		{ Offset = 0 },
 		{ MaxNum1 = MaxNum0 },
 		{ VarNames = [Var - Name | VarNames1] }
 	),
 	stack_layout__construct_var_name_rvals(VarNames, CurNum + 1,
-		MaxNum1, MaxNum, MaybeRvals1),
-	{ MaybeRvals = [yes(Rval) | MaybeRvals1] }.
+		MaxNum1, MaxNum, Offsets1).
 
 %---------------------------------------------------------------------------%
 
-:- pred stack_layout__construct_procid_rvals(proc_label::in,
-	list(maybe(rval))::out, initial_arg_types::out) is det.
+	% Construct the layout describing a single internal label
+	% for accurate GC and/or execution tracing.
 
-stack_layout__construct_procid_rvals(ProcLabel, Rvals, ArgTypes) :-
-	(
-		ProcLabel = proc(DefModule, PredFunc, DeclModule,
-			PredName, Arity, ProcId),
-		stack_layout__represent_pred_or_func(PredFunc, PredFuncCode),
-		prog_out__sym_name_to_string(DefModule, DefModuleString),
-		prog_out__sym_name_to_string(DeclModule, DeclModuleString),
-		proc_id_to_int(ProcId, Mode),
-		Rvals = [
-				yes(const(int_const(PredFuncCode))),
-				yes(const(string_const(DeclModuleString))),
-				yes(const(string_const(DefModuleString))),
-				yes(const(string_const(PredName))),
-				yes(const(int_const(Arity))),
-				yes(const(int_const(Mode)))
-			],
-		ArgTypes = [1 - yes(integer), 3 - yes(string),
-				2 - yes(int_least16)]
-	;
-		ProcLabel = special_proc(DefModule, PredName, TypeModule,
-			TypeName, Arity, ProcId),
-		prog_out__sym_name_to_string(TypeModule, TypeModuleString),
-		prog_out__sym_name_to_string(DefModule, DefModuleString),
-		proc_id_to_int(ProcId, Mode),
-		Rvals = [
-				yes(const(string_const(TypeName))),
-				yes(const(string_const(TypeModuleString))),
-				yes(const(string_const(DefModuleString))),
-				yes(const(string_const(PredName))),
-				yes(const(int_const(Arity))),
-				yes(const(int_const(Mode)))
-			],
-		ArgTypes = [4 - yes(string), 2 - yes(int_least16)]
-	).
-
-:- pred stack_layout__represent_pred_or_func(pred_or_func::in, int::out) is det.
-
-stack_layout__represent_pred_or_func(predicate, 0).
-stack_layout__represent_pred_or_func(function, 1).
-
-%---------------------------------------------------------------------------%
-
-	% Construct the layout describing a single internal label.
-
-:- pred stack_layout__construct_internal_layout(label::in,
+:- pred stack_layout__construct_internal_layout(layout_name::in,
 	pair(label, internal_layout_info)::in,
+	assoc_list(pair(label, label_vars), internal_layout_info)::in,
+	assoc_list(pair(label, label_vars), internal_layout_info)::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
-
-stack_layout__construct_internal_layout(EntryLabel, Label - Internal) -->
-		% generate the required rvals
-	stack_layout__get_module_name(ModuleName),
-	{ EntryAddrRval = const(data_addr_const(data_addr(ModuleName,
-		proc_layout(EntryLabel)))) },
-	stack_layout__construct_internal_rvals(Internal, VarInfoRvals,
-		VarInfoRvalTypes),
-	{ LayoutRvals = [yes(EntryAddrRval) | VarInfoRvals] },
-	{ ArgTypes = initial([1 - no], VarInfoRvalTypes) },
-	{ CData = comp_gen_c_data(ModuleName, internal_layout(Label),
-		no, LayoutRvals, ArgTypes, []) },
-	stack_layout__add_internal_layout_data(CData, Label).
-
-	% Construct the rvals required for accurate GC or for tracing.
 
-:- pred stack_layout__construct_internal_rvals(internal_layout_info::in,
-	list(maybe(rval))::out, create_arg_types::out,
-	stack_layout_info::in, stack_layout_info::out) is det.
-
-stack_layout__construct_internal_rvals(Internal, RvalList, ArgTypes) -->
+stack_layout__construct_internal_layout(ProcLayoutName, Label - Internal,
+		LabelLayouts, [(Label - LabelVars) - Internal | LabelLayouts])
+		-->
 	{ Internal = internal_layout_info(Trace, Resume, Return) },
 	(
 		{ Trace = no },
@@ -1048,7 +558,6 @@
 		{ TraceLayout = layout_label_info(TraceLiveVarSet,
 			TraceTypeVarMap) }
 	),
-	{ TraceArgTypes = [2 - yes(int_least16)] },
 	{
 		Resume = no,
 		set__init(ResumeLiveVarSet),
@@ -1061,9 +570,10 @@
 	(
 		{ Trace = yes(trace_port_layout_info(_, Port, GoalPath, _)) },
 		{ Return = no },
-		{ llds_out__trace_port_to_num(Port, PortNum) },
+		{ MaybePort = yes(Port) },
 		{ trace__path_to_string(GoalPath, GoalPathStr) },
-		stack_layout__lookup_string_in_table(GoalPathStr, GoalPathNum)
+		stack_layout__lookup_string_in_table(GoalPathStr, GoalPathNum),
+		{ MaybeGoalPath = yes(GoalPathNum) }
 	;
 		{ Trace = no },
 		{ Return = yes(ReturnInfo) },
@@ -1071,7 +581,7 @@
 			% structures when we process exception events.
 			% (Since exception events are interface events,
 			% the goal path field is not meaningful then.)
-		{ llds_out__trace_port_to_num(exception, PortNum) },
+		{ MaybePort = yes(exception) },
 			% We only ever use the goal path fields of these
 			% layout structures when we process "fail" commands
 			% in the debugger.
@@ -1082,7 +592,8 @@
 		->
 			{ trace__path_to_string(GoalPath, GoalPathStr) },
 			stack_layout__lookup_string_in_table(GoalPathStr,
-				GoalPathNum)
+				GoalPathNum),
+			{ MaybeGoalPath = yes(GoalPathNum) }
 		;
 				% If tracing is enabled, then exactly one of
 				% the calls for which this label is a return
@@ -1090,20 +601,18 @@
 				% do, then tracing is not enabled, and
 				% therefore the goal path of this label will
 				% not be accessed.
-			{ GoalPathNum = 0 }
+			{ MaybeGoalPath = no }
 		)
 	;
 		{ Trace = no },
 		{ Return = no },
-		{ PortNum = -1 },
-		{ GoalPathNum = -1 }
+		{ MaybePort = no },
+		{ MaybeGoalPath = no }
 	;
 		{ Trace = yes(_) },
 		{ Return = yes(_) },
 		{ error("label has both trace and return layout info") }
 	),
-	{ TraceRvals = [yes(const(int_const(PortNum))),
-			yes(const(int_const(GoalPathNum)))] },
 	stack_layout__get_agc_stack_layout(AgcStackLayout),
 	{
 		Return = no,
@@ -1113,10 +622,12 @@
 		Return = yes(return_layout_info(_, ReturnLayout)),
 		ReturnLayout = layout_label_info(ReturnLiveVarSet0,
 			ReturnTypeVarMap0),
-		( AgcStackLayout = yes ->
+		(
+			AgcStackLayout = yes,
 			ReturnLiveVarSet = ReturnLiveVarSet0,
 			ReturnTypeVarMap = ReturnTypeVarMap0
 		;
+			AgcStackLayout = no,
 			% This set of variables must be for uplevel printing
 			% in execution tracing, so we are interested only
 			% in (a) variables, not temporaries, (b) only named
@@ -1135,12 +646,8 @@
 		{ Resume = no },
 		{ Return = no }
 	->
-			% The -1 says that there is no info available
-			% about variables at this label. (Zero would say
-			% that there are no variables live at this label,
-			% which may not be true.)
-		{ RvalList = [yes(const(int_const(-1)))] },
-		{ ArgTypes = initial([1 - yes(integer)], none) }
+		{ MaybeVarInfo = no },
+		{ LabelVars = label_has_no_var_info }
 	;
 			% XXX ignore differences in insts inside var_infos
 		{ set__union(TraceLiveVarSet, ResumeLiveVarSet, LiveVarSet0) },
@@ -1149,39 +656,36 @@
 			TypeVarMap0) },
 		{ map__union(set__intersect, TypeVarMap0, ReturnTypeVarMap,
 			TypeVarMap) },
-		stack_layout__construct_livelval_rvals(LiveVarSet,
-			TypeVarMap, LivelvalRvalList, LivelvalArgTypes),
-		{ append(TraceRvals, LivelvalRvalList, RvalList) },
-		{ ArgTypes = initial(TraceArgTypes, LivelvalArgTypes) }
-	).
+		stack_layout__construct_livelval_rvals(LiveVarSet, TypeVarMap,
+			EncodedLength, LiveValRval, NamesRval, TypeParamRval),
+		{ VarInfo = label_var_info(EncodedLength, 
+			LiveValRval, NamesRval, TypeParamRval) },
+		{ MaybeVarInfo = yes(VarInfo) },
+		{ LabelVars = label_has_var_info }
+	),
+
+	{ LayoutData = label_layout_data(Label, ProcLayoutName,
+		MaybePort, MaybeGoalPath, MaybeVarInfo) },
+	{ CData = layout_data(LayoutData) },
+	{ LayoutName = label_layout(Label, LabelVars) },
+	stack_layout__add_internal_layout_data(CData, Label, LayoutName).
 
 %---------------------------------------------------------------------------%
 
 :- pred stack_layout__construct_livelval_rvals(set(var_info)::in,
-	map(tvar, set(layout_locn))::in, list(maybe(rval))::out,
-	create_arg_types::out, stack_layout_info::in, stack_layout_info::out)
-	is det.
+	map(tvar, set(layout_locn))::in, int::out, rval::out, rval::out,
+	rval::out, stack_layout_info::in, stack_layout_info::out) is det.
 
-stack_layout__construct_livelval_rvals(LiveLvalSet, TVarLocnMap,
-		RvalList, ArgTypes) -->
+stack_layout__construct_livelval_rvals(LiveLvalSet, TVarLocnMap, EncodedLength,
+		LiveValRval, NamesRval, TypeParamRval) -->
 	{ set__to_sorted_list(LiveLvalSet, LiveLvals) },
-	{ list__length(LiveLvals, Length) },
-	( { Length > 0 } ->
 		{ stack_layout__sort_livevals(LiveLvals, SortedLiveLvals) },
 		stack_layout__construct_liveval_arrays(SortedLiveLvals,
-			VarLengthRval, LiveValRval, NamesRval),
+		EncodedLength, LiveValRval, NamesRval),
 		stack_layout__get_cell_counter(C0),
 		{ stack_layout__construct_tvar_vector(TVarLocnMap,
 			TypeParamRval, C0, C) },
-		stack_layout__set_cell_counter(C),
-		{ RvalList = [yes(VarLengthRval), yes(LiveValRval),
-			yes(NamesRval), yes(TypeParamRval)] },
-		{ ArgTypes = initial([1 - yes(integer), 3 - yes(data_ptr)],
-			none) }
-	;
-		{ RvalList = [yes(const(int_const(0)))] },
-		{ ArgTypes = initial([1 - yes(integer)], none) }
-	).
+	stack_layout__set_cell_counter(C).
 
 :- pred stack_layout__construct_tvar_vector(map(tvar, set(layout_locn))::in,
 	rval::out, counter::in, counter::out) is det.
@@ -1303,7 +807,7 @@
 		;
 			error("tvar has empty set of locations")
 		),
-		stack_layout__represent_locn_as_int(Locn, Rval),
+		stack_layout__represent_locn_as_int_rval(Locn, Rval),
 		stack_layout__construct_type_param_locn_vector(TVarLocns,
 			NextSlot, VectorTail),
 		Vector = [yes(Rval) | VectorTail]
@@ -1339,10 +843,10 @@
 	% and a corresponding vector of variable names.
 
 :- pred stack_layout__construct_liveval_arrays(list(var_info)::in,
-	rval::out, rval::out, rval::out,
+	int::out, rval::out, rval::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
-stack_layout__construct_liveval_arrays(VarInfos, LengthRval,
+stack_layout__construct_liveval_arrays(VarInfos, EncodedLength,
 		TypeLocnVector, NumVector) -->
 	{ int__pow(2, stack_layout__short_count_bits, BytesLimit) },
 	stack_layout__construct_liveval_array_infos(VarInfos,
@@ -1352,9 +856,8 @@
 	{ list__length(ByteArrayInfo, ByteArrayLength) },
 	{ list__append(IntArrayInfo, ByteArrayInfo, AllArrayInfo) },
 
-	{ EncodedLength is IntArrayLength << stack_layout__short_count_bits
+	{ EncodedLength = IntArrayLength << stack_layout__short_count_bits
 		+ ByteArrayLength },
-	{ LengthRval = const(int_const(EncodedLength)) },
 
 	{ SelectLocns = (pred(ArrayInfo::in, MaybeLocnRval::out) is det :-
 		ArrayInfo = live_array_info(LocnRval, _, _, _),
@@ -1424,7 +927,7 @@
 			BytesSoFar + 1, BytesLimit, IntVars, ByteVars0),
 		{ ByteVars = [Var | ByteVars0] }
 	;
-		{ stack_layout__represent_locn_as_int(Locn, LocnRval) },
+		{ stack_layout__represent_locn_as_int_rval(Locn, LocnRval) },
 		{ Var = live_array_info(LocnRval, TypeRval, TypeRvalType,
 			VarNumRval) },
 		stack_layout__construct_liveval_array_infos(VarInfos,
@@ -1479,22 +982,26 @@
 	% with runtime/mercury_ho_call.h, which contains macros to access
 	% the data structures we build here.
 
-stack_layout__construct_closure_layout(ProcLabel, ClosureLayoutInfo,
-		Rvals, ArgTypes, C0, C) :-
-	stack_layout__construct_procid_rvals(ProcLabel, ProcIdRvals,
-		ProcIdTypes),
-	ClosureLayoutInfo = closure_layout_info(ClosureArgs,
-		TVarLocnMap),
+stack_layout__construct_closure_layout(CallerProcLabel, SeqNo,
+		ClosureLayoutInfo, ClosureProcLabel,
+		ModuleName, FileName, LineNumber, GoalPath,
+		Rvals, ArgTypes, Data, C0, C) :-
+	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),
+	ClosureLayoutInfo = closure_layout_info(ClosureArgs, TVarLocnMap),
 	stack_layout__construct_closure_arg_rvals(ClosureArgs,
-		ClosureArgRvals, ClosureArgTypes, C0, C1),
+		MaybeClosureArgRvals, ClosureArgTypes, C0, C1),
 	stack_layout__construct_tvar_vector(TVarLocnMap, TVarVectorRval,
 		C1, C),
-	TVarVectorRvals = [yes(TVarVectorRval)],
-	TVarVectorTypes = [1 - yes(data_ptr)],
-	list__append(TVarVectorRvals, ClosureArgRvals, LayoutRvals),
-	list__append(ProcIdRvals, LayoutRvals, Rvals),
-	ArgTypes = initial(ProcIdTypes, initial(TVarVectorTypes,
-		initial(ClosureArgTypes, none))).
+	MaybeTVarVectorRval = yes(TVarVectorRval),
+	TVarVectorType = 1 - yes(data_ptr),
+	Rvals = [MaybeProcIdRval, MaybeTVarVectorRval | MaybeClosureArgRvals],
+	ArgTypes = initial([ProcIdType, TVarVectorType | ClosureArgTypes],
+		none).
 
 :- pred stack_layout__construct_closure_arg_rvals(list(closure_arg_info)::in,
 	list(maybe(rval))::out, initial_arg_types::out,
@@ -1617,25 +1124,28 @@
 	% A more general representation that would allow more indirection
 	% would be much harder to fit into one machine word.
 
-:- pred stack_layout__represent_locn_as_int(layout_locn, rval).
-:- mode stack_layout__represent_locn_as_int(in, out) is det.
+:- pred stack_layout__represent_locn_as_int_rval(layout_locn::in, rval::out)
+	is det.
 
-stack_layout__represent_locn_as_int(direct(Lval), Rval) :-
-	stack_layout__represent_lval(Lval, Word),
+stack_layout__represent_locn_as_int_rval(Locn, Rval) :-
+	stack_layout__represent_locn_as_int(Locn, Word),
 	Rval = const(int_const(Word)).
-stack_layout__represent_locn_as_int(indirect(Lval, Offset), Rval) :-
+
+:- pred stack_layout__represent_locn_as_int(layout_locn::in, int::out) is det.
+
+stack_layout__represent_locn_as_int(direct(Lval), Word) :-
+	stack_layout__represent_lval(Lval, Word).
+stack_layout__represent_locn_as_int(indirect(Lval, Offset), Word) :-
 	stack_layout__represent_lval(Lval, BaseWord),
 	require((1 << stack_layout__long_lval_offset_bits) > Offset,
 	"stack_layout__represent_locn: offset too large to be represented"),
 	BaseAndOffset is (BaseWord << stack_layout__long_lval_offset_bits)
 		+ Offset,
-	stack_layout__make_tagged_word(lval_indirect, BaseAndOffset, Word),
-	Rval = const(int_const(Word)).
+	stack_layout__make_tagged_word(lval_indirect, BaseAndOffset, Word).
 
 	% Construct a four byte representation of an lval.
 
-:- pred stack_layout__represent_lval(lval, int).
-:- mode stack_layout__represent_lval(in, out) is det.
+:- pred stack_layout__represent_lval(lval::in, int::out) is det.
 
 stack_layout__represent_lval(reg(r, Num), Word) :-
 	stack_layout__make_tagged_word(lval_r_reg, Num, Word).
@@ -1804,9 +1314,15 @@
 	% The 2 bit is set iff the max number of solutions is more than zero.
 	% The 1 bit is set iff the max number of solutions is more than one.
 
-:- pred stack_layout__represent_determinism(determinism::in, rval::out) is det.
+:- pred stack_layout__represent_determinism_rval(determinism::in, rval::out)
+	is det.
+
+stack_layout__represent_determinism_rval(Detism, const(int_const(Code))) :-
+	stack_layout__represent_determinism(Detism, Code).
+
+:- pred stack_layout__represent_determinism(determinism::in, int::out) is det.
 
-stack_layout__represent_determinism(Detism, const(int_const(Code))) :-
+stack_layout__represent_determinism(Detism, Code) :-
 	(
 		Detism = det,
 		Code = 6		/* 0110 */
@@ -1847,7 +1363,7 @@
 	;	unknown_callee
 	;	not_a_return.
 
-:- type line_no_info == pair(label, is_label_return).
+:- type line_no_info == pair(layout_name, is_label_return).
 
 :- type label_table == map(int, list(line_no_info)).
 
@@ -1862,13 +1378,12 @@
 		static_code_addresses	:: bool, % have static code addresses?
 		proc_layouts		:: list(comp_gen_c_data),
 		internal_layouts	:: list(comp_gen_c_data),
-		label_set		:: set_bbbtree(label),
+		label_set		:: map(label, data_addr),
 					   % The set of labels (both entry
 					   % and internal) with layouts.
-		proc_layout_args	:: list(maybe(rval)),
+		proc_layout_name_list	:: list(layout_name),
 					   % The list of proc_layouts in
-					   % the module, represented as create
-					   % args.
+					   % the module.
 		string_table		:: string_table,
 		label_tables		:: map(string, label_table),
 					   % Maps each filename that
@@ -1910,7 +1425,7 @@
 :- pred stack_layout__get_internal_layout_data(list(comp_gen_c_data)::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__get_label_set(set_bbbtree(label)::out,
+:- pred stack_layout__get_label_set(map(label, data_addr)::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
 :- pred stack_layout__get_string_table(string_table::out,
@@ -1950,33 +1465,33 @@
 	stack_layout__get_module_info(ModuleInfo),
 	{ module_info_get_cell_counter(ModuleInfo, CellCounter) }.
 
-:- pred stack_layout__add_proc_layout_data(comp_gen_c_data::in, data_name::in,
-	label::in, stack_layout_info::in, stack_layout_info::out) is det.
+:- pred stack_layout__add_proc_layout_data(comp_gen_c_data::in,
+	layout_name::in, label::in,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-stack_layout__add_proc_layout_data(NewProcLayout, NewDataName, NewLabel,
+stack_layout__add_proc_layout_data(ProcLayout, ProcLayoutName, Label,
 		LI0, LI) :-
 	ProcLayouts0 = LI0 ^ proc_layouts,
-	ProcLayouts = [NewProcLayout | ProcLayouts0],
+	ProcLayouts = [ProcLayout | ProcLayouts0],
 	LabelSet0 = LI0 ^ label_set,
-	set_bbbtree__insert(LabelSet0, NewLabel, LabelSet),
-	ModuleInfo = LI0 ^ module_info,
-	module_info_name(ModuleInfo, ModuleName),
-	NewProcLayoutArg = yes(const(data_addr_const(
-		data_addr(ModuleName, NewDataName)))),
-	ProcLayoutArgs0 = LI0 ^ proc_layout_args,
-	ProcLayoutArgs = [NewProcLayoutArg | ProcLayoutArgs0],
+	map__det_insert(LabelSet0, Label, layout_addr(ProcLayoutName),
+		LabelSet),
+	ProcLayoutNames0 = LI0 ^ proc_layout_name_list,
+	ProcLayoutNames = [ProcLayoutName | ProcLayoutNames0],
 	LI = (((LI0 ^ proc_layouts := ProcLayouts)
 		^ label_set := LabelSet)
-		^ proc_layout_args := ProcLayoutArgs).
+		^ proc_layout_name_list := ProcLayoutNames).
 
 :- pred stack_layout__add_internal_layout_data(comp_gen_c_data::in,
-	label::in, stack_layout_info::in, stack_layout_info::out) is det.
+	label::in, layout_name::in, stack_layout_info::in,
+	stack_layout_info::out) is det.
 
-stack_layout__add_internal_layout_data(NewInternalLayout, NewLabel, LI0, LI) :-
+stack_layout__add_internal_layout_data(InternalLayout, Label, LayoutName,
+		LI0, LI) :-
 	InternalLayouts0 = LI0 ^ internal_layouts,
-	InternalLayouts = [NewInternalLayout | InternalLayouts0],
+	InternalLayouts = [InternalLayout | InternalLayouts0],
 	LabelSet0 = LI0 ^ label_set,
-	set_bbbtree__insert(LabelSet0, NewLabel, LabelSet),
+	map__det_insert(LabelSet0, Label, layout_addr(LayoutName), LabelSet),
 	LI = ((LI0 ^ internal_layouts := InternalLayouts)
 		^ label_set := LabelSet).
 
Index: compiler/trace.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/trace.m,v
retrieving revision 1.43
diff -u -b -r1.43 trace.m
--- compiler/trace.m	2000/12/18 05:14:23	1.43
+++ compiler/trace.m	2001/01/02 07:41:35
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% Copyright (C) 1997-2000 The University of Melbourne.
+% Copyright (C) 1997-2001 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.
 %-----------------------------------------------------------------------------%
@@ -218,9 +218,9 @@
 
 :- implementation.
 
-:- import_module continuation_info, trace_params, type_util, llds_out, tree.
-:- import_module (inst), instmap, inst_match, code_util, mode_util, options.
-:- import_module code_model.
+:- import_module continuation_info, trace_params, llds_out, layout_out, tree.
+:- import_module type_util, (inst), instmap, inst_match, mode_util.
+:- import_module code_model, code_util, options.
 
 :- import_module list, bool, int, string, map, std_util, require, term, varset.
 
@@ -543,7 +543,7 @@
 		MaybeRedoLabel = yes(RedoLayoutLabel),
 		trace__redo_layout_slot(CodeModel, RedoLayoutLval),
 		trace__stackref_to_string(RedoLayoutLval, RedoLayoutStr),
-		llds_out__make_stack_layout_name(RedoLayoutLabel,
+		layout_out__make_label_layout_name(RedoLayoutLabel,
 			LayoutAddrStr),
 		string__append_list([
 			FillSlotsUptoIoSeq, "\n",
@@ -802,7 +802,7 @@
 		VarLocs, ProcInfo, TvarDataMap),
 	set__list_to_set(VarInfoList, VarInfoSet),
 	LayoutLabelInfo = layout_label_info(VarInfoSet, TvarDataMap),
-	llds_out__get_label(Label, yes, LabelStr),
+	layout_out__make_label_layout_name(Label, LabelStr),
 	DeclStmt = "\t\tMR_Code *MR_jumpaddr;\n",
 	SaveStmt = "\t\tMR_save_transient_registers();\n",
 	RestoreStmt = "\t\tMR_restore_transient_registers();\n",
@@ -810,8 +810,8 @@
 	},
 	{ string__append_list([
 		"\t\tMR_jumpaddr = MR_trace(\n",
-		"\t\t\t(const MR_Stack_Layout_Label *)\n",
-		"\t\t\t&mercury_data__layout__", LabelStr, ");\n"],
+		"\t\t\t(const MR_Label_Layout *)\n",
+		"\t\t\t&", LabelStr, ");\n"],
 		CallStmt) },
 	code_info__add_trace_layout_for_label(Label, Context, Port, Path,
 		LayoutLabelInfo),
Index: compiler/trace_params.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/trace_params.m,v
retrieving revision 1.3
diff -u -b -r1.3 trace_params.m
--- compiler/trace_params.m	2000/11/10 01:00:56	1.3
+++ compiler/trace_params.m	2001/01/02 07:41:41
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% Copyright (C) 2000 The University of Melbourne.
+% Copyright (C) 2000-2001 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.
 %-----------------------------------------------------------------------------%
@@ -42,7 +42,7 @@
 :- func trace_level_none = trace_level.
 
 	% This is used to represent the trace level in the module layout.
-:- func trace_level_rep(trace_level) = int.
+:- func trace_level_rep(trace_level) = string.
 
 :- implementation.
 
@@ -232,11 +232,11 @@
 
 	% If this is modified, then the corresponding code in
 	% runtime/mercury_stack_layout.h needs to be updated.
-trace_level_rep(none) = 0.
-trace_level_rep(shallow) = 1.
-trace_level_rep(deep) = 2.
-trace_level_rep(decl) = 3.
-trace_level_rep(decl_rep) = 4.
+trace_level_rep(none)	  = "MR_TRACE_LEVEL_NONE".
+trace_level_rep(shallow)  = "MR_TRACE_LEVEL_SHALLOW".
+trace_level_rep(deep)	  = "MR_TRACE_LEVEL_DEEP".
+trace_level_rep(decl)	  = "MR_TRACE_LEVEL_DECL".
+trace_level_rep(decl_rep) = "MR_TRACE_LEVEL_DECL_REP".
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/unify_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/unify_gen.m,v
retrieving revision 1.112
diff -u -b -r1.112 unify_gen.m
--- compiler/unify_gen.m	2000/11/23 04:32:50	1.112
+++ compiler/unify_gen.m	2001/01/02 07:41:43
@@ -1,5 +1,5 @@
 %---------------------------------------------------------------------------%
-% Copyright (C) 1994-2000 The University of Melbourne.
+% Copyright (C) 1994-2001 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.
 %---------------------------------------------------------------------------%
@@ -28,7 +28,8 @@
 	;	branch_on_failure.
 
 :- pred unify_gen__generate_unification(code_model::in, unification::in,
-	code_tree::out, code_info::in, code_info::out) is det.
+	hlds_goal_info::in, code_tree::out, code_info::in, code_info::out)
+	is det.
 
 :- pred unify_gen__generate_tag_test(prog_var::in, cons_id::in, test_sense::in,
 	label::out, code_tree::out, code_info::in, code_info::out) is det.
@@ -41,7 +42,7 @@
 :- import_module hlds_module, hlds_pred, prog_data, prog_out, code_util.
 :- import_module mode_util, type_util, code_aux, hlds_out, tree, arg_info.
 :- import_module globals, options, continuation_info, stack_layout.
-:- import_module rl.
+:- import_module rl, trace.
 
 :- import_module term, bool, string, int, list, map, require, std_util.
 
@@ -50,7 +51,7 @@
 
 %---------------------------------------------------------------------------%
 
-unify_gen__generate_unification(CodeModel, Uni, Code) -->
+unify_gen__generate_unification(CodeModel, Uni, GoalInfo, Code) -->
 	{ CodeModel = model_non ->
 		error("nondet unification in unify_gen__generate_unification")
 	;
@@ -67,7 +68,7 @@
 		{ Uni = construct(Var, ConsId, Args, Modes, _, _, AditiInfo) },
 		( code_info__variable_is_forward_live(Var) ->
 			unify_gen__generate_construction(Var, ConsId,
-				Args, Modes, AditiInfo, Code)
+				Args, Modes, AditiInfo, GoalInfo, Code)
 		;
 			{ Code = empty }
 		)
@@ -271,27 +272,30 @@
 
 :- pred unify_gen__generate_construction(prog_var::in, cons_id::in,
 	list(prog_var)::in, list(uni_mode)::in, maybe(rl_exprn_id)::in,
-	code_tree::out, code_info::in, code_info::out) is det.
+	hlds_goal_info::in, code_tree::out, code_info::in, code_info::out)
+	is det.
 
-unify_gen__generate_construction(Var, Cons, Args, Modes, AditiInfo, Code) -->
+unify_gen__generate_construction(Var, Cons, Args, Modes, AditiInfo, GoalInfo,
+		Code) -->
 	code_info__cons_id_to_tag(Var, Cons, Tag),
 	unify_gen__generate_construction_2(Tag, Var, Args,
-		Modes, AditiInfo, Code).
+		Modes, AditiInfo, GoalInfo, Code).
 
 :- pred unify_gen__generate_construction_2(cons_tag::in, prog_var::in, 
 	list(prog_var)::in, list(uni_mode)::in, maybe(rl_exprn_id)::in,
-	code_tree::out, code_info::in, code_info::out) is det.
+	hlds_goal_info::in, code_tree::out, code_info::in, code_info::out)
+	is det.
 
 unify_gen__generate_construction_2(string_constant(String),
-		Var, _Args, _Modes, _, empty) -->
+		Var, _Args, _Modes, _, _, empty) -->
 	code_info__assign_const_to_var(Var, const(string_const(String))).
 unify_gen__generate_construction_2(int_constant(Int),
-		Var, _Args, _Modes, _, empty) -->
+		Var, _Args, _Modes, _, _, empty) -->
 	code_info__assign_const_to_var(Var, const(int_const(Int))).
 unify_gen__generate_construction_2(float_constant(Float),
-		Var, _Args, _Modes, _, empty) -->
+		Var, _Args, _Modes, _, _, empty) -->
 	code_info__assign_const_to_var(Var, const(float_const(Float))).
-unify_gen__generate_construction_2(no_tag, Var, Args, Modes, _, Code) -->
+unify_gen__generate_construction_2(no_tag, Var, Args, Modes, _, _, Code) -->
 	( { Args = [Arg], Modes = [Mode] } ->
 		code_info__variable_type(Arg, Type),
 		unify_gen__generate_sub_unify(ref(Var), ref(Arg),
@@ -301,7 +305,7 @@
 		"unify_gen__generate_construction_2: no_tag: arity != 1") }
 	).
 unify_gen__generate_construction_2(unshared_tag(Ptag),
-		Var, Args, Modes, _, Code) -->
+		Var, Args, Modes, _, _, Code) -->
 	code_info__get_module_info(ModuleInfo),
 	unify_gen__var_types(Args, ArgTypes),
 	{ unify_gen__generate_cons_args(Args, ArgTypes, Modes, ModuleInfo,
@@ -310,7 +314,7 @@
 	{ unify_gen__var_type_msg(VarType, VarTypeMsg) },
 	code_info__assign_cell_to_var(Var, Ptag, Rvals, VarTypeMsg, Code).
 unify_gen__generate_construction_2(shared_remote_tag(Ptag, Sectag),
-		Var, Args, Modes, _, Code) -->
+		Var, Args, Modes, _, _, Code) -->
 	code_info__get_module_info(ModuleInfo),
 	unify_gen__var_types(Args, ArgTypes),
 	{ unify_gen__generate_cons_args(Args, ArgTypes, Modes, ModuleInfo,
@@ -321,11 +325,11 @@
 	{ unify_gen__var_type_msg(VarType, VarTypeMsg) },
 	code_info__assign_cell_to_var(Var, Ptag, Rvals, VarTypeMsg, Code).
 unify_gen__generate_construction_2(shared_local_tag(Bits1, Num1),
-		Var, _Args, _Modes, _, empty) -->
+		Var, _Args, _Modes, _, _, empty) -->
 	code_info__assign_const_to_var(Var,
 		mkword(Bits1, unop(mkbody, const(int_const(Num1))))).
 unify_gen__generate_construction_2(type_ctor_info_constant(ModuleName,
-		TypeName, TypeArity), Var, Args, _Modes, _, empty) -->
+		TypeName, TypeArity), Var, Args, _Modes, _, _, empty) -->
 	( { Args = [] } ->
 		[]
 	;
@@ -335,7 +339,7 @@
 	{ DataAddr = rtti_addr(RttiTypeId, type_ctor_info) },
 	code_info__assign_const_to_var(Var, const(data_addr_const(DataAddr))).
 unify_gen__generate_construction_2(base_typeclass_info_constant(ModuleName,
-		ClassId, Instance), Var, Args, _Modes, _, empty) -->
+		ClassId, Instance), Var, Args, _Modes, _, _, empty) -->
 	( { Args = [] } ->
 		[]
 	;
@@ -344,7 +348,7 @@
 	code_info__assign_const_to_var(Var, const(data_addr_const(data_addr(
 		ModuleName, base_typeclass_info(ClassId, Instance))))).
 unify_gen__generate_construction_2(tabling_pointer_constant(PredId, ProcId),
-		Var, Args, _Modes, _, empty) -->
+		Var, Args, _Modes, _, _, empty) -->
 	( { Args = [] } ->
 		[]
 	;
@@ -356,7 +360,7 @@
 	{ DataAddr = data_addr(ModuleName, tabling_pointer(ProcLabel)) },
 	code_info__assign_const_to_var(Var, const(data_addr_const(DataAddr))).
 unify_gen__generate_construction_2(code_addr_constant(PredId, ProcId),
-		Var, Args, _Modes, _, empty) -->
+		Var, Args, _Modes, _, _, empty) -->
 	( { Args = [] } ->
 		[]
 	;
@@ -367,7 +371,7 @@
 	code_info__assign_const_to_var(Var, const(code_addr_const(CodeAddr))).
 unify_gen__generate_construction_2(
 		pred_closure_tag(PredId, ProcId, EvalMethod),
-		Var, Args, _Modes, _AditiInfo, Code) -->
+		Var, Args, _Modes, _AditiInfo, GoalInfo, Code) -->
 	% This code constructs or extends a closure.
 	% The structure of closures is defined in runtime/mercury_ho_call.h.
 
@@ -534,10 +538,21 @@
 		),
 		{ continuation_info__generate_closure_layout(
 			ModuleInfo, PredId, ProcId, ClosureInfo) },
+		{ module_info_name(ModuleInfo, ModuleName) },
+		{ goal_info_get_context(GoalInfo, Context) },
+		{ term__context_file(Context, FileName) },
+		{ term__context_line(Context, LineNumber) },
+		{ goal_info_get_goal_path(GoalInfo, GoalPath) },
+		{ trace__path_to_string(GoalPath, GoalPathStr) },
+		code_info__get_cur_proc_label(CallerProcLabel),
+		code_info__get_next_closure_seq_no(SeqNo),
 		code_info__get_cell_counter(C0),
-		{ stack_layout__construct_closure_layout(ProcLabel,
-			ClosureInfo, ClosureLayoutMaybeRvals,
-			ClosureLayoutArgTypes, C0, C) },
+		{ stack_layout__construct_closure_layout(CallerProcLabel,
+			SeqNo, ClosureInfo, ProcLabel, ModuleName,
+			FileName, LineNumber, GoalPathStr,
+			ClosureLayoutMaybeRvals, ClosureLayoutArgTypes,
+			Data, C0, C) },
+		code_info__add_closure_layout(Data),
 		code_info__set_cell_counter(C),
 		code_info__get_next_cell_number(ClosureLayoutCellNo),
 		{ Reuse = no },
cvs diff: Diffing compiler/notes
cvs diff: Diffing debian
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/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
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/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/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 library
Index: library/exception.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/exception.m,v
retrieving revision 1.38
diff -u -b -r1.38 exception.m
--- library/exception.m	2001/01/01 04:03:50	1.38
+++ library/exception.m	2001/01/02 02:15:12
@@ -1036,7 +1036,7 @@
 	MR_Word *current_frame)
 {
 	const MR_Internal		*label;
-	const MR_Stack_Layout_Label	*return_label_layout;
+	const MR_Label_Layout	*return_label_layout;
 
 	/*
 	** Find the layout info for the stack frame pointed to by MR_succip
@@ -1049,7 +1049,7 @@
 	return_label_layout = label->i_layout;
 
 	while (return_label_layout != NULL) {
-		const MR_Stack_Layout_Entry	*entry_layout;
+		const MR_Proc_Layout		*entry_layout;
 		MR_Code 			*MR_jumpaddr;
 		MR_Stack_Walk_Step_Result	result;
 		const char			*problem;
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
Index: runtime/mercury_accurate_gc.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_accurate_gc.c,v
retrieving revision 1.10
diff -u -b -r1.10 mercury_accurate_gc.c
--- runtime/mercury_accurate_gc.c	2000/11/23 02:00:21	1.10
+++ runtime/mercury_accurate_gc.c	2001/01/02 07:43:06
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -66,8 +66,8 @@
 MR_schedule_agc(MR_Code *pc_at_signal, MR_Word *sp_at_signal, 
 	MR_Word *curfr_at_signal)
 {
-	MR_Stack_Layout_Label		*layout;
-	const MR_Stack_Layout_Entry	*entry_layout;
+	MR_Label_Layout		*layout;
+	const MR_Proc_Layout	*proc_layout;
 	MR_Long_Lval_Type		type;
 	MR_Long_Lval			location;
 	const char			*reason;
@@ -106,9 +106,9 @@
 	/* Search for the entry label */
 
 	entry_label = MR_prev_entry_by_addr(pc_at_signal);
-	entry_layout = entry_label->e_layout;
+	proc_layout = entry_label->e_layout;
 
-	determinism = entry_layout->MR_sle_detism;
+	determinism = proc_layout->MR_sle_detism;
 
 	if (determinism < 0) {
 		/*
@@ -155,7 +155,7 @@
 	}
 	gc_scheduled = TRUE;
 
-	location = entry_layout->MR_sle_succip_locn;
+	location = proc_layout->MR_sle_succip_locn;
 	type = MR_LONG_LVAL_TYPE(location);
 	number = MR_LONG_LVAL_NUMBER(location);
 	if (MR_DETISM_DET_STACK(determinism)) {
@@ -240,15 +240,14 @@
 {
     MR_Internal                     *label, *first_label;
     int                             i, count;
-    const MR_Stack_Layout_Label     *internal_layout;
-    const MR_Stack_Layout_Vars      *vars;
+    const MR_Label_Layout	    *label_layout;
     MR_MemoryZone                   *old_heap, *new_heap;
     MR_TypeInfoParams               type_params;
     bool                            succeeded;
     bool                            top_frame = TRUE;
     MR_MemoryList                   allocated_memory_cells = NULL;
     MR_Word                         *old_hp, *new_hp;
-    MR_Stack_Layout_Entry           *entry_layout;
+    MR_Proc_Layout	            *proc_layout;
     MR_Word                         *first_stack_pointer;
     MR_Word                         *first_current_frame,
     MR_Word                         *first_max_frame;
@@ -291,7 +290,7 @@
 #endif
 
     label = MR_lookup_internal_by_addr(success_ip);
-    internal_layout = label->i_layout;
+    label_layout = label->i_layout;
 
 #ifdef MR_DEBUG_AGC_COLLECTION
     first_label = label;
@@ -322,7 +321,7 @@
     do {
         MR_Stack_Walk_Step_Result       result;
         const char                      *problem;
-        const MR_Stack_Layout_Label     *return_label_layout;
+        const MR_Label_Layout           *return_label_layout;
 	int				short_var_count, long_var_count;
 
 #ifdef MR_DEBUG_AGC_COLLECTION
@@ -330,15 +329,14 @@
         fflush(NULL);
 #endif
 
-        vars = &(internal_layout->MR_sll_var_info);
-        short_var_count = MR_short_desc_var_count(vars);
-        long_var_count = MR_long_desc_var_count(vars);
+        short_var_count = MR_short_desc_var_count(label_layout);
+        long_var_count = MR_long_desc_var_count(label_layout);
 
         /* Get the type parameters from the stack frame. */
 
 	/* XXX We must pass NULL since the registers have not been saved */
 	/* XXX This is probably a bug; Tyson should look into it */
-        type_params = MR_materialize_typeinfos_base(vars,
+        type_params = MR_materialize_typeinfos_base(label_layout,
             NULL, stack_pointer, current_frame);
         
         /* Copy each live variable */
@@ -348,8 +346,8 @@
             MR_PseudoTypeInfo pseudo_type_info;
             MR_TypeInfo type_info;
 
-	    locn = MR_long_desc_var_locn(vars, i);
-            pseudo_type_info = MR_var_pti(vars, i);
+	    locn = MR_long_desc_var_locn(label_layout, i);
+            pseudo_type_info = MR_var_pti(label_layout, i);
 
             type_info = MR_make_type_info(type_params, pseudo_type_info,
                 &allocated_memory_cells);
@@ -364,8 +362,8 @@
             MR_PseudoTypeInfo pseudo_type_info;
             MR_TypeInfo type_info;
 
-	    locn = MR_short_desc_var_locn(vars, i);
-            pseudo_type_info = MR_var_pti(vars, i);
+	    locn = MR_short_desc_var_locn(label_layout, i);
+            pseudo_type_info = MR_var_pti(label_layout, i);
 
             type_info = MR_make_type_info(type_params, pseudo_type_info,
                 &allocated_memory_cells);
@@ -377,14 +375,14 @@
 
         MR_free(type_params);
 
-        entry_layout = internal_layout->MR_sll_entry;
+        proc_layout = label_layout->MR_sll_entry;
 
 	{
 		MR_Long_Lval            location;
 		MR_Long_Lval_Type            type;
 		int                     number;
 
-		location = entry_layout->MR_sle_succip_locn;
+		location = proc_layout->MR_sle_succip_locn;
 		type = MR_LONG_LVAL_TYPE(location);
 		number = MR_LONG_LVAL_NUMBER(location);
 		if (type != MR_LONG_LVAL_TYPE_STACKVAR) {
@@ -393,7 +391,7 @@
 		
 		success_ip = (Code *) MR_based_stackvar(stack_pointer, number);
 		stack_pointer = stack_pointer - 
-			entry_layout->MR_sle_stack_slots;
+			proc_layout->MR_sle_stack_slots;
 		label = MR_lookup_internal_by_addr(success_ip);
 	}
 
@@ -401,7 +399,7 @@
 	we should use this code eventually, but it requires a bit of
 	a redesign of the code around here.
  
-        result = MR_stack_walk_step(entry_layout, &internal_layout,
+        result = MR_stack_walk_step(proc_layout, &label_layout,
             (MR_Word **) &stack_pointer, &current_frame, &problem);
 
         if (result == STEP_ERROR_BEFORE || result == STEP_ERROR_AFTER) {
@@ -413,9 +411,9 @@
             break;
         }
 	return_label_layout = label->i_layout;
-        internal_layout = return_label_layout;
+        label_layout = return_label_layout;
         top_frame = FALSE;
-    } while (internal_layout != NULL); /* end for each stack frame... */
+    } while (label_layout != NULL); /* end for each stack frame... */
 
 
     /* 
@@ -453,18 +451,17 @@
 	if (label != NULL) {
 		int short_var_count, long_var_count;
 
-		internal_layout = label->i_layout;
-		short_var_count = MR_short_desc_var_count(vars);
-		long_var_count = MR_long_desc_var_count(vars);
-		/* var_count = internal_layout->MR_sll_var_count; */
-		vars = &(internal_layout->MR_sll_var_info);
+		label_layout = label->i_layout;
+		short_var_count = MR_short_desc_var_count(label_layout);
+		long_var_count = MR_long_desc_var_count(label_layout);
+		/* var_count = label_layout->MR_sll_var_count; */
 
 		/* 
 		** XXX We must pass NULL since the registers have not
 		** been saved This is probably a bug; Tyson should look
 		** into it
 		*/
-		type_params = MR_materialize_typeinfos_base(vars,
+		type_params = MR_materialize_typeinfos_base(label_layout,
 		    NULL, stack_pointer, MR_redofr_slot(max_frame));
         
 		/* Copy each live variable */
@@ -473,8 +470,8 @@
 		    MR_PseudoTypeInfo pseudo_type_info;
 		    MR_TypeInfo type_info;
 
-		    locn = MR_long_desc_var_locn(vars, i);
-		    pseudo_type_info = MR_var_pti(vars, i);
+		    locn = MR_long_desc_var_locn(label_layout, i);
+		    pseudo_type_info = MR_var_pti(label_layout, i);
 
 		    type_info = MR_make_type_info(type_params, pseudo_type_info,
 			&allocated_memory_cells);
@@ -489,8 +486,8 @@
 		    MR_PseudoTypeInfo pseudo_type_info;
 		    MR_TypeInfo type_info;
 
-		    locn = MR_short_desc_var_locn(vars, i);
-		    pseudo_type_info = MR_var_pti(vars, i);
+		    locn = MR_short_desc_var_locn(label_layout, i);
+		    pseudo_type_info = MR_var_pti(label_layout, i);
 
 		    type_info = MR_make_type_info(type_params, pseudo_type_info,
 			&allocated_memory_cells);
Index: runtime/mercury_agc_debug.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_agc_debug.c,v
retrieving revision 1.13
diff -u -b -r1.13 mercury_agc_debug.c
--- runtime/mercury_agc_debug.c	2000/11/23 02:00:21	1.13
+++ runtime/mercury_agc_debug.c	2001/01/02 07:43:09
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -24,7 +24,7 @@
 static	void	dump_short_value(MR_Short_Lval locn, MemoryZone *heap_zone,
 			Word * stack_pointer, Word *current_frame,
 			bool do_regs);
-static  void	dump_live_variables(const MR_Stack_Layout_Label *layout, 
+static  void	dump_live_variables(const MR_Label_Layout *layout, 
 			MemoryZone *heap_zone, bool top_frame,
 			Word *stack_pointer, Word *current_frame);
 
@@ -166,10 +166,9 @@
 #ifdef NATIVE_GC
 	MR_Word saved_regs[MR_MAX_FAKE_REG];
 	int i, short_var_count, long_var_count;
-	const MR_Stack_Layout_Vars *vars;
 	MR_Word *type_params, type_info, value;
-	MR_Stack_Layout_Entry *entry_layout;
-	const MR_Stack_Layout_Label *layout;
+	MR_Proc_Layout *entry_layout;
+	const MR_Label_Layout *layout;
 	const MR_Code *success_ip;
 	bool top_frame = TRUE;
 
@@ -227,21 +226,19 @@
 }
 
 static void
-dump_live_variables(const MR_Stack_Layout_Label *layout, 
+dump_live_variables(const MR_Label_Layout *label_layout, 
 		MemoryZone *heap_zone, bool top_frame,
 		Word *stack_pointer, Word *current_frame)
 {
 	int short_var_count, long_var_count, i;
-	const MR_Stack_Layout_Vars *vars;
 	MR_TypeInfo type_info;
 	MR_Word value;
 	MR_TypeInfoParams type_params;
         MR_Word saved_regs[MR_MAX_FAKE_REG];
         MR_Word *current_regs;
 
-	vars = &(layout->MR_sll_var_info);
-	short_var_count = MR_short_desc_var_count(vars);
-	long_var_count = MR_long_desc_var_count(vars);
+	short_var_count = MR_short_desc_var_count(label_layout);
+	long_var_count = MR_long_desc_var_count(label_layout);
 
 	/*
 	** For the top stack frame, we should pass a pointer to
@@ -256,15 +253,15 @@
 	} else {
 		current_regs = NULL;
 	}
-	type_params = MR_materialize_typeinfos_base(vars,
+	type_params = MR_materialize_typeinfos_base(label_layout,
 		current_regs, stack_pointer, current_frame);
 
 	for (i = 0; i < long_var_count; i++) {
 		fprintf(stderr, "%-12s\t", "");
-		MR_print_proc_id(stderr, layout->MR_sll_entry);
+		MR_print_proc_id(stderr, label_layout->MR_sll_entry);
 
-		dump_long_value(MR_long_desc_var_locn(vars, i), heap_zone,
-			stack_pointer, current_frame, top_frame);
+		dump_long_value(MR_long_desc_var_locn(label_layout, i),
+			heap_zone, stack_pointer, current_frame, top_frame);
 		fprintf(stderr, "\n");
 		fflush(NULL);
 
@@ -276,7 +273,7 @@
 		MR_hp = MR_ENGINE(debug_heap_zone->min);
 		MR_virtual_hp = MR_ENGINE(debug_heap_zone->min);
 
-		if (MR_get_type_and_value_base(vars, i,
+		if (MR_get_type_and_value_base(label_layout, i,
 				current_regs, stack_pointer,
 				current_frame, type_params,
 				&type_info, &value)) {
@@ -292,10 +289,10 @@
 
 	for (; i < short_var_count; i++) {
 		fprintf(stderr, "%-12s\t", "");
-		MR_print_proc_id(stderr, layout->MR_sll_entry);
+		MR_print_proc_id(stderr, label_layout->MR_sll_entry);
 
-		dump_short_value(MR_short_desc_var_locn(vars, i), heap_zone,
-			stack_pointer, current_frame, top_frame);
+		dump_short_value(MR_short_desc_var_locn(label_layout, i),
+			heap_zone, stack_pointer, current_frame, top_frame);
 		fprintf(stderr, "\n");
 		fflush(NULL);
 		
@@ -307,7 +304,7 @@
 		MR_hp = MR_ENGINE(debug_heap_zone->min);
 		MR_virtual_hp = MR_ENGINE(debug_heap_zone->min);
 
-		if (MR_get_type_and_value_base(vars, i,
+		if (MR_get_type_and_value_base(label_layout, i,
 				current_regs, stack_pointer,
 				current_frame, type_params,
 				&type_info, &value)) {
Index: runtime/mercury_goto.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_goto.h,v
retrieving revision 1.27
diff -u -b -r1.27 mercury_goto.h
--- runtime/mercury_goto.h	2000/11/25 13:04:33	1.27
+++ runtime/mercury_goto.h	2001/01/02 07:43:11
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1995-2000 The University of Melbourne.
+** Copyright (C) 1995-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -20,12 +20,10 @@
 #define MR_entry(label) MR_paste(_entry_,label)
 #define MR_skip(label) MR_paste(skip_,label)
 
-#define MR_ENTRY_LAYOUT(label)	  	(const MR_Stack_Layout_Entry *)	\
-					(MR_Word) 			\
-				&(MR_paste(mercury_data__layout__,label))
-#define MR_INTERNAL_LAYOUT(label) 	(const MR_Stack_Layout_Label *)	\
-					(MR_Word)			\
-				&(MR_paste(mercury_data__layout__,label))
+#define MR_ENTRY_LAYOUT(label)	  	(const MR_Proc_Layout *) (MR_Word)\
+				&(MR_paste(mercury_data__proc_layout__,label))
+#define MR_INTERNAL_LAYOUT(label) 	(const MR_Label_Layout *) (MR_Word)\
+				&(MR_paste(mercury_data__label_layout__,label))
 
 /*
 ** Passing the name of a label to MR_insert_{internal,entry}_label
Index: runtime/mercury_ho_call.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_ho_call.h,v
retrieving revision 1.3
diff -u -b -r1.3 mercury_ho_call.h
--- runtime/mercury_ho_call.h	2000/08/03 06:18:46	1.3
+++ runtime/mercury_ho_call.h	2001/01/07 11:27:48
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1999, 2000 The University of Melbourne.
+** Copyright (C) 1999-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -18,7 +18,7 @@
 #ifndef	MERCURY_HO_CALL_H
 #define	MERCURY_HO_CALL_H
 
-#include "mercury_stack_layout.h"
+#include "mercury_stack_layout.h"	/* for MR_Closure_Id etc */
 #include "mercury_type_info.h"		/* for MR_PseudoTypeInfo */
 
 /*
@@ -27,7 +27,7 @@
 ** in any closure that calls that procedure. It is represented as a
 ** vector of words containing
 **
-**	a MR_Stack_Layout_Proc_Id structure
+**	a pointer to an MR_Closure_Id structure
 **	a pointer to information about the locations of typeinfos
 **		for the type parameters of the procedure
 **		(NULL if there are no type parameters)
@@ -63,15 +63,28 @@
 ** will not have any layout information. This will be indicated by the value
 ** of num_all_args being negative, which says that the only field of this
 ** structure containing valid information is proc_id.
+**
+** The Dyn_Link variant is for closures created by browser/dl.m. The closure_id
+** field of such closures will contain an invalid proc_id (which you can tell
+** from the negative arity) and a creation context that is also different from
+** other closures: instead of specifying the source context where the closure
+** is created, it puts a sequence number into the field that normally contains
+** the line number.
 */
 
 typedef struct MR_Closure_Layout_Struct {
-	MR_Stack_Layout_Proc_Id	proc_id;
+	MR_Closure_Id		*closure_id;
 	MR_Type_Param_Locns	*type_params;
 	MR_Integer			num_all_args;
 	MR_PseudoTypeInfo	arg_pseudo_type_info[MR_VARIABLE_SIZED];
 } MR_Closure_Layout;
 
+typedef struct MR_Closure_Dyn_Link_Layout_Struct {
+	MR_Closure_Id		*closure_id;
+	MR_Type_Param_Locns	*type_params;
+	MR_Integer		num_all_args;
+} MR_Closure_Dyn_Link_Layout;
+
 /*
 ** A closure is a vector of words containing:
 **
Index: runtime/mercury_init.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_init.h,v
retrieving revision 1.28
diff -u -b -r1.28 mercury_init.h
--- runtime/mercury_init.h	2000/12/04 18:35:06	1.28
+++ runtime/mercury_init.h	2001/01/02 07:43:20
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1993-2000 The University of Melbourne.
+** Copyright (C) 1993-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -150,10 +150,10 @@
 extern	MR_String	ML_type_name(MR_Word);
 
 /* in runtime/mercury_trace_base.c */
-extern	MR_Code	*MR_trace_fake(const MR_Stack_Layout_Label *);
+extern	MR_Code	*MR_trace_fake(const MR_Label_Layout *);
 
 /* in trace/mercury_trace.c */
-extern	MR_Code	*MR_trace_real(const MR_Stack_Layout_Label *);
+extern	MR_Code	*MR_trace_real(const MR_Label_Layout *);
 extern	void	MR_trace_interrupt_handler(void);
 
 /* in trace/mercury_trace_tables.c */
Index: runtime/mercury_label.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_label.c,v
retrieving revision 1.19
diff -u -b -r1.19 mercury_label.c
--- runtime/mercury_label.c	2000/12/04 18:35:08	1.19
+++ runtime/mercury_label.c	2001/01/02 07:44:22
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1994-2000 The University of Melbourne.
+** Copyright (C) 1994-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -88,7 +88,7 @@
 
 void
 MR_insert_entry_label(const char *name, MR_Code *addr,
-	const MR_Stack_Layout_Entry *entry_layout)
+	const MR_Proc_Layout *entry_layout)
 {
 	MR_do_init_label_tables();
 
@@ -203,7 +203,7 @@
 
 void
 MR_insert_internal_label(const char *name, MR_Code *addr,
-	const MR_Stack_Layout_Label *label_layout)
+	const MR_Label_Layout *label_layout)
 {
 	MR_Internal	*internal;
 
Index: runtime/mercury_label.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_label.h,v
retrieving revision 1.7
diff -u -b -r1.7 mercury_label.h
--- runtime/mercury_label.h	2000/11/23 02:00:32	1.7
+++ runtime/mercury_label.h	2001/01/02 07:44:27
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1994-1998, 2000 The University of Melbourne.
+** Copyright (C) 1994-1998, 2000-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -17,7 +17,7 @@
 
 #include "mercury_types.h"		/* for `MR_Code *' */
 #include "mercury_dlist.h" 		/* for `List' */
-#include "mercury_stack_layout.h"	/* for `MR_Stack_Layout_*' */
+#include "mercury_stack_layout.h"	/* for `MR_Proc_Layout' etc */
 
 #if     defined(NATIVE_GC) || defined(MR_DEBUG_GOTOS)
   #define	MR_NEED_ENTRY_LABEL_ARRAY
@@ -38,7 +38,7 @@
 
 typedef struct s_entry {
 	const MR_Code			*e_addr;
-	const MR_Stack_Layout_Entry	*e_layout;
+	const MR_Proc_Layout	*e_layout;
 	const char			*e_name;
 } MR_Entry;
 
@@ -52,7 +52,7 @@
 
 typedef struct s_internal {
 	const MR_Code			*i_addr;
-	const MR_Stack_Layout_Label	*i_layout;
+	const MR_Label_Layout	*i_layout;
 	const char			*i_name;
 } MR_Internal;
 
@@ -60,7 +60,7 @@
 
 #ifdef	MR_NEED_ENTRY_LABEL_INFO
   extern void		MR_insert_entry_label(const char *name, MR_Code *addr,
-				const MR_Stack_Layout_Entry *entry_layout);
+				const MR_Proc_Layout *entry_layout);
 #else
   #define MR_insert_entry_label(n, a, l)	/* nothing */
 #endif	/* not MR_NEED_ENTRY_LABEL_INFO */
@@ -71,7 +71,7 @@
 
 extern	void		MR_insert_internal_label(const char *name,
 				MR_Code *addr,
-				const MR_Stack_Layout_Label *label_layout);
+				const MR_Label_Layout *label_layout);
 extern	MR_Internal	*MR_lookup_internal_by_addr(const MR_Code *addr);
 extern	void		MR_process_all_internal_labels(void f(const void *));
 
Index: runtime/mercury_layout_util.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_layout_util.c,v
retrieving revision 1.21
diff -u -b -r1.21 mercury_layout_util.c
--- runtime/mercury_layout_util.c	2000/11/23 02:00:32	1.21
+++ runtime/mercury_layout_util.c	2001/01/02 07:44:29
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -64,15 +64,15 @@
 }
 
 MR_TypeInfoParams
-MR_materialize_typeinfos(const MR_Stack_Layout_Vars *vars,
+MR_materialize_typeinfos(const MR_Label_Layout *label_layout,
 	MR_Word *saved_regs)
 {
-	return MR_materialize_typeinfos_base(vars, saved_regs,
+	return MR_materialize_typeinfos_base(label_layout, saved_regs,
 		MR_saved_sp(saved_regs), MR_saved_curfr(saved_regs));
 }
 
 MR_TypeInfoParams
-MR_materialize_typeinfos_base(const MR_Stack_Layout_Vars *vars,
+MR_materialize_typeinfos_base(const MR_Label_Layout *label_layout,
 	MR_Word *saved_regs, MR_Word *base_sp, MR_Word *base_curfr)
 {
 	MR_TypeInfoParams	type_params;
@@ -80,16 +80,18 @@
 	MR_Integer		count;
 	int			i;
 
-	if (vars->MR_slvs_tvars != NULL) {
-		count = vars->MR_slvs_tvars->MR_tp_param_count;
+	if (label_layout->MR_sll_tvars != NULL) {
+		count = label_layout->MR_sll_tvars->MR_tp_param_count;
 		type_params = (MR_TypeInfoParams)
 			MR_NEW_ARRAY(MR_Word, count + 1);
 
 		for (i = 0; i < count; i++) {
-			if (vars->MR_slvs_tvars->MR_tp_param_locns[i] != 0) {
+			if (label_layout->MR_sll_tvars->MR_tp_param_locns[i]
+					!= 0)
+			{
 				type_params[i + 1] = (MR_TypeInfo)
 					MR_lookup_long_lval_base(
-						vars->MR_slvs_tvars->
+						label_layout->MR_sll_tvars->
 							MR_tp_param_locns[i],
 						saved_regs,
 						base_sp, base_curfr,
@@ -343,33 +345,33 @@
 }
 
 bool
-MR_get_type_and_value(const MR_Stack_Layout_Vars *vars, int i,
+MR_get_type_and_value(const MR_Label_Layout *label_layout, int i,
 	MR_Word *saved_regs, MR_TypeInfo *type_params, MR_TypeInfo *type_info,
 	MR_Word *value)
 {
-	return MR_get_type_and_value_base(vars, i, saved_regs,
+	return MR_get_type_and_value_base(label_layout, i, saved_regs,
 		MR_saved_sp(saved_regs), MR_saved_curfr(saved_regs),
 		type_params, type_info, value);
 }
 
 bool
-MR_get_type_and_value_base(const MR_Stack_Layout_Vars *vars, int i,
+MR_get_type_and_value_base(const MR_Label_Layout *label_layout, int i,
 	MR_Word *saved_regs, MR_Word *base_sp, MR_Word *base_curfr,
 	MR_TypeInfo *type_params, MR_TypeInfo *type_info, MR_Word *value)
 {
 	MR_PseudoTypeInfo	pseudo_type_info;
 	bool			succeeded;
 
-	pseudo_type_info = MR_var_pti(vars, i);
+	pseudo_type_info = MR_var_pti(label_layout, i);
 	*type_info = MR_create_type_info(type_params, pseudo_type_info);
 
-	if (i < MR_long_desc_var_count(vars)) {
+	if (i < MR_long_desc_var_count(label_layout)) {
 		*value = MR_lookup_long_lval_base(
-			MR_long_desc_var_locn(vars, i),
+			MR_long_desc_var_locn(label_layout, i),
 			saved_regs, base_sp, base_curfr, &succeeded);
 	} else {
 		*value = MR_lookup_short_lval_base(
-			MR_short_desc_var_locn(vars, i),
+			MR_short_desc_var_locn(label_layout, i),
 			saved_regs, base_sp, base_curfr, &succeeded);
 	}
 
@@ -377,22 +379,22 @@
 }
 
 bool
-MR_get_type(const MR_Stack_Layout_Vars *vars, int i, MR_Word *saved_regs,
+MR_get_type(const MR_Label_Layout *label_layout, int i, MR_Word *saved_regs,
 	MR_TypeInfo *type_params, MR_TypeInfo *type_info)
 {
-	return MR_get_type_base(vars, i, saved_regs,
+	return MR_get_type_base(label_layout, i, saved_regs,
 		MR_saved_sp(saved_regs), MR_saved_curfr(saved_regs),
 		type_params, type_info);
 }
 
 bool
-MR_get_type_base(const MR_Stack_Layout_Vars *vars, int i,
+MR_get_type_base(const MR_Label_Layout *label_layout, int i,
 	MR_Word *saved_regs, MR_Word *base_sp, MR_Word *base_curfr,
 	MR_TypeInfo *type_params, MR_TypeInfo *type_info)
 {
 	MR_PseudoTypeInfo	pseudo_type_info;
 
-	pseudo_type_info = MR_var_pti(vars, i);
+	pseudo_type_info = MR_var_pti(label_layout, i);
 	*type_info = MR_create_type_info(type_params, pseudo_type_info);
 	
 	return TRUE;
Index: runtime/mercury_layout_util.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_layout_util.h,v
retrieving revision 1.13
diff -u -b -r1.13 mercury_layout_util.h
--- runtime/mercury_layout_util.h	2000/11/23 02:00:33	1.13
+++ runtime/mercury_layout_util.h	2001/01/02 07:44:31
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -9,7 +9,7 @@
 
 #include "mercury_std.h"
 #include "mercury_types.h"		/* for MR_Word, etc. */
-#include "mercury_stack_layout.h"	/* for MR_Stack_Layout_Vars, etc. */
+#include "mercury_stack_layout.h"	/* for MR_Label_Layout, etc. */
 #include "mercury_type_info.h"		/* for MR_TypeInfoParams, etc. */
 
 /*
@@ -21,17 +21,17 @@
 extern	void	MR_copy_saved_regs_to_regs(int max_mr_num, MR_Word *saved_regs);
 
 /*
-** A MR_Stack_Layout_Vars describes the variables that are live at a given
+** A MR_Label_Layout describes the variables that are live at a given
 ** program point. Some of the types of these variables may contain type
 ** variables. Since the values of those type variables are not known until
-** runtime, the MR_Stack_Layout_Vars cannot include full typeinfos for the
+** runtime, the MR_Label_Layout cannot include full typeinfos for the
 ** variables. Instead, it contains pseudo-typeinfos, in which some parts
 ** of some typeinfo structures may contain an indication "this data is
 ** not available at compile time, but at runtime it will be in this location".
 **
-** MR_materialize_typeinfos takes as input a MR_Stack_Layout_Vars
-** structure. It returns a vector of typeinfos which has one entry for each
-** pseudo-typeinfo in the MR_Stack_Layout_Vars structure, with this typeinfo
+** MR_materialize_typeinfos takes as input a MR_Label_Layout structure.
+** It returns a vector of typeinfos which has one entry for each
+** pseudo-typeinfo in the MR_Label_Layout structure, with this typeinfo
 ** being the pseudo-typeinfo with the runtime-only information substituted in.
 ** Since type variable numbers start at one, the element of this array at
 ** index zero will not have a type_info in it.  We store a dummy type_ctor_info
@@ -49,10 +49,10 @@
 */ 
 
 extern	MR_TypeInfoParams	MR_materialize_typeinfos(
-					const MR_Stack_Layout_Vars *vars,
+					const MR_Label_Layout *label_layout,
 					MR_Word *saved_regs);
 extern	MR_TypeInfoParams	MR_materialize_typeinfos_base(
-					const MR_Stack_Layout_Vars *vars,
+					const MR_Label_Layout *label_layout,
 					MR_Word *saved_regs,
 					MR_Word *base_sp, MR_Word *base_curfr);
 
@@ -115,18 +115,18 @@
 ** be allocated on the Mercury heap.
 */
 
-extern	bool	MR_get_type_and_value(const MR_Stack_Layout_Vars *vars,
+extern	bool	MR_get_type_and_value(const MR_Label_Layout *label_layout,
 			int var, MR_Word *saved_regs, MR_TypeInfo *type_params,
 			MR_TypeInfo *type_info, MR_Word *value);
-extern	bool	MR_get_type_and_value_base(const MR_Stack_Layout_Vars *vars,
+extern	bool	MR_get_type_and_value_base(const MR_Label_Layout *label_layout,
 			int var, MR_Word *saved_regs,
 			MR_Word *base_sp, MR_Word *base_curfr,
 			MR_TypeInfo *type_params, MR_TypeInfo *type_info,
 			MR_Word *value);
-extern	bool	MR_get_type(const MR_Stack_Layout_Vars *vars, int var,
+extern	bool	MR_get_type(const MR_Label_Layout *label_layout, int var,
 			MR_Word *saved_regs, MR_TypeInfo *type_params,
 			MR_TypeInfo *type_info);
-extern	bool	MR_get_type_base(const MR_Stack_Layout_Vars *vars, int var,
+extern	bool	MR_get_type_base(const MR_Label_Layout *label_layout, int var,
 			MR_Word *saved_regs, MR_Word *base_sp,
 			MR_Word *base_curfr, MR_TypeInfo *type_params,
 			MR_TypeInfo *type_info);
Index: runtime/mercury_stack_layout.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_layout.h,v
retrieving revision 1.45
diff -u -b -r1.45 mercury_stack_layout.h
--- runtime/mercury_stack_layout.h	2000/12/06 06:05:45	1.45
+++ runtime/mercury_stack_layout.h	2001/01/07 09:50:29
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -19,6 +19,10 @@
 #include "mercury_types.h"
 #include "mercury_std.h"			/* for MR_VARIABLE_SIZED */
 
+/* forward declarations */
+typedef	struct MR_Proc_Layout_Struct	MR_Proc_Layout;
+typedef struct MR_Module_Layout_Struct	MR_Module_Layout;
+
 /*-------------------------------------------------------------------------*/
 /*
 ** Definitions for MR_PredFunc. This enum should EXACTLY match the definition
@@ -204,18 +208,97 @@
 
 /*-------------------------------------------------------------------------*/
 /*
-** Definitions for MR_Stack_Layout_Vars
+** Definitions for MR_Label_Layout
 */
 
 /*
-** If MR_slvs_tvars == NULL, there are no type parameters.
-** If it is != NULL, then MR_slvs_tvars->MR_tp_param_count is the number
-** of type parameters, and the element at index i in the array
-** MR_slvs_tvars->MR_tp_param_locns describes the location of the typeinfo
-** structure for type variable i+1 (since array offsets start at zero
-** but type variable numbers start at one). If one of these type variables
-** is not referred to by the variables described in MR_slvs_pairs,
-** the corresponding entry will be zero.
+** An MR_Label_Layout structure describes the debugging and accurate gc
+** information available at a given label.
+**
+** The MR_sll_entry field points to the proc layout structure of the procedure
+** in which the label occurs.
+**
+** The MR_sll_port field will contain a negative number if there is no
+** execution tracing port associated with the label. If there is, the
+** field will contain a value of type MR_Trace_Port. For labels associated
+** with events, this will be the port of the event. For return labels,
+** this port will be exception (since exception events are associated with
+** the return from the call that raised the exception).
+**
+** The MR_sll_goal_path field contains an offset into the module-wide string
+** table, leading to a string that gives the goal path associated with the
+** label. If there is no meaningful goal path associated with the label,
+** the offset will be zero, leading to the empty string.
+**
+** The remaining fields give information about the values live at the given
+** label, if this information is available. If it is available, the
+** MR_has_valid_var_count macro will return true and the last three fields are
+** meaningful; if it is not available, the macro will return false and the last
+** three fields are not meaningful (i.e. you are looking at an
+** MR_Label_Layout_No_Var_Info structure).
+**
+** The format in which we store information about the values live at the label
+** is somewhat complicated, due to our desire to make this information compact.
+** We can represent a location in one of two ways, as an 8-bit MR_Short_Lval
+** or as a 32-bit MR_Long_Lval. We prefer representing a location as an
+** MR_Short_Lval, but of course not all locations can be represented in
+** this way, so those other locations are represented as MR_Long_Lvals.
+**
+** The MR_sll_var_count field, if it is valid, is encoded by the formula
+** (#Long << MR_SHORT_COUNT_BITS + #Short), where #Short is the number
+** data items whose descriptions fit into an MR_Short_Lval and #Long is the
+** number of data items whose descriptions do not. (The number of distinct
+** values that fit into a 8 bits also fits into 8 bits, but since some
+** locations hold the value of more than one variable at a time, not all
+** the values need to be distinct; this is why MR_SHORT_COUNT_BITS is
+** more than 8.)
+**
+** The MR_sll_locns_types field point a memory area that contain three vectors
+** back to back. The first vector has #Long + #Short word-sized elements,
+** each of which is a pointer to a MR_PseudoTypeInfo giving the type of a live
+** data item, with a small integer instead of a pointer representing a special
+** kind of live data item (e.g. a saved succip or hp). The second vector is
+** an array of #Long MR_Long_Lvals, and the third is an array of #Short
+** MR_Short_Lvals, each of which describes a location. The pseudotypeinfo
+** pointed to by the slot at subscript i in the first vector describes
+** the type of the data stored in slot i in the second vector if i < #Long, and
+** the type of the data stored in slot i - #Long in the third vector
+** otherwise.
+**
+** The MR_sll_var_nums field may be NULL, which means that there is no
+** information about the variable numbers of the live values. If the field
+** is not NULL, it points to a vector of variable numbers, which has an element
+** for each live data item. This is either the live data item's HLDS variable
+** number, or one of two special values. Zero means that the live data item
+** is not a variable (e.g. it is a saved copy of succip). The largest possible
+** 16-bit number on the other hand means "the number of this variable does not
+** fit into 16 bits". With the exception of these special values, the value
+** in this slot uniquely identifies the variable.
+**
+** The types of the live variables may or may not have type variables in them.
+** If they do not, the MR_sll_tvars field will be NULL. If they do, it will
+** point to an MR_Type_Param_Locns structure that gives the locations of the
+** typeinfos for those type variables. This structure gives the number of type
+** variables and their locations, so that the code that needs the type
+** parameters can materialize all the type parameters from their location
+** descriptions in one go. This is an optimization, since the type parameter
+** vector could simply be indexed on demand by the type variable's variable
+** number stored within the MR_PseudoTypeInfos stored inside the first vector
+** pointed to by the MR_sll_locns_types field.
+**
+** Since we allocate type variable numbers sequentially, the MR_tp_param_locns
+** vector will usually be dense. However, after all variables whose types
+** include e.g. type variable 2 have gone out of scope, variables whose
+** types include type variable 3 may still be around. In cases like this,
+** the entry for type variable 2 will be zero; this signals to the code
+** in the internal debugger that materializes typeinfo structures that
+** this typeinfo structure need not be materialized. Note that the array
+** element MR_tp_param_locns[i] describes the location of the typeinfo
+** structure for type variable i+1, since array offsets start at zero
+** but type variable numbers start at one.
+**
+** XXX: Presently, inst information is ignored; we assume that all live values
+** are ground.
 */
 
 typedef	struct MR_Type_Param_Locns_Struct {
@@ -223,124 +306,239 @@
 	MR_Long_Lval		MR_tp_param_locns[MR_VARIABLE_SIZED];
 } MR_Type_Param_Locns;
 
-/*
-** This data structure describes the variables live at a given point.
-** The count of live variables is encoded; it gives separately the counts
-** of variables that have short and long location descriptions, or it may
-** say that there is no information about variables at this point (which is
-** very different from saying that there are no variables live at this point).
-** You can decode the count using the macros below.
-**
-** The last three fields are meaningful only if the MR_has_valid_var_count
-** macro returns true.
-**
-** The var nums array pointer may be NULL, in which case no information about
-** variable numbers is available.
-**
-** The type parameters array may also be NULL, but this means that there are
-** no type parameters in the types of the variables live at this point.
-**
-** For further information, see the top of compiler/stack_layout.m.
-*/
-
-typedef	struct MR_Stack_Layout_Vars_Struct {
-	MR_Integer		MR_slvs_var_count;
-	void			*MR_slvs_locns_types;
-	MR_uint_least16_t	*MR_slvs_var_nums;
-	MR_Type_Param_Locns	*MR_slvs_tvars;
-} MR_Stack_Layout_Vars;
+typedef	struct MR_Label_Layout_Struct {
+	const MR_Proc_Layout		*MR_sll_entry;
+	MR_int_least16_t		MR_sll_port;
+	MR_int_least16_t		MR_sll_goal_path;
+	MR_Integer			MR_sll_var_count; /* >= 0 */
+	const void			*MR_sll_locns_types;
+	const MR_uint_least16_t		*MR_sll_var_nums;
+	const MR_Type_Param_Locns	*MR_sll_tvars;
+} MR_Label_Layout;
+
+typedef	struct MR_Label_Layout_No_Var_Info_Struct {
+	const MR_Proc_Layout		*MR_sll_entry;
+	MR_int_least16_t		MR_sll_port;
+	MR_int_least16_t		MR_sll_goal_path;
+	MR_Integer			MR_sll_var_count; /* < 0 */
+} MR_Label_Layout_No_Var_Info;
+
+#define	MR_label_goal_path(layout)					    \
+	((layout)->MR_sll_entry->MR_sle_module_layout->MR_ml_string_table   \
+	+ (layout)->MR_sll_goal_path)
 
 #define	MR_SHORT_COUNT_BITS	10
 #define	MR_SHORT_COUNT_MASK	((1 << MR_SHORT_COUNT_BITS) - 1)
 
-#define	MR_has_valid_var_count(slvs)					    \
-		(((slvs)->MR_slvs_var_count) >= 0)
-#define	MR_has_valid_var_info(slvs)					    \
-		(((slvs)->MR_slvs_var_count) > 0)
-#define	MR_long_desc_var_count(slvs)					    \
-		(((slvs)->MR_slvs_var_count) >> MR_SHORT_COUNT_BITS)
-#define	MR_short_desc_var_count(slvs)					    \
-		(((slvs)->MR_slvs_var_count) & MR_SHORT_COUNT_MASK)
-#define	MR_all_desc_var_count(slvs)					    \
-		(MR_long_desc_var_count(slvs) + MR_short_desc_var_count(slvs))
-
-#define	MR_var_pti(slvs, i)						    \
-		(((MR_PseudoTypeInfo *) ((slvs)->MR_slvs_locns_types))[(i)])
-#define	MR_end_of_var_ptis(slvs)					    \
-		(&MR_var_pti((slvs), MR_all_desc_var_count(slvs)))
-#define	MR_long_desc_var_locn(slvs, i)					    \
-		(((MR_uint_least32_t *) MR_end_of_var_ptis(slvs))[(i)])
-#define	MR_end_of_long_desc_var_locns(slvs)				    \
-		(&MR_long_desc_var_locn((slvs), MR_long_desc_var_count(slvs)))
-#define	MR_short_desc_var_locn(slvs, i)					    \
+#define	MR_has_valid_var_count(sll)					    \
+		(((sll)->MR_sll_var_count) >= 0)
+#define	MR_has_valid_var_info(sll)					    \
+		(((sll)->MR_sll_var_count) > 0)
+#define	MR_long_desc_var_count(sll)					    \
+		(((sll)->MR_sll_var_count) >> MR_SHORT_COUNT_BITS)
+#define	MR_short_desc_var_count(sll)					    \
+		(((sll)->MR_sll_var_count) & MR_SHORT_COUNT_MASK)
+#define	MR_all_desc_var_count(sll)					    \
+		(MR_long_desc_var_count(sll) + MR_short_desc_var_count(sll))
+
+#define	MR_var_pti(sll, i)						    \
+		(((MR_PseudoTypeInfo *) ((sll)->MR_sll_locns_types))[(i)])
+#define	MR_end_of_var_ptis(sll)						    \
+		(&MR_var_pti((sll), MR_all_desc_var_count(sll)))
+#define	MR_long_desc_var_locn(sll, i)					    \
+		(((MR_uint_least32_t *) MR_end_of_var_ptis(sll))[(i)])
+#define	MR_end_of_long_desc_var_locns(sll)				    \
+		(&MR_long_desc_var_locn((sll), MR_long_desc_var_count(sll)))
+#define	MR_short_desc_var_locn(sll, i)					    \
 		(((MR_uint_least8_t *)					    \
-			MR_end_of_long_desc_var_locns(slvs))[(i)])
+			MR_end_of_long_desc_var_locns(sll))[(i)])
 
+/*
+** Define a stack layout for an internal label.
+**
+** The MR_MAKE_INTERNAL_LAYOUT_WITH_ENTRY variant allows you to specify
+** the label name (l) and the entry label name (e) independently, which
+** means that it can be used for labels in code fragments which are
+** simultaneously part of several procedures. (Some hand-written code
+** in the library is like this; the different procedures usually differ
+** only in attributes such as the uniqueness of their arguments.)
+**
+** The MR_MAKE_INTERNAL_LAYOUT variant assumes that the internal label
+** is in the procedure named by the entry label.
+**
+** The only useful information in the structures created by these macros
+** is the reference to the procedure layout, which allows you to find the
+** stack frame size and the succip location, thereby enabling stack tracing.
+**
+** For the native garbage collector, we will need to add meaningful
+** live value information as well to these macros.
+*/ 
+
+#define MR_MAKE_INTERNAL_LAYOUT_WITH_ENTRY(label, entry) \
+	MR_Label_Layout_No_Var_Info mercury_data__label_layout__##label = {\
+		(MR_Proc_Layout *) &mercury_data__proc_layout__##entry,	\
+		-1,							\
+		0,							\
+		-1		/* No info about live values */		\
+	}
+
+#define MR_MAKE_INTERNAL_LAYOUT(entry, labelnum)			\
+	MR_MAKE_INTERNAL_LAYOUT_WITH_ENTRY(entry##_i##labelnum, entry)
+
 /*-------------------------------------------------------------------------*/
 /*
-** Definitions for MR_Stack_Layout_Entry
+** Definitions for MR_Proc_Layout
 */
 
 /*
-** This structure records information about a procedure.
-** The structure has three groups of fields:
+** The MR_Stack_Traversal structure contains the following fields:
 **
-**	(1) those needed for traversing the stack;
-**	(2) those needed for identifying the procedure;
-**	(3) those needed for execution tracing.
+** The code_addr field points to the start of the procedure's code.
+** This allows the profiler to figure out which procedure a sampled program
+** counter belongs to, and allows the debugger to implement retry.
 **
-** For accurate garbage collection, we only need group (1).
-** For stack tracing, we need groups (1) and (2).
-** For execution tracing, we need groups (1), (2) and (3).
+** The succip_locn field encodes the location of the saved succip if it is
+** saved in a general purpose stack slot. If the succip is saved in a special
+** purpose stack slot (as it is for model_non procedures) or if the procedure
+** never saves the succip (as in leaf procedures), this field will contain -1.
 **
-** To save space, for each use we only include the fields that belong
-** to the needed groups, plus the first field in the first non-included group,
-** which is set to a special value to indicate the absence of the group
-** and any following groups.
+** The stack_slots field gives the number of general purpose stack slots
+** in the procedure.
 **
-** Group (1) is always present and meaningful.
-** Group (2) is present and meaningful
-** if MR_ENTRY_LAYOUT_HAS_PROC_ID(entry) evaluates to true.
-** Group (3) is present and meaningful
-** if MR_ENTRY_LAYOUT_HAS_EXEC_TRACE(entry) evaluates to true.
-**
-** Group (2) fields have a different interpretation if the procedure is
-** compiler-generated. You can test whether this is the case by using the macro
-** MR_ENTRY_LAYOUT_COMPILER_GENERATED, but only after checking that
-** MR_ENTRY_LAYOUT_HAS_PROC_ID is true.
-**
-** For further details on the semantics of the fields, see stack_layout.m.
+** The detism field encodes the determinism of the procedure.
 */
 
+typedef struct MR_Stack_Traversal_Struct {
+	MR_Code			*MR_trav_code_addr;
+	MR_Long_Lval		MR_trav_succip_locn;
+	MR_int_least16_t	MR_trav_stack_slots;
+	MR_Determinism		MR_trav_detism;
+} MR_Stack_Traversal;
+
 /*
+** MR_Proc_Id is a union. The usual alternative identifies ordinary
+** procedures, while the other alternative identifies automatically generated
+** unification, comparison and index procedures. The meanings of the fields
+** in both forms are the same as in procedure labels. The runtime system
+** can figure out which form is present by using the macro
+** MR_ENTRY_LAYOUT_COMPILER_GENERATED, which will return true only if
+** the procedure is of the second type.
+**
+** The compiler generates MR_User_Proc_Id and MR_Compiler_Proc_Id structures
+** in order to avoid having to initialize the MR_Proc_Id union through the
+** inapplicable alternative.
+**
 ** The places that know about the structure of procedure ids include
-** browser/dl.m and of course compiler/stack_layout, besides all the places 
-** that refer to the C types we now define.
+** browser/dl.m and besides all the places that refer to the C types below.
 */
 
-typedef struct MR_Stack_Layout_User_Proc_Struct {
+typedef struct MR_User_Proc_Id_Struct {
 	MR_PredFunc		MR_user_pred_or_func;
 	MR_ConstString		MR_user_decl_module;
 	MR_ConstString		MR_user_def_module;
 	MR_ConstString		MR_user_name;
 	MR_int_least16_t	MR_user_arity;
 	MR_int_least16_t	MR_user_mode;
-} MR_Stack_Layout_User_Proc;
+} MR_User_Proc_Id;
 
-typedef struct MR_Stack_Layout_Compiler_Proc_Struct {
+typedef struct MR_Compiler_Proc_Id_Struct {
 	MR_ConstString		MR_comp_type_name;
 	MR_ConstString		MR_comp_type_module;
 	MR_ConstString		MR_comp_def_module;
 	MR_ConstString		MR_comp_pred_name;
 	MR_int_least16_t	MR_comp_arity;
 	MR_int_least16_t	MR_comp_mode;
-} MR_Stack_Layout_Compiler_Proc;
+} MR_Compiler_Proc_Id;
 
-typedef union MR_Stack_Layout_Proc_Id_Union {
-	MR_Stack_Layout_User_Proc	MR_proc_user;
-	MR_Stack_Layout_Compiler_Proc	MR_proc_comp;
-} MR_Stack_Layout_Proc_Id;
+typedef union MR_Proc_Id_Union {
+	MR_User_Proc_Id		MR_proc_user;
+	MR_Compiler_Proc_Id	MR_proc_comp;
+} MR_Proc_Id;
 
+#define	MR_ENTRY_LAYOUT_COMPILER_GENERATED(entry)		\
+		((MR_Unsigned) entry->MR_sle_user.MR_user_pred_or_func \
+		> MR_FUNCTION)
+
+/*
+** The MR_Exec_Trace structure contains the following fields.
+**
+** The call_label field points to the label layout structure for the label
+** associated with the call event at the entry to the procedure. The purpose
+** of this field is to allow the debugger to find out which variables
+** are where on entry, so it can reexecute the procedure if asked to do so
+** and if the values of the required variables are still available.
+**
+** The module_layout field points to the module info structure of the module
+** containing the procedure. This allows the debugger access to the string table
+** stored there, as well the table associating source-file contexts with labels.
+**
+** The proc_rep field contains a representation of the body of the procedure
+** as a Mercury term of type goal_rep, defined in program_representation.m.
+** If will be 0 if no such representation is available.
+**
+** The used_var_names field points to an array that contains offsets
+** into the string table, with the offset at index i-1 giving the name of
+** variable i (since variable numbers start at one). If a variable has no name
+** or cannot be referred to from an event, the offset will be zero, at which
+** offset the string table will contain an empty string. The string table
+** is restricted to be small enough to be addressed with 16 bits;
+** a string is reserved near the start for a string that says "too many
+** variables". Stack_layout.m will generate a reference to this string
+** instead of generating an offset that does not fit into 16 bits.
+** Therefore using the stored offset to index into the string table
+** is always safe.
+**
+** The max_var_num field gives the number of elements in the used_var_names
+** table.
+**
+** The max_r_num field tells the debugger which Mercury abstract machine
+** registers need saving in MR_trace: besides the special registers, it is
+** the general-purpose registers rN for values of N up to and including the
+** value of this field. Note that this field contains an upper bound; in
+** general, there will be calls to MR_trace at which the number of the highest
+** numbered general purpose (i.e. rN) registers is less than this. However,
+** storing the upper bound gets us almost all the benefit (of not saving and
+** restoring all the thousand rN registers) for a small fraction of the static
+** space cost of storing the actual number in label layout structures.
+**
+** If the procedure is compiled with deep tracing, the maybe_from_full field
+** will contain a negative number. If it is compiled with shallow tracing,
+** it will contain the number of the stack slot that holds the flag that says
+** whether this incarnation of the procedure was called from deeply traced code
+** or not. (The determinism of the procedure decides whether the stack slot
+** refers to a stackvar or a framevar.)
+**
+** If the procedure has an I/O state argument, the maybe_io_seq field will
+** contain the number of the stack slot that holds the value the I/O action
+** counter had on entry to this procedure.
+**
+** If trailing is not enabled, the maybe_trail field will contain a negative
+** number. If it is enabled, it will contain number of the first of two stack
+** slots used for checkpointing the state of the trail on entry to the
+** procedure. The first contains the trail pointer, the second the ticket.
+**
+** If the procedure lives on the nondet stack, or if it cannot create any
+** temporary nondet stack frames, the maybe_maxfr field will contain a negative
+** number. If it lives on the det stack, and can create temporary nondet stack
+** frames, it will contain the number number of the stack slot that contains the
+** value of maxfr on entry, for use in executing the retry debugger command
+** from the middle of the procedure.
+**
+** The eval_method field contains a representation of the evaluation method
+** used by the procedure. The retry command needs this information if it is
+** to reset the call tables of the procedure invocations being retried.
+**
+** We cannot put enums into structures as bit fields. To avoid wasting space,
+** we put MR_EvalMethodInts into structures instead of MR_EvalMethods
+** themselves.
+**
+** If --trace-decl is not set, the maybe_decl field will contain a negative
+** number. If it is set, it will contain the number of the first of two stack
+** slots used by the declarative debugger; the other slot is the next higher
+** numbered one. (The determinism of the procedure decides whether the stack
+** slot refers to a stackvar or a framevar.)
+*/
+
 typedef	enum {
 	MR_EVAL_METHOD_NORMAL,
 	MR_EVAL_METHOD_LOOP_CHECK,
@@ -349,47 +547,107 @@
 	MR_EVAL_METHOD_TABLE_IO
 } MR_EvalMethod;
 
-/*
-** We cannot put enums into structures as bit fields. To avoid wasting space,
-** we put MR_EvalMethodInts into structures instead of MR_EvalMethods
-** themselves.
-*/
-
 typedef	MR_int_least8_t		MR_EvalMethodInt;
-
-typedef	struct MR_Stack_Layout_Entry_Struct {
-	/* stack traversal group */
-	MR_Code			*MR_sle_code_addr;
-	MR_Long_Lval		MR_sle_succip_locn;
-	MR_int_least16_t	MR_sle_stack_slots;
-	MR_Determinism		MR_sle_detism;
-
-	/* proc id group */
-	MR_Stack_Layout_Proc_Id	MR_sle_proc_id;
-
-	/* exec trace group */
-	struct MR_Stack_Layout_Label_Struct
-				*MR_sle_call_label;
-	struct MR_Module_Layout_Struct
-				*MR_sle_module_layout;
-	MR_Word			MR_sle_proc_rep;
-	MR_int_least16_t	*MR_sle_used_var_names;
-	MR_int_least16_t	MR_sle_max_var_num;
-	MR_int_least16_t	MR_sle_max_r_num;
-	MR_int_least8_t		MR_sle_maybe_from_full;
-	MR_int_least8_t		MR_sle_maybe_io_seq;
-	MR_int_least8_t		MR_sle_maybe_trail;
-	MR_int_least8_t		MR_sle_maybe_maxfr;
-	MR_EvalMethodInt	MR_sle_eval_method_CAST_ME;
-	MR_int_least8_t		MR_sle_maybe_call_table;
-	MR_int_least8_t		MR_sle_maybe_decl_debug;
-} MR_Stack_Layout_Entry;
 
-#define	MR_sle_eval_method(entry)				\
-			((MR_EvalMethod) (entry)->MR_sle_eval_method_CAST_ME)
+typedef	struct MR_Exec_Trace_Struct {
+	const MR_Label_Layout	*MR_exec_call_label;
+	const MR_Module_Layout	*MR_exec_module_layout;
+	MR_Word			MR_exec_proc_rep;
+	const MR_int_least16_t	*MR_exec_used_var_names;
+	MR_int_least16_t	MR_exec_max_var_num;
+	MR_int_least16_t	MR_exec_max_r_num;
+	MR_int_least8_t		MR_exec_maybe_from_full;
+	MR_int_least8_t		MR_exec_maybe_io_seq;
+	MR_int_least8_t		MR_exec_maybe_trail;
+	MR_int_least8_t		MR_exec_maybe_maxfr;
+	MR_EvalMethodInt	MR_exec_eval_method_CAST_ME;
+	MR_int_least8_t		MR_exec_maybe_call_table;
+	MR_int_least8_t		MR_exec_maybe_decl_debug;
+} MR_Exec_Trace;
 
-#define	MR_sle_user	MR_sle_proc_id.MR_proc_user
-#define	MR_sle_comp	MR_sle_proc_id.MR_proc_comp
+/*-------------------------------------------------------------------------*/
+/*
+** Definitions for MR_Proc_Layout
+**
+** Proc layout structures contain one, two or three substructures.
+**
+** - The first substructure is the MR_Stack_Traversal structure, which contains
+**   information that enables the stack to be traversed, e.g. for accurate gc.
+**   It is always present if proc layouts are present at all.
+**
+** - The second group is the MR_Proc_Id union, which identifies the
+**   procedure in terms that are meaningful to both humans and machines.
+**   It will be generated only if the module is compiled with stack tracing,
+**   execution tracing or profiling. The MR_Proc_Id union has two alternatives,
+**   one for user-defined procedures and one for procedures of the compiler
+**   generated Unify, Index and Compare predicates.
+**
+** - The third group is the MR_Exec_Trace structure, which contains
+**   information specifically intended for the debugger. It will be generated
+**   only if the module is compiled with execution tracing.
+**
+** The runtime system considers all proc layout structures to be of type
+** MR_Proc_Layout, but must use the macros defined below to check for the 
+** existence of each substructure before accessing the fields of that
+** substructure. The macros are MR_ENTRY_LAYOUT_HAS_PROC_ID to check for the
+** MR_Proc_Id substructure and MR_ENTRY_LAYOUT_HAS_EXEC_TRACE to check for the
+** MR_Exec_Trace substructure.
+**
+** The reason why some substructures may be missing is to save space.
+** If the options with which a module is compiled do not require execution
+** tracing, then the MR_Exec_Trace substructure will not present, and if the
+** options do not require procedure identification, then the MR_Proc_Id
+** substructure will not be present either
+**
+** The compiler itself generates proc layout structures using the following
+** five types.
+**
+** - When generating only stack traversal information, the compiler will
+**   generate proc layout structures of type MR_Proc_Layout_Traversal.
+**
+** - When generating only stack traversal and procedure id information, the
+**   compiler will generate proc layout structures of types MR_Proc_Layout_User
+**   and MR_Proc_Layout_Compiler.
+**
+** - When generating all three groups of information, the compiler will
+**   generate proc layout structures of types MR_Proc_Layout_User_Exec
+**   and MR_Proc_Layout_Compiler_Exec.
+*/
+
+struct MR_Proc_Layout_Struct {
+	MR_Stack_Traversal	MR_sle_traversal;
+	MR_Proc_Id		MR_sle_proc_id;
+	MR_Exec_Trace		MR_sle_exec_trace;
+};
+
+typedef	struct MR_Proc_Layout_Traversal_Struct {
+	MR_Stack_Traversal	MR_trav_traversal;
+	MR_Word			MR_trav_no_proc_id;	/* will be -1 */
+} MR_Proc_Layout_Traversal;
+
+typedef	struct MR_Proc_Layout_User_Struct {
+	MR_Stack_Traversal	MR_user_traversal;
+	MR_User_Proc_Id		MR_user_id;
+	MR_Word			MR_user_no_exec_trace;	/* will be NULL */
+} MR_Proc_Layout_User;
+
+typedef	struct MR_Proc_Layout_Compiler_Struct {
+	MR_Stack_Traversal	MR_comp_traversal;
+	MR_Compiler_Proc_Id	MR_comp_id;
+	MR_Word			MR_comp_no_exec_trace;	/* will be NULL */
+} MR_Proc_Layout_Compiler;
+
+typedef	struct MR_Proc_Layout_User_Exec_Struct {
+	MR_Stack_Traversal	MR_user_exec_traversal;
+	MR_User_Proc_Id		MR_user_exec_id;
+	MR_Exec_Trace		MR_user_exec_trace;
+} MR_Proc_Layout_User_Exec;
+
+typedef	struct MR_Proc_Layout_Compiler_Exec_Struct {
+	MR_Stack_Traversal	MR_comp_exec_traversal;
+	MR_Compiler_Proc_Id	MR_comp_exec_id;
+	MR_Exec_Trace		MR_comp_exec_trace;
+} MR_Proc_Layout_Compiler_Exec;
 
 #define	MR_ENTRY_LAYOUT_HAS_PROC_ID(entry)			\
 		((MR_Word) entry->MR_sle_user.MR_user_pred_or_func != -1)
@@ -398,13 +656,34 @@
 		(MR_ENTRY_LAYOUT_HAS_PROC_ID(entry)		\
 		&& entry->MR_sle_call_label != NULL)
 
-#define	MR_ENTRY_LAYOUT_COMPILER_GENERATED(entry)		\
-		((MR_Unsigned) entry->MR_sle_user.MR_user_pred_or_func \
-		> MR_FUNCTION)
+#define	MR_sle_code_addr	MR_sle_traversal.MR_trav_code_addr
+#define	MR_sle_succip_locn	MR_sle_traversal.MR_trav_succip_locn
+#define	MR_sle_stack_slots	MR_sle_traversal.MR_trav_stack_slots
+#define	MR_sle_detism		MR_sle_traversal.MR_trav_detism
+
+#define	MR_sle_user		MR_sle_proc_id.MR_proc_user
+#define	MR_sle_comp		MR_sle_proc_id.MR_proc_comp
 
+#define	MR_sle_call_label	MR_sle_exec_trace.MR_exec_call_label
+#define	MR_sle_module_layout	MR_sle_exec_trace.MR_exec_module_layout
+#define	MR_sle_proc_rep	MR_sle_exec_trace.MR_exec_proc_rep
+#define	MR_sle_used_var_names	MR_sle_exec_trace.MR_exec_used_var_names
+#define	MR_sle_max_var_num	MR_sle_exec_trace.MR_exec_max_var_num
+#define	MR_sle_max_r_num	MR_sle_exec_trace.MR_exec_max_r_num
+#define	MR_sle_maybe_from_full	MR_sle_exec_trace.MR_exec_maybe_from_full
+#define	MR_sle_maybe_io_seq	MR_sle_exec_trace.MR_exec_maybe_io_seq
+#define	MR_sle_maybe_trail	MR_sle_exec_trace.MR_exec_maybe_trail
+#define	MR_sle_maybe_maxfr	MR_sle_exec_trace.MR_exec_maybe_maxfr
+#define	MR_sle_maybe_call_table MR_sle_exec_trace.MR_exec_maybe_call_table
+#define	MR_sle_maybe_decl_debug MR_sle_exec_trace.MR_exec_maybe_decl_debug
+
+#define	MR_sle_eval_method(proc_layout_ptr)				\
+			((MR_EvalMethod) (proc_layout_ptr)->		\
+				MR_sle_exec_trace.MR_exec_eval_method_CAST_ME)
+
 /*
 ** Define a layout structure for a procedure, containing information
-** for the first two groups of fields.
+** for the first two substructures.
 **
 ** The slot count and the succip location parameters do not have to be
 ** supplied for procedures that live on the nondet stack, since for such
@@ -422,8 +701,8 @@
 ** the MR_MAKE_PROC_LAYOUT macro has to be accompanied by a call to the
 ** MR_INIT_PROC_LAYOUT_ADDR macro in the initialization code of the C module
 ** that defines the entry. (The cast in the body of MR_INIT_PROC_LAYOUT_ADDR
-** is needed because compiler-generated layout structures have their own
-** compiler-generated type.)
+** is needed because compiler-generated layout structures may use any of the
+** five variant types listed above.)
 */ 
 
 #define	MR_ENTRY_NO_SLOT_COUNT		-1
@@ -435,28 +714,30 @@
  #define	MR_MAKE_PROC_LAYOUT_ADDR(entry)		((MR_Code *) NULL)
  #define	MR_INIT_PROC_LAYOUT_ADDR(entry)				\
 		do {							\
-			((MR_Stack_Layout_Entry *) &			\
-			mercury_data__layout__##entry)			\
+			((MR_Proc_Layout *) &				\
+			mercury_data__proc_layout__##entry)		\
 				->MR_sle_code_addr = MR_ENTRY(entry);	\
 		} while (0)
 #endif
 
 #define MR_MAKE_PROC_LAYOUT(entry, detism, slots, succip_locn,		\
 		pf, module, name, arity, mode) 				\
-	MR_Stack_Layout_Entry mercury_data__layout__##entry = {		\
+	MR_Proc_Layout_User mercury_data__proc_layout__##entry = {	\
+		{							\
 		MR_MAKE_PROC_LAYOUT_ADDR(entry),			\
 		succip_locn,						\
 		slots,							\
-		detism,							\
-		{{							\
+			detism						\
+		},							\
+		{							\
 			pf,						\
 			module,						\
 			module,						\
 			name,						\
 			arity,						\
 			mode						\
-		}},							\
-		NULL							\
+		},							\
+		0							\
 	}
 
 /*
@@ -505,88 +786,40 @@
 #define MR_redo_layout_framevar(base_curfr)   MR_based_framevar(base_curfr, 4)
 #define MR_redo_fromfull_framevar(base_curfr) MR_based_framevar(base_curfr, 5)
 
-/*-------------------------------------------------------------------------*/
-/*
-** Definitions for MR_Stack_Layout_Label
-*/
-
-typedef	struct MR_Stack_Layout_Label_Struct {
-	MR_Stack_Layout_Entry	*MR_sll_entry;
-	MR_int_least16_t	MR_sll_port;
-	MR_int_least16_t	MR_sll_goal_path;
-	MR_Stack_Layout_Vars	MR_sll_var_info;
-} MR_Stack_Layout_Label;
-
-#define	MR_label_goal_path(layout)					\
-	((layout)->MR_sll_entry->MR_sle_module_layout->MR_ml_string_table\
-	+ (layout)->MR_sll_goal_path)
 
-/*
-** Define a stack layout for an internal label.
-**
-** The MR_MAKE_INTERNAL_LAYOUT_WITH_ENTRY variant allows you to specify
-** the label name (l) and the entry label name (e) independently, which
-** means that it can be used for labels in code fragments which are
-** simultaneously part of several procedures. (Some hand-written code
-** in the library is like this; the different procedures usually differ
-** only in attributes such as the uniqueness of their arguments.)
-**
-** The MR_MAKE_INTERNAL_LAYOUT variant assumes that the internal label
-** is in the procedure named by the entry label.
-**
-** The only useful information in the structures created by these macros
-** is the reference to the procedure layout, which allows you to find the
-** stack frame size and the succip location, thereby enabling stack tracing.
-**
-** For the native garbage collector, we will need to add meaningful
-** live value information as well to these macros.
-*/ 
-
-#define MR_MAKE_INTERNAL_LAYOUT_WITH_ENTRY(label, entry) \
-	MR_Stack_Layout_Label mercury_data__layout__##label = {		\
-		&mercury_data__layout__##entry,				\
-		-1,							\
-		-1,							\
-		{							\
-			-1,		/* No info about live values */	\
-			NULL,						\
-			NULL,						\
-			NULL						\
-		}							\
-	}
-
-#define MR_MAKE_INTERNAL_LAYOUT(entry, labelnum)			\
-	MR_MAKE_INTERNAL_LAYOUT_WITH_ENTRY(entry##_i##labelnum, entry)
-
 /*-------------------------------------------------------------------------*/
 /*
 ** Definitions for MR_Module_Layout
 **
-** The layout struct for a module contains three main components.
+** The layout structure for a module contains the following fields.
 **
-** The first is a string table, which contains strings referred to by other
-** layout structures in the module (initially only the tables containing
-** variables names, referred to from label layout structures).
-**
-** The second is a table containing pointers to the proc layout structures
-** of all the procedures in the module.
-**
-** The third component contains N tables if the module has labels corresponding
-** to contexts that refer to N filenames. For each filename, the table gives
-** the name of the file and the number of labels in that file in this module;
-** for each such label it gives its line number and its label layout struct.
+** The MR_ml_name field contains the name of the module.
 **
+** The MR_ml_string_table field contains the module's string table, which
+** contains strings referred to by other layout structures in the module
+** (initially only the tables containing variables names, referred to from
+** label layout structures). The MR_ml_string_table_size field gives the size
+** of the table in bytes.
+**
+** The MR_ml_procs field points to an array containing pointers to the proc
+** layout structures of all the procedures in the module; the MR_ml_proc_count
+** field gives the number of entries in the array.
+**
+** The MR_ml_module_file_layout field points to an array of N file layout
+** pointers if the module has labels corresponding to contexts that refer
+** to the names of N files. For each file, the table gives its name, the
+** number of labels in that file in this module, and for each such label,
+** it gives its line number and a pointer to its label layout struct.
 ** The corresponding elements of the label_lineno and label_layout arrays
 ** refer to the same label. (The reason why they are not stored together
 ** is space efficiency; adding a 16 bit field to a label layout structure would
 ** require padding.) The labels are sorted on line number.
+**
+** The MR_ml_trace_level field gives the trace level that the module was
+** compiled with.  If the MR_Trace_Level enum is modified, then the
+** corresponding function in compiler/trace_params.m must also be updated.
 */
 
-/*
-** The trace level that the module was compiled with.  If this enum is
-** modified, then the corresponding function in compiler/trace_params.m
-** must be updated.
-*/
 typedef enum {
 	MR_TRACE_LEVEL_NONE,
 	MR_TRACE_LEVEL_SHALLOW,
@@ -596,22 +829,59 @@
 } MR_Trace_Level;
 
 typedef struct MR_Module_File_Layout_Struct {
-	MR_String		MR_mfl_filename;
+	MR_ConstString			MR_mfl_filename;
 	MR_Integer		MR_mfl_label_count;
 	/* the following fields point to arrays of size MR_mfl_label_count */
-	MR_int_least16_t	*MR_mfl_label_lineno;
-	MR_Stack_Layout_Label	**MR_mfl_label_layout;
+	const MR_int_least16_t		*MR_mfl_label_lineno;
+	const MR_Label_Layout		**MR_mfl_label_layout;
 } MR_Module_File_Layout;
 
-typedef	struct MR_Module_Layout_Struct {
-	MR_String		MR_ml_name;
+struct MR_Module_Layout_Struct {
+	MR_ConstString			MR_ml_name;
 	MR_Integer		MR_ml_string_table_size;
-	char			*MR_ml_string_table;
+	const char			*MR_ml_string_table;
 	MR_Integer		MR_ml_proc_count;
-	MR_Stack_Layout_Entry	**MR_ml_procs;
+	const MR_Proc_Layout		**MR_ml_procs;
 	MR_Integer		MR_ml_filename_count;
-	MR_Module_File_Layout	**MR_ml_module_file_layout;
+	const MR_Module_File_Layout	**MR_ml_module_file_layout;
 	MR_Trace_Level		MR_ml_trace_level;
-} MR_Module_Layout;
+};
+
+/*-------------------------------------------------------------------------*/
+/*
+** Definitions for MR_Closure_Id
+**
+** Each closure contains an MR_Closure_Id structure. The proc_id field
+** identifies the procedure called by the closure. The other fields identify
+** the context where the closure was created.
+**
+** The compiler generates closure id structures as either MR_User_Closure_Id
+** or MR_Compiler_Closure_Id structures in order to avoid initializing the
+** MR_Proc_Id union through an inappropriate member.
+*/
+
+typedef struct MR_Closure_Id_Struct {
+	MR_Proc_Id		proc_id;
+	MR_ConstString		module_name;
+	MR_ConstString		file_name;
+	MR_Integer		line_number;
+	MR_ConstString		goal_path;
+} MR_Closure_Id;
+
+typedef struct MR_User_Closure_Id_Struct {
+	MR_User_Proc_Id		proc_id;
+	MR_ConstString		module_name;
+	MR_ConstString		file_name;
+	MR_Integer		line_number;
+	MR_ConstString		goal_path;
+} MR_User_Closure_Id;
+
+typedef struct MR_Compiler_Closure_Id_Struct {
+	MR_Compiler_Proc_Id	proc_id;
+	MR_ConstString		module_name;
+	MR_ConstString		file_name;
+	MR_Integer		line_number;
+	MR_ConstString		goal_path;
+} MR_Compiler_Closure_Id;
 
 #endif /* not MERCURY_STACK_LAYOUT_H */
Index: runtime/mercury_stack_trace.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_trace.c,v
retrieving revision 1.40
diff -u -b -r1.40 mercury_stack_trace.c
--- runtime/mercury_stack_trace.c	2000/11/28 04:31:45	1.40
+++ runtime/mercury_stack_trace.c	2001/01/02 07:44:36
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -18,14 +18,14 @@
 static	void	MR_dump_stack_record_init(bool include_trace_data,
 			bool include_contexts);
 static	void	MR_dump_stack_record_frame(FILE *fp,
-			const MR_Stack_Layout_Label *label_layout,
+			const MR_Label_Layout *label_layout,
 			MR_Word *base_sp, MR_Word *base_curfr, 
 			MR_Print_Stack_Record print_stack_record);
 static	void	MR_dump_stack_record_flush(FILE *fp, 
 			MR_Print_Stack_Record print_stack_record);
 
 static	void	MR_print_proc_id_internal(FILE *fp,
-			const MR_Stack_Layout_Entry *entry, bool spec);
+			const MR_Proc_Layout *entry, bool spec);
 
 static	void	MR_maybe_print_context(FILE *fp,
 			const char *filename, int lineno);
@@ -45,7 +45,7 @@
 #else
 
 	const MR_Internal		*label;
-	const MR_Stack_Layout_Label	*layout;
+	const MR_Label_Layout	*layout;
 	const char			*result;
 
 	fprintf(stderr, "Stack dump follows:\n");
@@ -68,15 +68,15 @@
 }
 
 const char *
-MR_dump_stack_from_layout(FILE *fp, const MR_Stack_Layout_Label *label_layout,
+MR_dump_stack_from_layout(FILE *fp, const MR_Label_Layout *label_layout,
 	MR_Word *det_stack_pointer, MR_Word *current_frame,
 	bool include_trace_data, bool include_contexts,
 	MR_Print_Stack_Record print_stack_record)
 {
 	MR_Stack_Walk_Step_Result	result;
-	const MR_Stack_Layout_Entry	*entry_layout;
-	const MR_Stack_Layout_Label	*cur_label_layout;
-	const MR_Stack_Layout_Label	*prev_label_layout;
+	const MR_Proc_Layout		*entry_layout;
+	const MR_Label_Layout		*cur_label_layout;
+	const MR_Label_Layout		*prev_label_layout;
 	const char			*problem;
 	MR_Word				*stack_trace_sp;
 	MR_Word				*stack_trace_curfr;
@@ -121,13 +121,13 @@
 	return NULL;
 }
 
-const MR_Stack_Layout_Label *
-MR_find_nth_ancestor(const MR_Stack_Layout_Label *label_layout,
-	int ancestor_level, MR_Word **stack_trace_sp, MR_Word **stack_trace_curfr,
+const MR_Label_Layout *
+MR_find_nth_ancestor(const MR_Label_Layout *label_layout, int ancestor_level,
+	MR_Word **stack_trace_sp, MR_Word **stack_trace_curfr,
 	const char **problem)
 {
 	MR_Stack_Walk_Step_Result	result;
-	const MR_Stack_Layout_Label	*return_label_layout;
+	const MR_Label_Layout		*return_label_layout;
 	int				i;
 
 	if (ancestor_level < 0) {
@@ -158,8 +158,8 @@
 }
 
 MR_Stack_Walk_Step_Result
-MR_stack_walk_step(const MR_Stack_Layout_Entry *entry_layout,
-	const MR_Stack_Layout_Label **return_label_layout,
+MR_stack_walk_step(const MR_Proc_Layout *entry_layout,
+	const MR_Label_Layout **return_label_layout,
 	MR_Word **stack_trace_sp_ptr, MR_Word **stack_trace_curfr_ptr,
 	const char **problem_ptr)
 {
@@ -277,7 +277,7 @@
 	}
 }
 
-static	const MR_Stack_Layout_Entry	*prev_entry_layout;
+static	const MR_Proc_Layout	*prev_entry_layout;
 static	int				prev_entry_layout_count;
 static	int				prev_entry_start_level;
 static	MR_Word				*prev_entry_base_sp;
@@ -302,11 +302,11 @@
 }
 
 static void
-MR_dump_stack_record_frame(FILE *fp, const MR_Stack_Layout_Label *label_layout,
+MR_dump_stack_record_frame(FILE *fp, const MR_Label_Layout *label_layout,
 	MR_Word *base_sp, MR_Word *base_curfr,
 	MR_Print_Stack_Record print_stack_record)
 {
-	const MR_Stack_Layout_Entry	*entry_layout;
+	const MR_Proc_Layout	*entry_layout;
 	const char			*filename;
 	int				linenumber;
 	bool				must_flush;
@@ -376,7 +376,7 @@
 }
 
 void
-MR_dump_stack_record_print(FILE *fp, const MR_Stack_Layout_Entry *entry_layout,
+MR_dump_stack_record_print(FILE *fp, const MR_Proc_Layout *entry_layout,
 	int count, int start_level, MR_Word *base_sp, MR_Word *base_curfr,
 	const char *filename, int linenumber, const char *goal_path,
 	bool context_mismatch)
@@ -415,10 +415,10 @@
 }
 
 bool
-MR_find_context(const MR_Stack_Layout_Label *label, const char **fileptr,
+MR_find_context(const MR_Label_Layout *label, const char **fileptr,
 	int *lineptr)
 {
-	const MR_Stack_Layout_Entry	*proc;
+	const MR_Proc_Layout		*proc;
 	const MR_Module_Layout		*module;
 	const MR_Module_File_Layout	*file_layout;
 	int				i, j;
@@ -445,8 +445,7 @@
 
 void
 MR_maybe_print_call_trace_info(FILE *fp, bool include_trace_data,
-	const MR_Stack_Layout_Entry *entry,
-	MR_Word *base_sp, MR_Word *base_curfr)
+	const MR_Proc_Layout *entry, MR_Word *base_sp, MR_Word *base_curfr)
 {
 	if (include_trace_data) {
 		MR_print_call_trace_info(fp, entry, base_sp, base_curfr);
@@ -459,7 +458,7 @@
 */
 
 void
-MR_print_call_trace_info(FILE *fp, const MR_Stack_Layout_Entry *entry,
+MR_print_call_trace_info(FILE *fp, const MR_Proc_Layout *entry,
 	MR_Word *base_sp, MR_Word *base_curfr)
 {
 	bool	print_details;
@@ -521,19 +520,19 @@
 }
 
 void
-MR_print_proc_id(FILE *fp, const MR_Stack_Layout_Entry *entry)
+MR_print_proc_id(FILE *fp, const MR_Proc_Layout *entry)
 {
 	MR_print_proc_id_internal(fp, entry, FALSE);
 }
 
 void
-MR_print_proc_spec(FILE *fp, const MR_Stack_Layout_Entry *entry)
+MR_print_proc_spec(FILE *fp, const MR_Proc_Layout *entry)
 {
 	MR_print_proc_id_internal(fp, entry, TRUE);
 }
 
 static void
-MR_print_proc_id_internal(FILE *fp, const MR_Stack_Layout_Entry *entry,
+MR_print_proc_id_internal(FILE *fp, const MR_Proc_Layout *entry,
 	bool spec)
 {
 	if (! MR_ENTRY_LAYOUT_HAS_PROC_ID(entry)) {
@@ -597,7 +596,7 @@
 
 void
 MR_print_proc_id_trace_and_context(FILE *fp, bool include_trace_data,
-	MR_Context_Position pos, const MR_Stack_Layout_Entry *entry,
+	MR_Context_Position pos, const MR_Proc_Layout *entry,
 	MR_Word *base_sp, MR_Word *base_curfr,
 	const char *path, const char *filename, int lineno, bool print_parent, 
 	const char *parent_filename, int parent_lineno, int indent)
Index: runtime/mercury_stack_trace.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_trace.h,v
retrieving revision 1.24
diff -u -b -r1.24 mercury_stack_trace.h
--- runtime/mercury_stack_trace.h	2000/11/23 02:00:40	1.24
+++ runtime/mercury_stack_trace.h	2001/01/02 07:44:45
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -58,14 +58,14 @@
 */
 
 typedef	void		(*MR_Print_Stack_Record)(FILE *fp,
-				const MR_Stack_Layout_Entry *proc_layout,
+				const MR_Proc_Layout *proc_layout,
 				int count, int level,
 				MR_Word *base_sp, MR_Word * base_curfr,
 				const char *filename, int linenumber,
 				const char *goal_path, bool context_mismatch);
 
 extern	const char	*MR_dump_stack_from_layout(FILE *fp,
-				const MR_Stack_Layout_Label *label_layout,
+				const MR_Label_Layout *label_layout,
 				MR_Word *det_stack_pointer,
 				MR_Word *current_frame,
 				bool include_trace_data,
@@ -97,8 +97,8 @@
 **	and problem will point to an error message.
 */
 
-extern	const MR_Stack_Layout_Label *MR_find_nth_ancestor(
-			const MR_Stack_Layout_Label *label_layout,
+extern	const MR_Label_Layout *MR_find_nth_ancestor(
+			const MR_Label_Layout *label_layout,
 			int ancestor_level, MR_Word **stack_trace_sp,
 			MR_Word **stack_trace_curfr, const char **problem);
 
@@ -127,8 +127,8 @@
 } MR_Stack_Walk_Step_Result;
 
 extern  MR_Stack_Walk_Step_Result
-MR_stack_walk_step(const MR_Stack_Layout_Entry *entry_layout,
-		const MR_Stack_Layout_Label **return_label_layout,
+MR_stack_walk_step(const MR_Proc_Layout *entry_layout,
+		const MR_Label_Layout **return_label_layout,
 		MR_Word **stack_trace_sp_ptr, MR_Word **stack_trace_curfr_ptr,
 		const char **problem_ptr);
 
@@ -164,7 +164,7 @@
 ** it returns FALSE.
 */
 
-extern	bool	MR_find_context(const MR_Stack_Layout_Label *label,
+extern	bool	MR_find_context(const MR_Label_Layout *label,
 			const char **fileptr, int *lineptr);
 
 /*
@@ -180,12 +180,12 @@
 */
 
 extern	void	MR_print_call_trace_info(FILE *fp,
-			const MR_Stack_Layout_Entry *entry,
+			const MR_Proc_Layout *entry,
 			MR_Word *base_sp, MR_Word *base_curfr);
 
 extern	void	MR_maybe_print_call_trace_info(FILE *fp,
 			bool include_trace_data,
-			const MR_Stack_Layout_Entry *entry,
+			const MR_Proc_Layout *entry,
 			MR_Word *base_sp, MR_Word *base_curfr);
 
 /*
@@ -195,15 +195,14 @@
 ** the caller can put something else after the procedure id on the same line.
 */
 
-extern	void	MR_print_proc_id(FILE *fp, const MR_Stack_Layout_Entry *entry);
+extern	void	MR_print_proc_id(FILE *fp, const MR_Proc_Layout *entry);
 
 /*
 ** MR_print_proc_spec prints a string that uniquely specifies the given
 ** procedure to the debugger.
 */
 
-extern	void	MR_print_proc_spec(FILE *fp,
-			const MR_Stack_Layout_Entry *entry);
+extern	void	MR_print_proc_spec(FILE *fp, const MR_Proc_Layout *entry);
 
 /*
 ** MR_print_proc_id_trace_and_context prints an identification of the given
@@ -222,7 +221,7 @@
 
 extern	void	MR_print_proc_id_trace_and_context(FILE *fp,
 			bool include_trace_data, MR_Context_Position pos,
-			const MR_Stack_Layout_Entry *entry,
+			const MR_Proc_Layout *entry,
 			MR_Word *base_sp, MR_Word *base_curfr, const char *path,
 			const char *filename, int lineno, bool print_parent,
 			const char *parent_filename, int parent_lineno,
@@ -233,7 +232,7 @@
 */
 
 extern	void	MR_dump_stack_record_print(FILE *fp,
-			const MR_Stack_Layout_Entry *entry_layout, int count,
+			const MR_Proc_Layout *entry_layout, int count,
 			int start_level, MR_Word *base_sp, MR_Word *base_curfr,
 			const char *filename, int linenumber,
 			const char *goal_path, bool context_mismatch);
Index: runtime/mercury_trace_base.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace_base.c,v
retrieving revision 1.31
diff -u -b -r1.31 mercury_trace_base.c
--- runtime/mercury_trace_base.c	2000/12/06 06:05:47	1.31
+++ runtime/mercury_trace_base.c	2001/01/02 07:44:49
@@ -3,7 +3,7 @@
 ENDINIT
 */
 /*
-** Copyright (C) 1997-2000 The University of Melbourne.
+** Copyright (C) 1997-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -139,7 +139,7 @@
 };
 
 MR_Code *
-MR_trace(const MR_Stack_Layout_Label *layout)
+MR_trace(const MR_Label_Layout *layout)
 {
 	if (! MR_trace_enabled) {
 		return NULL;
@@ -164,7 +164,7 @@
 }
 
 MR_Code *
-MR_trace_fake(const MR_Stack_Layout_Label *layout)
+MR_trace_fake(const MR_Label_Layout *layout)
 {
 	MR_tracing_not_enabled();
 	/*NOTREACHED*/
@@ -363,7 +363,7 @@
 	{
 		MR_Code	*MR_jumpaddr;
 		MR_save_transient_registers();
-		MR_jumpaddr = MR_trace((const MR_Stack_Layout_Label *)
+		MR_jumpaddr = MR_trace((const MR_Label_Layout *)
 			MR_redo_layout_framevar(MR_redofr_slot(MR_curfr)));
 		MR_restore_transient_registers();
 		if (MR_jumpaddr != NULL) {
@@ -389,7 +389,7 @@
 	{
 		MR_Code	*MR_jumpaddr;
 		MR_save_transient_registers();
-		MR_jumpaddr = MR_trace((const MR_Stack_Layout_Label *)
+		MR_jumpaddr = MR_trace((const MR_Label_Layout *)
 			MR_redo_layout_framevar(MR_redofr_slot(MR_curfr)));
 		MR_restore_transient_registers();
 		if (MR_jumpaddr != NULL) {
Index: runtime/mercury_trace_base.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace_base.h,v
retrieving revision 1.15
diff -u -b -r1.15 mercury_trace_base.h
--- runtime/mercury_trace_base.h	2000/12/06 06:05:47	1.15
+++ runtime/mercury_trace_base.h	2001/01/02 07:44:52
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1997-2000 The University of Melbourne.
+** Copyright (C) 1997-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -63,8 +63,8 @@
 ** after the event. (NULL means it should continue as usual.)
 */
 
-extern	MR_Code	*MR_trace(const MR_Stack_Layout_Label *);
-extern	MR_Code	*MR_trace_fake(const MR_Stack_Layout_Label *);
+extern	MR_Code	*MR_trace(const MR_Label_Layout *);
+extern	MR_Code	*MR_trace_fake(const MR_Label_Layout *);
 
 /*
 ** MR_trace_init() is called from mercury_runtime_init()
Index: runtime/mercury_wrapper.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_wrapper.c,v
retrieving revision 1.83
diff -u -b -r1.83 mercury_wrapper.c
--- runtime/mercury_wrapper.c	2000/12/13 12:13:09	1.83
+++ runtime/mercury_wrapper.c	2001/01/02 07:44:56
@@ -3,7 +3,7 @@
 ENDINIT
 */
 /*
-** Copyright (C) 1994-2000 The University of Melbourne.
+** Copyright (C) 1994-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -224,7 +224,7 @@
 
 MR_Code	*MR_library_trace_browser;
 
-MR_Code	*(*volatile MR_trace_func_ptr)(const MR_Stack_Layout_Label *);
+MR_Code	*(*volatile MR_trace_func_ptr)(const MR_Label_Layout *);
 
 void	(*MR_address_of_trace_interrupt_handler)(void);
 
Index: runtime/mercury_wrapper.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_wrapper.h,v
retrieving revision 1.40
diff -u -b -r1.40 mercury_wrapper.h
--- runtime/mercury_wrapper.h	2000/12/04 18:35:11	1.40
+++ runtime/mercury_wrapper.h	2001/01/02 07:44:58
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1994-2000 The University of Melbourne.
+** Copyright (C) 1994-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -15,7 +15,7 @@
 #include "mercury_regs.h"		/* needs to come first */
 #include <stddef.h>			/* for `size_t' */
 #include "mercury_std.h"		/* for `bool' */
-#include "mercury_stack_layout.h"	/* for `MR_Stack_Layout_Label' etc */
+#include "mercury_stack_layout.h"	/* for `MR_Label_Layout' etc */
 #include "mercury_trace_base.h"		/* for `MR_trace_port' */
 #include "mercury_stacks.h"		/* for `MR_{Cut,Generator}StackFrame' */
 
@@ -140,7 +140,7 @@
 */
 
 extern	MR_Code		*(*volatile MR_trace_func_ptr)(
-				const MR_Stack_Layout_Label *);
+				const MR_Label_Layout *);
 
 /*
 ** If the init file was built with tracing enabled, then
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/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/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
cvs diff: Diffing trace
Index: trace/mercury_trace.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace.c,v
retrieving revision 1.35
diff -u -b -r1.35 mercury_trace.c
--- trace/mercury_trace.c	2000/12/20 07:44:57	1.35
+++ trace/mercury_trace.c	2001/01/02 07:45:42
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1997-2000 The University of Melbourne.
+** Copyright (C) 1997-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -60,31 +60,30 @@
 	TRUE	/* must check */
 };
 
-MR_Code 		*MR_trace_real(const MR_Stack_Layout_Label *layout);
+MR_Code 		*MR_trace_real(const MR_Label_Layout *layout);
 static	MR_Code		*MR_trace_event(MR_Trace_Cmd_Info *cmd,
 				bool interactive,
-				const MR_Stack_Layout_Label *layout,
+				const MR_Label_Layout *layout,
 				MR_Trace_Port port, MR_Unsigned seqno,
 				MR_Unsigned depth);
-static	bool		MR_in_traced_region(
-				const MR_Stack_Layout_Entry *proc_layout,
+static	bool		MR_in_traced_region(const MR_Proc_Layout *proc_layout,
 				MR_Word *base_sp, MR_Word *base_curfr);
 static	bool		MR_is_io_state(MR_PseudoTypeInfo pti);
 static	bool		MR_find_saved_io_counter(
-				const MR_Stack_Layout_Label *call_label,
+				const MR_Label_Layout *call_label,
 				MR_Word *base_sp, MR_Word *base_curfr,
 				MR_Unsigned *saved_io_counter_ptr);
-static	const MR_Stack_Layout_Label *MR_unwind_stacks_for_retry(
-				const MR_Stack_Layout_Label *top_layout,
+static	const MR_Label_Layout *MR_unwind_stacks_for_retry(
+				const MR_Label_Layout *top_layout,
 				int ancestor_level, MR_Word **base_sp_ptr,
 				MR_Word **base_curfr_ptr,
 				MR_Word **base_maxfr_ptr,
 				const char **problem);
-static	const char	*MR_undo_updates_of_maxfr(const MR_Stack_Layout_Entry
+static	const char	*MR_undo_updates_of_maxfr(const MR_Proc_Layout
 				*level_layout, MR_Word *sp, MR_Word *curfr,
 				MR_Word **maxfr_ptr);
 static	MR_Word		MR_trace_find_input_arg(
-				const MR_Stack_Layout_Label *label, 
+				const MR_Label_Layout *label, 
 				MR_Word *saved_regs,
 				MR_Word *base_sp, MR_Word *base_curfr,
 				MR_uint_least16_t var_num, bool *succeeded);
@@ -96,7 +95,7 @@
 #endif
 
 static	void		MR_init_call_table_array(void);
-static	void		MR_maybe_record_call_table(const MR_Stack_Layout_Entry
+static	void		MR_maybe_record_call_table(const MR_Proc_Layout
 				*level_layout, MR_Word *sp, MR_Word *curfr);
 static	void		MR_reset_call_table_array(void);
 static	void		MR_abandon_call_table_array(void);
@@ -114,7 +113,7 @@
 */
 
 MR_Code *
-MR_trace_real(const MR_Stack_Layout_Label *layout)
+MR_trace_real(const MR_Label_Layout *layout)
 {
 	MR_Integer	maybe_from_full;
 	MR_Unsigned	seqno;
@@ -335,7 +334,7 @@
 */
 
 static MR_Code *
-MR_trace_interrupt(const MR_Stack_Layout_Label *layout)
+MR_trace_interrupt(const MR_Label_Layout *layout)
 {
 	MR_Unsigned	seqno;
 	MR_Unsigned	depth;
@@ -381,7 +380,7 @@
 
 static MR_Code *
 MR_trace_event(MR_Trace_Cmd_Info *cmd, bool interactive,
-	const MR_Stack_Layout_Label *layout, MR_Trace_Port port,
+	const MR_Label_Layout *layout, MR_Trace_Port port,
 	MR_Unsigned seqno, MR_Unsigned depth)
 {
 	MR_Code		*jumpaddr;
@@ -458,11 +457,10 @@
 	MR_Word				*base_sp;
 	MR_Word				*base_curfr;
 	MR_Word				*base_maxfr;
-	const MR_Stack_Layout_Label	*top_layout;
-	const MR_Stack_Layout_Label	*return_label_layout;
-	const MR_Stack_Layout_Label	*call_label;
-	const MR_Stack_Layout_Entry	*level_layout;
-	const MR_Stack_Layout_Vars	*input_args;
+	const MR_Label_Layout		*top_layout;
+	const MR_Label_Layout		*return_label_layout;
+	const MR_Label_Layout		*call_label;
+	const MR_Proc_Layout		*level_layout;
 	MR_Word				*args;
 	int				arg_max;
 	int				arg_num;
@@ -518,8 +516,7 @@
 	}
 
 	call_label = level_layout->MR_sle_call_label;
-	input_args = &call_label->MR_sll_var_info;
-	if (input_args->MR_slvs_var_count < 0) {
+	if (call_label->MR_sll_var_count < 0) {
 		*problem = "Cannot perform retry because information about "
 		          "the input arguments is not available.";
 		goto report_problem;
@@ -540,14 +537,14 @@
 		/* just to prevent uninitialized variable warnings */
 	saved_io_action_counter = 0;
 
-	for (i = 0; i < MR_all_desc_var_count(input_args); i++) {
+	for (i = 0; i < MR_all_desc_var_count(call_label); i++) {
 		arg_value = MR_trace_find_input_arg(return_label_layout,
 				saved_regs, base_sp, base_curfr,
-				input_args->MR_slvs_var_nums[i],
+				call_label->MR_sll_var_nums[i],
 				&succeeded);
 
 		if (! succeeded) {
-			if (MR_is_io_state(MR_var_pti(input_args, i))) {
+			if (MR_is_io_state(MR_var_pti(call_label, i))) {
 				/*
 				** Since I/O state input arguments are not
 				** used, we can leave arg_value containing
@@ -567,12 +564,12 @@
 			}
 		}
 
-		if (i < MR_long_desc_var_count(input_args)) {
+		if (i < MR_long_desc_var_count(call_label)) {
 			arg_num = MR_get_register_number_long(
-				MR_long_desc_var_locn(input_args, i));
+				MR_long_desc_var_locn(call_label, i));
 		} else {
 			arg_num = MR_get_register_number_short(
-				MR_short_desc_var_locn(input_args, i));
+				MR_short_desc_var_locn(call_label, i));
 		}
 
 		if (arg_num > 0) {
@@ -778,7 +775,7 @@
 }
 
 static bool
-MR_in_traced_region(const MR_Stack_Layout_Entry *proc_layout,
+MR_in_traced_region(const MR_Proc_Layout *proc_layout,
 	MR_Word *base_sp, MR_Word *base_curfr)
 {
 	if (proc_layout->MR_sle_maybe_from_full <= 0) {
@@ -816,11 +813,11 @@
 }
 
 static bool
-MR_find_saved_io_counter(const MR_Stack_Layout_Label *call_label,
+MR_find_saved_io_counter(const MR_Label_Layout *call_label,
 	MR_Word *base_sp, MR_Word *base_curfr,
 	MR_Unsigned *saved_io_counter_ptr)
 {
-	const MR_Stack_Layout_Entry	*level_layout;
+	const MR_Proc_Layout	*level_layout;
 	MR_Unsigned			saved_io_counter;
 
 	level_layout = call_label->MR_sll_entry;
@@ -854,14 +851,14 @@
 ** to point to a string giving the reason for its failure.
 */
 
-static const MR_Stack_Layout_Label *
-MR_unwind_stacks_for_retry(const MR_Stack_Layout_Label *top_layout,
+static const MR_Label_Layout *
+MR_unwind_stacks_for_retry(const MR_Label_Layout *top_layout,
 	int ancestor_level, MR_Word **sp_ptr, MR_Word **curfr_ptr,
 	MR_Word **maxfr_ptr, const char **problem)
 {
 	MR_Stack_Walk_Step_Result       result;
-	const MR_Stack_Layout_Entry	*level_layout;
-	const MR_Stack_Layout_Label	*return_label_layout;
+	const MR_Proc_Layout		*level_layout;
+	const MR_Label_Layout		*return_label_layout;
 	int				i;
 
 	if (ancestor_level < 0) {
@@ -945,7 +942,7 @@
 }
 
 static const char *
-MR_undo_updates_of_maxfr(const MR_Stack_Layout_Entry *level_layout,
+MR_undo_updates_of_maxfr(const MR_Proc_Layout *level_layout,
 	MR_Word *level_sp, MR_Word *level_curfr, MR_Word **maxfr_ptr)
 {
 	if (MR_DETISM_DET_STACK(level_layout->MR_sle_detism)) {
@@ -983,29 +980,27 @@
 }
 
 static MR_Word
-MR_trace_find_input_arg(const MR_Stack_Layout_Label *label, MR_Word *saved_regs,
-	MR_Word *base_sp, MR_Word *base_curfr, MR_uint_least16_t var_num,
-	bool *succeeded)
+MR_trace_find_input_arg(const MR_Label_Layout *label_layout,
+	MR_Word *saved_regs, MR_Word *base_sp, MR_Word *base_curfr,
+	MR_uint_least16_t var_num, bool *succeeded)
 {
-	const MR_Stack_Layout_Vars	*vars;
 	int				i;
 
-	vars = &label->MR_sll_var_info;
-	if (vars->MR_slvs_var_nums == NULL) {
+	if (label_layout->MR_sll_var_nums == NULL) {
 		*succeeded = FALSE;
 		return 0;
 	}
 
-	for (i = 0; i < MR_all_desc_var_count(vars); i++) {
-		if (var_num == vars->MR_slvs_var_nums[i]) {
-			if (i < MR_long_desc_var_count(vars)) {
+	for (i = 0; i < MR_all_desc_var_count(label_layout); i++) {
+		if (var_num == label_layout->MR_sll_var_nums[i]) {
+			if (i < MR_long_desc_var_count(label_layout)) {
 				return MR_lookup_long_lval_base(
-					MR_long_desc_var_locn(vars, i),
+					MR_long_desc_var_locn(label_layout, i),
 					saved_regs, base_sp, base_curfr,
 					succeeded);
 			} else {
 				return MR_lookup_short_lval_base(
-					MR_short_desc_var_locn(vars, i),
+					MR_short_desc_var_locn(label_layout, i),
 					saved_regs, base_sp, base_curfr,
 					succeeded);
 			}
@@ -1047,8 +1042,8 @@
 MR_check_minimal_model_calls(MR_Event_Info *event_info, int ancestor_level,
 	MR_Word *target_maxfr, const char **problem)
 {
-	const MR_Stack_Layout_Label	*label_layout;
-	const MR_Stack_Layout_Entry	*proc_layout;
+	const MR_Label_Layout		*label_layout;
+	const MR_Proc_Layout		*proc_layout;
 	MR_Word				*top_maxfr;
 	MR_Word				*cur_maxfr;
 	MR_Code				*redoip;
@@ -1223,7 +1218,7 @@
 }
 
 static void
-MR_maybe_record_call_table(const MR_Stack_Layout_Entry *level_layout,
+MR_maybe_record_call_table(const MR_Proc_Layout *level_layout,
 	MR_Word *base_sp, MR_Word *base_curfr)
 {
 	MR_TrieNode	call_table;
Index: trace/mercury_trace.h
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace.h,v
retrieving revision 1.19
diff -u -b -r1.19 mercury_trace.h
--- trace/mercury_trace.h	2000/12/06 06:06:04	1.19
+++ trace/mercury_trace.h	2001/01/02 07:45:44
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1997-2000 The University of Melbourne.
+** Copyright (C) 1997-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -32,7 +32,7 @@
 	MR_Unsigned			MR_call_seqno;
 	MR_Unsigned			MR_call_depth;
 	MR_Trace_Port			MR_trace_port;
-	const MR_Stack_Layout_Label	*MR_event_sll;
+	const MR_Label_Layout		*MR_event_sll;
 	const char 			*MR_event_path;
 	MR_Word				MR_saved_regs[MR_MAX_FAKE_REG];
 	int				MR_max_mr_num;
Index: trace/mercury_trace_declarative.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_declarative.c,v
retrieving revision 1.36
diff -u -b -r1.36 mercury_trace_declarative.c
--- trace/mercury_trace_declarative.c	2000/12/06 06:06:05	1.36
+++ trace/mercury_trace_declarative.c	2001/01/02 07:45:52
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -203,10 +203,10 @@
 MR_trace_decl_neg_failure(MR_Event_Info *event_info, MR_Trace_Node prev);
 
 static	MR_Trace_Node
-MR_trace_decl_get_slot(const MR_Stack_Layout_Entry *entry, MR_Word *saved_regs);
+MR_trace_decl_get_slot(const MR_Proc_Layout *entry, MR_Word *saved_regs);
 
 static	void
-MR_trace_decl_set_slot(const MR_Stack_Layout_Entry *entry, MR_Word *saved_regs,
+MR_trace_decl_set_slot(const MR_Proc_Layout *entry, MR_Word *saved_regs,
 		MR_Trace_Node node);
 
 static	MR_Trace_Node
@@ -231,14 +231,14 @@
 MR_trace_single_component(const char *path);
 
 static	MR_Word
-MR_decl_make_atom(const MR_Stack_Layout_Label *layout, MR_Word *saved_regs,
+MR_decl_make_atom(const MR_Label_Layout *layout, MR_Word *saved_regs,
 		MR_Trace_Port port);
 
 static	MR_ConstString
-MR_decl_atom_name(const MR_Stack_Layout_Entry *entry);
+MR_decl_atom_name(const MR_Proc_Layout *entry);
 
 static	MR_Word
-MR_decl_atom_args(const MR_Stack_Layout_Label *layout, MR_Word *saved_regs);
+MR_decl_atom_args(const MR_Label_Layout *layout, MR_Word *saved_regs);
 
 static	const char *
 MR_trace_start_collecting(MR_Unsigned event, MR_Unsigned seqno,
@@ -289,7 +289,7 @@
 MR_Code *
 MR_trace_decl_debug(MR_Trace_Cmd_Info *cmd, MR_Event_Info *event_info)
 {
-	MR_Stack_Layout_Entry 	*entry;
+	const MR_Proc_Layout 	*entry;
 	MR_Unsigned		depth;
 	MR_Trace_Node		trace;
 	MR_Event_Details	event_details;
@@ -476,7 +476,7 @@
 	MR_Trace_Node			node;
 	MR_Word				atom;
 	bool				at_depth_limit;
-	const MR_Stack_Layout_Label	*layout = event_info->MR_event_sll;
+	const MR_Label_Layout		*layout = event_info->MR_event_sll;
 
 	if (event_info->MR_call_depth == MR_edt_max_depth) {
 		at_depth_limit = TRUE;
@@ -871,7 +871,7 @@
 #ifdef MR_USE_DECL_STACK_SLOT
 
 static	MR_Trace_Node
-MR_trace_decl_get_slot(const MR_Stack_Layout_Entry *entry, MR_Word *saved_regs)
+MR_trace_decl_get_slot(const MR_Proc_Layout *entry, MR_Word *saved_regs)
 {
 	int			decl_slot;
 	MR_Word			*saved_sp;
@@ -893,7 +893,7 @@
 }
 
 static	void
-MR_trace_decl_set_slot(const MR_Stack_Layout_Entry *entry,
+MR_trace_decl_set_slot(const MR_Proc_Layout *entry,
 		MR_Word *saved_regs, MR_Trace_Node node)
 {
 	int			decl_slot;
@@ -1046,7 +1046,7 @@
 }
 
 static	MR_Word
-MR_decl_make_atom(const MR_Stack_Layout_Label *layout, MR_Word *saved_regs,
+MR_decl_make_atom(const MR_Label_Layout *layout, MR_Word *saved_regs,
 		MR_Trace_Port port)
 {
 	MR_PredFunc			pred_or_func;
@@ -1054,10 +1054,9 @@
 	MR_Word				arity;
 	MR_Word				atom;
 	int				i;
-	const MR_Stack_Layout_Vars	*vars;
 	int				arg_count;
 	MR_TypeInfoParams		type_params;
-	const MR_Stack_Layout_Entry	*entry = layout->MR_sll_entry;
+	const MR_Proc_Layout		*entry = layout->MR_sll_entry;
 
 	MR_trace_init_point_vars(layout, saved_regs, port);
 
@@ -1113,7 +1112,7 @@
 }
 
 static	MR_ConstString
-MR_decl_atom_name(const MR_Stack_Layout_Entry *entry)
+MR_decl_atom_name(const MR_Proc_Layout *entry)
 {
 	MR_ConstString		name;
 
@@ -1162,7 +1161,7 @@
 		MR_Code **jumpaddr)
 {
 	MR_Retry_Result		result;
-	MR_Stack_Layout_Entry 	*entry;
+	const MR_Proc_Layout 	*entry;
 	FILE			*out;
 	MR_Unsigned		depth_limit;
 	const char		*message;
Index: trace/mercury_trace_external.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_external.c,v
retrieving revision 1.49
diff -u -b -r1.49 mercury_trace_external.c
--- trace/mercury_trace_external.c	2000/12/06 06:06:05	1.49
+++ trace/mercury_trace_external.c	2001/01/02 07:45:50
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -168,12 +168,12 @@
 			MR_Word *debugger_request_ptr, 
 			MR_Integer *debugger_request_type_ptr);
 	
-static bool	MR_found_match(const MR_Stack_Layout_Label *layout,
+static bool	MR_found_match(const MR_Label_Layout *layout,
 			MR_Trace_Port port, MR_Unsigned seqno,
 			MR_Unsigned depth,
 			/* XXX registers */
 			const char *path, MR_Word search_data);
-static void	MR_output_current_slots(const MR_Stack_Layout_Label *layout,
+static void	MR_output_current_slots(const MR_Label_Layout *layout,
 			MR_Trace_Port port, MR_Unsigned seqno,
 			MR_Unsigned depth, const char *path);
 static void	MR_output_current_vars(MR_Word var_list, MR_Word string_list);
@@ -185,10 +185,11 @@
 static MR_Word	MR_trace_make_type_list(void);
 static MR_Word	MR_trace_make_nth_var(MR_Word debugger_request);
 static int	MR_get_var_number(MR_Word debugger_request);
-static void	MR_print_proc_id_to_socket(const MR_Stack_Layout_Entry *entry,
-			const char *extra, MR_Word *base_sp, MR_Word *base_curfr);
+static void	MR_print_proc_id_to_socket(const MR_Proc_Layout *entry,
+			const char *extra,
+			MR_Word *base_sp, MR_Word *base_curfr);
 static void	MR_dump_stack_record_print_to_socket(FILE *fp, 
-			const MR_Stack_Layout_Entry *entry_layout, int count,
+			const MR_Proc_Layout *entry_layout, int count,
 			int start_level, MR_Word *base_sp, MR_Word *base_curfr,
 			const char *filename, int linenumber,
 			const char *goal_path, bool context_mismatch);
@@ -208,7 +209,7 @@
 			MR_String, MR_Word, MR_Word *, MR_Char *),
 			MR_Unsigned seqno, MR_Unsigned depth,
 			MR_Trace_Port port, 
-			const MR_Stack_Layout_Label *layout, const char *path, 
+			const MR_Label_Layout *layout, const char *path, 
 			bool *stop_collecting);
 static void	MR_send_collect_result(void);
 
@@ -497,7 +498,7 @@
 	MR_Event_Details	event_details;
 	const char		*message;
         bool			include_trace_data = TRUE;
-	const MR_Stack_Layout_Label *layout = event_info->MR_event_sll;
+	const MR_Label_Layout	*layout = event_info->MR_event_sll;
 	MR_Unsigned		seqno = event_info->MR_call_seqno;
 	MR_Unsigned		depth = event_info->MR_call_depth;
 	MR_Trace_Port		port = event_info->MR_trace_port;
@@ -907,7 +908,7 @@
 }
 
 static void
-MR_output_current_slots(const MR_Stack_Layout_Label *layout,
+MR_output_current_slots(const MR_Label_Layout *layout,
 	MR_Trace_Port port, MR_Unsigned seqno, MR_Unsigned depth,
 	const char *path)
 {
@@ -1003,7 +1004,7 @@
 }
  
 static bool
-MR_found_match(const MR_Stack_Layout_Label *layout,
+MR_found_match(const MR_Label_Layout *layout,
 	MR_Trace_Port port, MR_Unsigned seqno, MR_Unsigned depth,
 	/* XXX live vars */
 	const char *path, MR_Word search_data)
@@ -1291,7 +1292,7 @@
 
 static void
 MR_dump_stack_record_print_to_socket(FILE *fp, 
-	const MR_Stack_Layout_Entry *entry_layout, int count, int start_level, 
+	const MR_Proc_Layout *entry_layout, int count, int start_level, 
 	MR_Word *base_sp, MR_Word *base_curfr,
 	const char *filename, int linenumber,
 	const char *goal_path, bool context_mismatch)
@@ -1301,7 +1302,7 @@
 }
 
 static void
-MR_print_proc_id_to_socket(const MR_Stack_Layout_Entry *entry,
+MR_print_proc_id_to_socket(const MR_Proc_Layout *entry,
 	const char *extra, MR_Word *base_sp, MR_Word *base_curfr)
 {
 	if (! MR_ENTRY_LAYOUT_HAS_PROC_ID(entry)) {
@@ -1481,7 +1482,7 @@
 	MR_Word, MR_Word, MR_String, MR_String, MR_String, MR_Integer,
 	MR_Integer, MR_Word, MR_Integer, MR_String, MR_Word, MR_Word *,
 	MR_Char *), MR_Unsigned seqno, MR_Unsigned depth, MR_Trace_Port port, 
-	const MR_Stack_Layout_Label *layout, const char *path, 
+	const MR_Label_Layout *layout, const char *path, 
 	bool *stop_collecting)
 {
 	MR_Char	result;		
Index: trace/mercury_trace_internal.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_internal.c,v
retrieving revision 1.91
diff -u -b -r1.91 mercury_trace_internal.c
--- trace/mercury_trace_internal.c	2000/12/18 05:16:57	1.91
+++ trace/mercury_trace_internal.c	2001/01/02 07:45:48
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -402,7 +402,7 @@
 MR_trace_set_level_and_report(int ancestor_level, bool detailed)
 {
 	const char			*problem;
-	const MR_Stack_Layout_Entry	*entry;
+	const MR_Proc_Layout	*entry;
 	MR_Word				*base_sp;
 	MR_Word				*base_curfr;
 	const char			*filename;
@@ -504,7 +504,7 @@
 */
 
 static void
-MR_mdb_print_proc_id(void *data, const MR_Stack_Layout_Entry *entry_layout)
+MR_mdb_print_proc_id(void *data, const MR_Proc_Layout *entry_layout)
 {
 	FILE	*fp = data;
 	MR_print_proc_id_for_debugger(fp, entry_layout);
@@ -577,7 +577,7 @@
 	MR_Event_Info *event_info, MR_Event_Details *event_details,
 	MR_Code **jumpaddr)
 {
-	const MR_Stack_Layout_Label	*layout;
+	const MR_Label_Layout	*layout;
 	MR_Word 				*saved_regs;
 
 	layout = event_info->MR_event_sll;
@@ -1756,7 +1756,7 @@
 			MR_trace_usage("help", "help");
 		}
 	} else if (streq(words[0], "proc_body")) {
-		const MR_Stack_Layout_Entry	*entry;
+		const MR_Proc_Layout	*entry;
 
 		entry = event_info->MR_event_sll->MR_sll_entry;
 		if (entry->MR_sle_proc_rep == 0) {
@@ -2927,7 +2927,7 @@
 static void
 MR_trace_event_print_internal_report(MR_Event_Info *event_info)
 {
-	const MR_Stack_Layout_Label	*parent;
+	const MR_Label_Layout	*parent;
 	const char			*filename, *parent_filename;
 	int				lineno, parent_lineno;
 	const char			*problem; /* not used */
Index: trace/mercury_trace_spy.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_spy.c,v
retrieving revision 1.16
diff -u -b -r1.16 mercury_trace_spy.c
--- trace/mercury_trace_spy.c	2000/12/18 05:16:59	1.16
+++ trace/mercury_trace_spy.c	2001/01/02 07:45:54
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -54,7 +54,7 @@
 */
 
 typedef struct {
-	const MR_Stack_Layout_Entry	*spy_proc;
+	const MR_Proc_Layout		*spy_proc;
 	MR_Spy_Point			*spy_points;
 } MR_Spied_Proc;
 
@@ -73,7 +73,7 @@
 */
 
 typedef struct {
-	const MR_Stack_Layout_Label	*spy_label;
+	const MR_Label_Layout	*spy_label;
 	int				spy_point_num;
 } MR_Spied_Label;
 
@@ -87,12 +87,10 @@
 /**************************************************************************/
 
 static	int	MR_compare_addr(const void *address1, const void *address2);
-static	int	MR_search_spy_table_for_proc(const MR_Stack_Layout_Entry
-			*entry);
-static	int	MR_search_spy_table_for_label(const MR_Stack_Layout_Label
-			*label);
-static	void	MR_add_line_spy_point_callback(const MR_Stack_Layout_Label
-			*label, int spy_point_num);
+static	int	MR_search_spy_table_for_proc(const MR_Proc_Layout *entry);
+static	int	MR_search_spy_table_for_label(const MR_Label_Layout *label);
+static	void	MR_add_line_spy_point_callback(const MR_Label_Layout *label,
+			int spy_point_num);
 static	int	MR_compare_spied_labels(const void *, const void *);
 
 /*
@@ -126,7 +124,7 @@
 */
 
 static int
-MR_search_spy_table_for_proc(const MR_Stack_Layout_Entry *entry)
+MR_search_spy_table_for_proc(const MR_Proc_Layout *entry)
 {
 	int	slot;
 	bool	found;
@@ -146,7 +144,7 @@
 */
 
 static int
-MR_search_spy_table_for_label(const MR_Stack_Layout_Label *label)
+MR_search_spy_table_for_label(const MR_Label_Layout *label)
 {
 	int	slot;
 	bool	found;
@@ -161,14 +159,14 @@
 }
 
 bool
-MR_event_matches_spy_point(const MR_Stack_Layout_Label *layout,
+MR_event_matches_spy_point(const MR_Label_Layout *layout,
 	MR_Trace_Port port, MR_Spy_Action *action_ptr)
 {
 	int				slot;
 	bool				enabled;
 	MR_Spy_Point			*point;
 	MR_Spy_Action			action;
-	const MR_Stack_Layout_Label	*parent;
+	const MR_Label_Layout	*parent;
 	const char			*problem;
 	MR_Word				*base_sp;
 	MR_Word				*base_curfr;
@@ -290,7 +288,7 @@
 
 int
 MR_add_proc_spy_point(MR_Spy_When when, MR_Spy_Action action,
-	const MR_Stack_Layout_Entry *entry, const MR_Stack_Layout_Label *label)
+	const MR_Proc_Layout *entry, const MR_Label_Layout *label)
 {
 	MR_Spy_Point	*point;
 	int		point_slot;
@@ -391,8 +389,7 @@
 }
 
 static void
-MR_add_line_spy_point_callback(const MR_Stack_Layout_Label *label,
-	int spy_point_num)
+MR_add_line_spy_point_callback(const MR_Label_Layout *label, int spy_point_num)
 {
 	int	spied_label_slot;
 
Index: trace/mercury_trace_spy.h
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_spy.h,v
retrieving revision 1.5
diff -u -b -r1.5 mercury_trace_spy.h
--- trace/mercury_trace_spy.h	2000/09/19 07:14:22	1.5
+++ trace/mercury_trace_spy.h	2001/01/02 07:45:58
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -39,8 +39,8 @@
 	bool				spy_enabled;
 	MR_Spy_When			spy_when;
 	MR_Spy_Action			spy_action;
-	const MR_Stack_Layout_Entry	*spy_proc;      /* if not LINENO */
-	const MR_Stack_Layout_Label	*spy_label;	/* if SPECIFIC */
+	const MR_Proc_Layout	*spy_proc;      /* if not LINENO */
+	const MR_Label_Layout	*spy_label;	/* if SPECIFIC */
 	char				*spy_filename;  /* if LINENO */
 	int				spy_linenumber; /* if LINENO */
 	MR_Spy_Point			*spy_next;	/* if not LINENO */
@@ -63,7 +63,7 @@
 ** action should be executed for the spy point.
 */
 
-extern	bool		MR_event_matches_spy_point(const MR_Stack_Layout_Label
+extern	bool		MR_event_matches_spy_point(const MR_Label_Layout
 				*layout, MR_Trace_Port port,
 				MR_Spy_Action *action);
 
@@ -74,8 +74,8 @@
 
 extern	int		MR_add_proc_spy_point(MR_Spy_When when,
 				MR_Spy_Action action,
-				const MR_Stack_Layout_Entry *entry,
-				const MR_Stack_Layout_Label *label);
+				const MR_Proc_Layout *entry,
+				const MR_Label_Layout *label);
 
 /*
 ** Add a new spy point on a line number (as opposed to on a procedure)
Index: trace/mercury_trace_tables.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_tables.c,v
retrieving revision 1.12
diff -u -b -r1.12 mercury_trace_tables.c
--- trace/mercury_trace_tables.c	2000/12/04 04:34:32	1.12
+++ trace/mercury_trace_tables.c	2001/01/02 07:46:08
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -33,11 +33,10 @@
 static	void	MR_insert_module_info(const MR_Module_Layout *);
 static	void	MR_process_matching_procedures_in_module(
 			const MR_Module_Layout *module, MR_Proc_Spec *spec,
-			void f(void *, const MR_Stack_Layout_Entry *),
-			void *);
-static	void	MR_process_line_layouts(MR_Module_File_Layout *file_layout,
-			int line, MR_file_line_callback callback_func,
-			int callback_arg);
+			void f(void *, const MR_Proc_Layout *), void *);
+static	void	MR_process_line_layouts(const MR_Module_File_Layout
+			*file_layout, int line,
+			MR_file_line_callback callback_func, int callback_arg);
 
 void
 MR_register_all_modules_and_procs(FILE *fp, bool verbose)
@@ -120,7 +119,7 @@
 	MR_file_line_callback callback_func, int callback_arg)
 {
 	int			i, j;
-	MR_Module_File_Layout	*file_layout;
+	const MR_Module_File_Layout	*file_layout;
 
 	for (i = 0; i < MR_module_info_next; i++) {
 		for (j = 0; j < MR_module_infos[i]->MR_ml_filename_count; j++)
@@ -136,7 +135,7 @@
 }
 
 static void
-MR_process_line_layouts(MR_Module_File_Layout *file_layout, int line,
+MR_process_line_layouts(const MR_Module_File_Layout *file_layout, int line,
 	MR_file_line_callback callback_func, int callback_arg)
 {
 	int			k;
@@ -312,12 +311,12 @@
 #define	MR_INIT_MATCH_PROC_SIZE		8
 
 static void
-MR_register_matches(void *data, const MR_Stack_Layout_Entry *entry)
+MR_register_matches(void *data, const MR_Proc_Layout *entry)
 {
 	MR_Matches_Info	*m;
 
 	m = (MR_Matches_Info *) data;
-	MR_ensure_room_for_next(m->match_proc, const MR_Stack_Layout_Entry *,
+	MR_ensure_room_for_next(m->match_proc, const MR_Proc_Layout *,
 		MR_INIT_MATCH_PROC_SIZE);
 	m->match_procs[m->match_proc_next] = entry;
 	m->match_proc_next++;
@@ -341,12 +340,12 @@
 */
 
 typedef struct {
-	const MR_Stack_Layout_Entry	*matching_entry;
+	const MR_Proc_Layout	*matching_entry;
 	bool	 			match_unique;
 } MR_Match_Info;
 
 static void
-MR_register_match(void *data, const MR_Stack_Layout_Entry *entry)
+MR_register_match(void *data, const MR_Proc_Layout *entry)
 {
 	MR_Match_Info	*m;
 
@@ -358,7 +357,7 @@
 	}
 }
 
-const MR_Stack_Layout_Entry *
+const MR_Proc_Layout *
 MR_search_for_matching_procedure(MR_Proc_Spec *spec, bool *unique)
 {
 	MR_Match_Info	m;
@@ -372,8 +371,7 @@
 
 void
 MR_process_matching_procedures(MR_Proc_Spec *spec,
-	void f(void *, const MR_Stack_Layout_Entry *),
-	void *data)
+	void f(void *, const MR_Proc_Layout *), void *data)
 {
 	if (spec->MR_proc_module != NULL) {
 		const MR_Module_Layout	*module;
@@ -411,10 +409,9 @@
 
 static void
 MR_process_matching_procedures_in_module(const MR_Module_Layout *module,
-	MR_Proc_Spec *spec, void f(void *, const MR_Stack_Layout_Entry *),
-	void *data)
+	MR_Proc_Spec *spec, void f(void *, const MR_Proc_Layout *), void *data)
 {
-	const MR_Stack_Layout_Entry	*cur_entry;
+	const MR_Proc_Layout	*cur_entry;
 	int				j;
 
 	for (j = 0; j < module->MR_ml_proc_count; j++) {
@@ -430,8 +427,7 @@
 }
 
 void
-MR_print_proc_id_for_debugger(FILE *fp,
-	const MR_Stack_Layout_Entry *entry_layout)
+MR_print_proc_id_for_debugger(FILE *fp, const MR_Proc_Layout *entry_layout)
 {
 	MR_print_proc_id(fp, entry_layout);
 	fprintf(fp, "\n");
Index: trace/mercury_trace_tables.h
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_tables.h,v
retrieving revision 1.7
diff -u -b -r1.7 mercury_trace_tables.h
--- trace/mercury_trace_tables.h	2000/08/25 09:53:37	1.7
+++ trace/mercury_trace_tables.h	2001/01/02 07:46:10
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1998-2000 The University of Melbourne.
+** Copyright (C) 1998-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -44,8 +44,7 @@
 ** with the supplied integer callback argument.
 */
 
-typedef	void		(*MR_file_line_callback)(const MR_Stack_Layout_Label *,
-				int);
+typedef	void		(*MR_file_line_callback)(const MR_Label_Layout *, int);
 
 extern	void		MR_process_file_line_layouts(const char *file,
 				int line, MR_file_line_callback callback_func,
@@ -112,7 +111,7 @@
 ** and set *unique to FALSE.
 */
 
-extern	const MR_Stack_Layout_Entry *MR_search_for_matching_procedure(
+extern	const MR_Proc_Layout *MR_search_for_matching_procedure(
 					MR_Proc_Spec *spec, bool *unique);
 
 /*
@@ -124,7 +123,7 @@
 */
 
 typedef struct {
-	const MR_Stack_Layout_Entry	**match_procs;
+	const MR_Proc_Layout	**match_procs;
 	int	 			match_proc_max;
 	int	 			match_proc_next;
 } MR_Matches_Info;
@@ -140,10 +139,10 @@
 */
 
 extern	void	MR_process_matching_procedures(MR_Proc_Spec *spec,
-			void f(void *, const MR_Stack_Layout_Entry *), 
+			void f(void *, const MR_Proc_Layout *), 
 			void *data);
 
 extern	void	MR_print_proc_id_for_debugger(FILE *fp,
-			const MR_Stack_Layout_Entry *entry);
+			const MR_Proc_Layout *entry);
 
 #endif	/* not MERCURY_TRACE_TABLES_H */
Index: trace/mercury_trace_vars.c
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_vars.c,v
retrieving revision 1.24
diff -u -b -r1.24 mercury_trace_vars.c
--- trace/mercury_trace_vars.c	2000/12/18 07:43:05	1.24
+++ trace/mercury_trace_vars.c	2001/01/02 07:46:01
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1999-2000 The University of Melbourne.
+** Copyright (C) 1999-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 */
@@ -91,12 +91,12 @@
 */
 
 typedef struct {
-	const MR_Stack_Layout_Label	*MR_point_top_layout;
+	const MR_Label_Layout	*MR_point_top_layout;
 	MR_Word				*MR_point_top_saved_regs;
 	MR_Trace_Port			MR_point_top_port;
 	const char			*MR_point_problem;
 	int				MR_point_level;
-	const MR_Stack_Layout_Entry	*MR_point_level_entry;
+	const MR_Proc_Layout	*MR_point_level_entry;
 	const char			*MR_point_level_filename;
 	int				MR_point_level_linenumber;
 	MR_Word				*MR_point_level_base_sp;
@@ -221,7 +221,7 @@
 }
 
 void
-MR_trace_init_point_vars(const MR_Stack_Layout_Label *top_layout,
+MR_trace_init_point_vars(const MR_Label_Layout *top_layout,
 	MR_Word *saved_regs, MR_Trace_Port port)
 {
 	MR_point.MR_point_top_layout = top_layout;
@@ -237,10 +237,9 @@
 	const char			*problem;
 	MR_Word				*base_sp;
 	MR_Word				*base_curfr;
-	const MR_Stack_Layout_Label	*top_layout;
-	const MR_Stack_Layout_Label	*level_layout;
-	const MR_Stack_Layout_Entry	*entry;
-	const MR_Stack_Layout_Vars	*vars;
+	const MR_Label_Layout		*top_layout;
+	const MR_Label_Layout		*level_layout;
+	const MR_Proc_Layout		*entry;
 	MR_Word				*valid_saved_regs;
 	int				var_count;
 	MR_TypeInfo			*type_params;
@@ -281,8 +280,7 @@
 		return problem;
 	}
 
-	vars = &level_layout->MR_sll_var_info;
-	if (! MR_has_valid_var_count(vars)) {
+	if (! MR_has_valid_var_count(level_layout)) {
 		return "there is no information about live variables";
 	}
 
@@ -306,8 +304,8 @@
 	MR_point.MR_point_level_base_sp = base_sp;
 	MR_point.MR_point_level_base_curfr = base_curfr;
 
-	if (MR_has_valid_var_info(vars)) {
-		var_count = MR_all_desc_var_count(vars);
+	if (MR_has_valid_var_info(level_layout)) {
+		var_count = MR_all_desc_var_count(level_layout);
 	} else {
 		/*
 		** If the count of variables is zero, then the rest of the
@@ -323,7 +321,7 @@
 		return NULL;
 	}
 
-	if (vars->MR_slvs_var_nums == NULL) {
+	if (level_layout->MR_sll_var_nums == NULL) {
 		return "there are no names for the live variables";
 	}
 
@@ -335,7 +333,7 @@
 		valid_saved_regs = NULL;
 	}
 
-	type_params = MR_materialize_typeinfos_base(vars,
+	type_params = MR_materialize_typeinfos_base(level_layout,
 				valid_saved_regs, base_sp, base_curfr);
 
 	MR_ensure_big_enough(var_count, MR_point.MR_point_var, 
@@ -356,7 +354,7 @@
 		int	var_num;
 		int	offset;
 
-		var_num = vars->MR_slvs_var_nums[i];
+		var_num = level_layout->MR_sll_var_nums[i];
 
 		if (var_num == 0) {
 			/* this value is not a variable */
@@ -379,13 +377,14 @@
 			continue;
 		}
 
-		pseudo_type_info = MR_var_pti(vars, i);
+		pseudo_type_info = MR_var_pti(level_layout, i);
 		if (MR_trace_type_is_ignored(pseudo_type_info)) {
 			continue;
 		}
 
-		if (! MR_get_type_and_value_base(vars, i, valid_saved_regs,
-			base_sp, base_curfr, type_params, &type_info, &value))
+		if (! MR_get_type_and_value_base(level_layout, i,
+			valid_saved_regs, base_sp, base_curfr,
+			type_params, &type_info, &value))
 		{
 			/* this value is not a variable */
 			continue;
@@ -533,7 +532,7 @@
 }
 
 void
-MR_trace_current_level_details(const MR_Stack_Layout_Entry **entry_ptr,
+MR_trace_current_level_details(const MR_Proc_Layout **entry_ptr,
 	const char **filename_ptr, int *linenumber_ptr,
 	MR_Word **base_sp_ptr, MR_Word **base_curfr_ptr)
 {
Index: trace/mercury_trace_vars.h
===================================================================
RCS file: /home/mercury1/repository/mercury/trace/mercury_trace_vars.h,v
retrieving revision 1.10
diff -u -b -r1.10 mercury_trace_vars.h
--- trace/mercury_trace_vars.h	2000/10/27 08:38:58	1.10
+++ trace/mercury_trace_vars.h	2001/01/02 07:46:03
@@ -1,5 +1,5 @@
 /*
-** Copyright (C) 1999-2000 The University of Melbourne.
+** Copyright (C) 1999-2001 The University of Melbourne.
 ** This file may only be copied under the terms of the GNU Library General
 ** Public License - see the file COPYING.LIB in the Mercury distribution.
 **
@@ -55,12 +55,12 @@
 } MR_Var_Spec;
 
 extern	void		MR_trace_init_point_vars(
-				const MR_Stack_Layout_Label *top_layout,
+				const MR_Label_Layout *top_layout,
 				MR_Word *saved_regs, MR_Trace_Port port);
 extern	const char	*MR_trace_set_level(int ancestor_level);
 extern	int		MR_trace_current_level(void);
 extern	void		MR_trace_current_level_details(
-				const MR_Stack_Layout_Entry **entry_ptr,
+				const MR_Proc_Layout **entry_ptr,
 				const char **filename_ptr, int *linenumber_ptr,
 				MR_Word **base_sp_ptr, MR_Word **base_curfr_ptr);
 
cvs diff: Diffing trial
cvs diff: Diffing util
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list