for review: a big step towards the trace-based debugger

Zoltan Somogyi zs at cs.mu.OZ.AU
Fri Mar 20 19:32:16 AEDT 1998


Tyson, Fergus, please review this.

This change makes the tracer a lot more useful. The major points are:

- you can now print the values of live variables at all trace ports,
  not just at entry and exit ports;

- you can now print the values of polymorphic variables;

- the implementation now longer saves and restores a thousand pseudo-registers
  unnecessarily;

- you can now execute programs compiled with tracing without user intervention
  if that is what you want.

The last change makes bootstrapping with --generate-trace possible in theory,
although this has not yet been done.

The three major things remaining to be done to make the tracer an adequate
replacement for Prolog debugging are

- a real term browser;

- spy points and other controls;

- being able to trace different modules at different levels
  (full/interface/none).

Two less important things to do are making the representation of typeinfos
themselves type correct :-( and not including (partially) clobbered variables
in trace events.

compiler/arg_info.m:
compiler/code_info.m:
	Move some code that always belonged in arg_info.m to arg_info.m
	from code_info.m.

compiler/code_exprn.m:
	Add a predicate to find out which registers are in use, so the tracer
	can avoid saving and restoring registers that are not use.

compiler/code_gen.m:
	Reorganize the handling of epilogs. Whereas epilogs used to generate
	the failure handling code, this is now done in generate_category_code,
	because failure handling is now complicated by having to save the
	input args for the fail event, and the setup for this naturally
	belongs in generate_category_code.

	Also move the responsibility for the call event to
	generate_category_code.

	Move Tyson's recent additions for tracing to trace.m in a generalized
	form, since they are now needed for all events, not just call and exit.

	Remove obsolete code for eager code generation.

compiler/code_info.m:
	Add a predicate to call the new predicate in code_exprn.

	Export a predicate for trace.m.

	Considerably simplify the treatment of continuation_infos,
	with code_info structures now storing only the stuff that can change
	during code generation (due to trace events).

compiler/code_util.m:
compiler/opt_util.m:
compiler/vn_filter.m:
	Move some code to code_util.m from opt_util.m and generalize it a bit,
	since the new predicate in code_exprn.m now needs the functionality.
	Make vn_filter.m refer to the moved predicates by their new name.

compiler/continuation_info.m:
	Major reorganization and simplification of the data structures.
	The data that changes during code generation is now stored in the
	code generator state; data that is only available after code generation
	is combined with the info from the code generator state and put into
	the HLDS; data that is available only after optimization is put
	directly into the HLDS.

	Do not add continuation_info records for labels that are not used
	either by tracing or by agc. For labels that are used by either,
	always include stack layout information if any variables are live.

compiler/continuation_info.m:
compiler/stack_layout.m:
	Do not associate the stack layout information at procedure entry and
	exit with the per-procedure data structure. Since we now associate this
	info with the labels of those events instead, they do not need special
	handling. However, do include a pointer to the call event's label's
	layout structure in the per-procedure data, so that we can later
	implement redo in the debugger.

compiler/stack_layout.m:
	Handle the possibility that the set of type variables that are needed
	at a point is not numbered 1-N without any missing type var numbers.

compiler/*_switch*.m:
compiler/ite_gen.m:
compiler/disj_gen.m:
compiler/pragma_c_gen.m:
	When creating trace events, associate not just a goal path but
	also a pre-death set with events that represent entry to a computation
	branch. Trace.m now needs the pre-death set so that it can avoid
	trying to flush variables that are not supposed to be live in the
	computation branch being traced.

compiler/handle_options.m:
	Handle some more implications of tracing, and document them better.

compiler/live_vars.m:
compiler/liveness.m:
compiler/store_alloc.m:
	If tracing is on, try to preserve the input arguments throughout
	the execution of the procedure. This is not possible if any part
	of an input argument is clobbered, but in the absence of a utility
	predicate that can test for this, we ignore the issue for now.

compiler/mercury_compile.m:
	Do not invoke continuation_info__process_instructions to add
	stack layout information about call return sites unless we are doing
	agc. (Tracing does not require this info, and it is big.)

compiler/{lambda,polymorphism,goal_util}.m:
	Enforce the invariant that if the signature of a procedure created
	for a lambda goal includes a type variable, it also includes the
	typeinfo for that type variable.

	(This change is from Simon.)

runtime/mercury_regorder.h:
	Add two new macros, MR_NUM_SPECIAL_REG and MR_MAX_SPECIAL_REG_MR
	that mercury_trace.c uses to decide how much fake_reg to save and
	restore.

runtime/mercury_stack_layout.h:
	Change the definition of MR_Var_Shape_Info to reflect the real type
	of one of its fields more closely.

	Make the type names conform to the Mercury style guide
	With_Studly_Cap_Names.

	Fix the definition of MR_DETISM_DET_CODE_MODEL.

runtime/mercury_stack_layout.c:
	Use the new forms of the type names.

runtime/mercury_trace.h:
	Modify the prototype of MR_trace() to reflect the new arg giving
	the number of the highest numbered rN register in use at the call.

runtime/mercury_trace.[ch]:
runtime/mercury_wrapper.c:
	Add support for turning tracing on and off and for choosing the
	external or internal debugger.

runtime/mercury_trace.c:
	Implement a new command set more in line with what we intend to
	grow towards in the future.

	Save/restore only the necessary registers, not all of them.

	Do not indent trace events by the depth, since the depth can get
	very large.

	There is a reference here back to the library, but this will
	go away when the tabling change is committed.

runtime/mercury_trace.[ch]:
	Add a new function, MR_trace_report. This function, which is for
	invocation in the event of a fatal error, reports what the number
	of the last event was (if tracing is enabled). This should allow
	the programmer to go more directly to the source of the problem.

runtime/mercury_wrapper.c:
	Remove the long obsolete code for initializing r[123] with integers.

library/require.m:
	

scripts/mmd:
	A new script for turning on the tracing code in an executable.

scripts/Mmakefile:
	Include mmd in the list of scripts to be installed.

tests/misc_tests/Mmakefile:
tests/misc_tests/debugger_regs.*:
tests/misc_tests/debugger_test.*:
	Move the tests of the debugger to the new tests/debugger directory.
	In the process, give debugger_test back its original name,
	"interpreter", and give it an input script that tests the new
	debugger commands while avoiding the printing of excessively large
	terms.

tests/debugger/Mmakefile:
tests/debugger/runtests:
tests/debugger/debugger_regs.*:
tests/debugger/interpreter.*:
	The moved test cases and copied Mmakefile/runtests.

tests/misc_tests/queens.*:
	A new test case to test the printing of variables in polymorphic
	procedures.

Zoltan.

Index: compiler/arg_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/arg_info.m,v
retrieving revision 1.27
diff -u -r1.27 arg_info.m
--- arg_info.m	1998/03/03 17:33:30	1.27
+++ arg_info.m	1998/03/11 04:56:38
@@ -23,7 +23,7 @@
 :- module arg_info.
 :- interface. 
 :- import_module hlds_module, hlds_pred, llds, globals, prog_data.
-:- import_module bool, list.
+:- import_module bool, list, assoc_list, term.
 
 :- pred generate_arg_info(module_info, module_info).
 :- mode generate_arg_info(in, out) is det.
@@ -45,12 +45,19 @@
 :- pred arg_info__ho_call_args_method(globals, args_method).
 :- mode arg_info__ho_call_args_method(in, out) is det.
 
+	% Given a list of the head variables and their argument information,
+	% return a list giving the input variables and their initial locations.
+:- pred arg_info__build_input_arg_list(assoc_list(var, arg_info),
+	assoc_list(var, rval)).
+:- mode arg_info__build_input_arg_list(in, out) is det.
+
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
 :- implementation.
 
-:- import_module map, int, mode_util, require.
+:- import_module code_util, mode_util.
+:- import_module std_util, map, int, require.
 
 %-----------------------------------------------------------------------------%
 
@@ -224,6 +231,21 @@
 arg_info__args_method_is_ho_callable(_, simple, no).
 
 arg_info__ho_call_args_method(_, compact).
+
+%---------------------------------------------------------------------------%
+
+arg_info__build_input_arg_list([], []).
+arg_info__build_input_arg_list([V - Arg | Rest0], VarArgs) :-
+	Arg = arg_info(Loc, Mode),
+	(
+		Mode = top_in
+	->
+		code_util__arg_loc_to_register(Loc, Reg),
+		VarArgs = [V - lval(Reg) | VarArgs0]
+	;
+		VarArgs = VarArgs0
+	),
+	arg_info__build_input_arg_list(Rest0, VarArgs0).
 
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
Index: compiler/code_exprn.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_exprn.m,v
retrieving revision 1.57
diff -u -r1.57 code_exprn.m
--- code_exprn.m	1998/03/03 17:33:44	1.57
+++ code_exprn.m	1998/03/16 05:09:26
@@ -239,12 +239,18 @@
 :- pred code_exprn__set_follow_vars(follow_vars, exprn_info, exprn_info).
 :- mode code_exprn__set_follow_vars(in, in, out) is det.
 
+%	code_exprn__max_reg_in_use(MaxReg)
+%		Returns the number of the highest numbered rN register in use.
+
+:- pred code_exprn__max_reg_in_use(exprn_info, int).
+:- mode code_exprn__max_reg_in_use(in, out) is det.
+
 %------------------------------------------------------------------------------%
 %------------------------------------------------------------------------------%
 
 :- implementation.
 
-:- import_module exprn_aux, tree.
+:- import_module code_util, exprn_aux, tree.
 :- import_module bool, bag, require, int, term, string, std_util.
 
 :- type var_stat	--->	evaled(set(rval))
@@ -1766,6 +1772,55 @@
 code_exprn__get_var_name(Var, Name) -->
 	code_exprn__get_varset(Varset),
 	{ varset__lookup_name(Varset, Var, Name) }.
+
+%------------------------------------------------------------------------------%
+
+code_exprn__max_reg_in_use(ExprnInfo, Max) :-
+	code_exprn__get_vars(Vars, ExprnInfo, _),
+	map__to_assoc_list(Vars, VarStats),
+	assoc_list__values(VarStats, Stats),
+	code_exprn__max_reg_in_use_vars(Stats, 0, Max1),
+	code_exprn__get_regs(InUseRegs, ExprnInfo, _),
+	bag__to_list_without_duplicates(InUseRegs, IRegs),
+	code_exprn__max_reg_in_use_lvals(IRegs, Max1, Max2),
+	code_exprn__get_acquired(Acquired, ExprnInfo, _),
+	set__to_sorted_list(Acquired, ARegs),
+	code_exprn__max_reg_in_use_lvals(ARegs, Max2, Max).
+
+:- pred code_exprn__max_reg_in_use_vars(list(var_stat), int, int).
+:- mode code_exprn__max_reg_in_use_vars(in, in, out) is det.
+
+code_exprn__max_reg_in_use_vars([], Max, Max).
+code_exprn__max_reg_in_use_vars([Stat | Stats], Max0, Max) :-
+	(
+		Stat = evaled(RvalSet),
+		set__to_sorted_list(RvalSet, Rvals),
+		code_exprn__max_reg_in_use_rvals(Rvals, Max0, Max1)
+	;
+		Stat = cached(Rval),
+		code_exprn__max_reg_in_use_rvals([Rval], Max0, Max1)
+	),
+	code_exprn__max_reg_in_use_vars(Stats, Max1, Max).
+
+:- pred code_exprn__max_reg_in_use_rvals(list(rval), int, int).
+:- mode code_exprn__max_reg_in_use_rvals(in, in, out) is det.
+
+code_exprn__max_reg_in_use_rvals(Rvals, Max0, Max) :-
+	list__map(code_util__lvals_in_rval, Rvals, LvalLists),
+	list__condense(LvalLists, Lvals),
+	code_exprn__max_reg_in_use_lvals(Lvals, Max0, Max).
+
+:- pred code_exprn__max_reg_in_use_lvals(list(lval), int, int).
+:- mode code_exprn__max_reg_in_use_lvals(in, in, out) is det.
+
+code_exprn__max_reg_in_use_lvals(Lvals, Max0, Max) :-
+	list__filter_map(code_exprn__lval_is_r_reg, Lvals, RegNumbers),
+	list__foldl(int__max, RegNumbers, Max0, Max).
+
+:- pred code_exprn__lval_is_r_reg(lval, int).
+:- mode code_exprn__lval_is_r_reg(in, out) is semidet.
+
+code_exprn__lval_is_r_reg(reg(r, N), N).
 
 %------------------------------------------------------------------------------%
 
Index: compiler/code_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_gen.m,v
retrieving revision 1.48
diff -u -r1.48 code_gen.m
--- code_gen.m	1998/03/03 17:33:45	1.48
+++ code_gen.m	1998/03/16 09:25:33
@@ -152,7 +152,6 @@
 	pred_info_procedures(PredInfo, ProcInfos),
 		% locate the proc_info structure for this mode of the predicate
 	map__lookup(ProcInfos, ProcId, ProcInfo),
-		% find out if the proc is deterministic/etc
 	generate_proc_code(ProcInfo, ProcId, PredId, ModuleInfo0, Globals,
 		ContInfo0, CellCount0, ContInfo1, CellCount1, Proc),
 	generate_proc_list_code(ProcIds, PredId, PredInfo, ModuleInfo0,
@@ -187,7 +186,7 @@
 		% get the goal for this procedure
 	proc_info_goal(ProcInfo, Goal),
 		% get the information about this procedure that we need.
-	proc_info_varset(ProcInfo, VarInfo),
+	proc_info_varset(ProcInfo, VarSet),
 	proc_info_liveness_info(ProcInfo, Liveness),
 	proc_info_stack_slots(ProcInfo, StackSlots),
 	proc_info_get_initial_instmap(ProcInfo, ModuleInfo, InitialInst),
@@ -207,21 +206,23 @@
 		SaveSuccip = no
 	),
 		% initialise the code_info structure 
-	code_info__init(VarInfo, Liveness, StackSlots, SaveSuccip, Globals,
+	code_info__init(VarSet, Liveness, StackSlots, SaveSuccip, Globals,
 		PredId, ProcId, ProcInfo, InitialInst, FollowVars,
-		ModuleInfo, CellCount0, ContInfo0, CodeInfo0),
+		ModuleInfo, CellCount0, CodeInfo0),
 		% generate code for the procedure
 	globals__lookup_bool_option(Globals, generate_trace, Trace),
-	( Trace = yes ->
+	code_util__make_proc_label(ModuleInfo, PredId, ProcId, ProcLabel),
+	(
+		Trace = yes
+	->
 		trace__setup(CodeInfo0, CodeInfo1)
 	;
 		CodeInfo1 = CodeInfo0
 	),
-	generate_category_code(CodeModel, Goal, CodeTree, FrameInfo,
-		CodeInfo1, CodeInfo),
+	generate_category_code(CodeModel, Goal, ProcInfo, CodeTree,
+		MaybeTraceCallLabel, FrameInfo, CodeInfo1, CodeInfo),
 		% extract the new continuation_info and cell count
-	code_info__get_continuation_info(ContInfo1, CodeInfo, _CodeInfo1),
-	code_info__get_cell_count(CellCount, CodeInfo, _CodeInfo2),
+	code_info__get_cell_count(CellCount, CodeInfo, _CodeInfo1),
 
 		% turn the code tree into a list
 	tree__flatten(CodeTree, FragmentList),
@@ -238,13 +239,12 @@
 		Instructions = Instructions0
 	),
 	( BasicStackLayout = yes ->
-		code_util__make_proc_label(ModuleInfo, PredId, ProcId,
-			ProcLabel),
-		continuation_info__add_proc_layout_info(proc(PredId, ProcId),
+		code_info__get_layout_info(LayoutInfo, CodeInfo, _CodeInfo2),
+		continuation_info__add_proc_info(proc(PredId, ProcId),
 			ProcLabel, TotalSlots, Detism, MaybeSuccipSlot,
-			ContInfo1, ContInfo)
+			MaybeTraceCallLabel, LayoutInfo, ContInfo0, ContInfo)
 	;
-		ContInfo = ContInfo1
+		ContInfo = ContInfo0
 	),
 
 		% get the name and arity of this predicate
@@ -253,11 +253,58 @@
 		% construct a c_procedure structure with all the information
 	Proc = c_procedure(Name, Arity, proc(PredId, ProcId), Instructions).
 
-:- pred generate_category_code(code_model, hlds_goal, code_tree, frame_info,
-				code_info, code_info).
-:- mode generate_category_code(in, in, out, out, in, out) is det.
+%---------------------------------------------------------------------------%
+
+	% Generate_category_code generates code for an entire procedure.
+	% Its algorithm has three main stages:
+	%
+	%	- generate code for the body goal
+	%	- generate code for the prologue
+	%	- generate code for the epilogue
+	%
+	% The only caller of generate_category_code, generate_proc_code,
+	% has set up the code generator state to reflect what the machine
+	% state will be on entry to the procedure. Ensuring that the
+	% machine state at exit/fail will conform to the expectation
+	% of the caller is the job of the epilogue.
+	%
+	% The reason why we generate the prologue after the body is that
+	% information such as the total number of stack slots needed,
+	% which is needed when creating the prologue, cannot be conveniently
+	% obtained before generating the body, since the code generator
+	% may allocate temporary variables to hold values such as saved
+	% heap and trail pointers.
+	%
+	% Code_gen__generate_prologue cannot depend on the code generator
+	% state, since when it is invoked this state is not appropriate
+	% for the prologue. Nor can it change the code generator state,
+	% since that would confuse code_gen__generate_epilogue.
+	%
+	% Generating CALL trace events is done by generate_category_code,
+	% since only on entry to generate_category_code is the code generator
+	% state set up right. Generating EXIT trace events is done by
+	% code_gen__generate_exit, since the epilogue takes care of the
+	% successes of all procedures of all three code models.
+	% Generating FAIL trace events is done by generate_category_code,
+	% since this requires modifying how we generate code for the body
+	% of the procedure (failures must now branch to a different place).
+	% Since FAIL trace events are part of the failure continuation,
+	% generate_category_code takes care of the failure continuation
+	% as well. (Det procedures of course have no failure continuation.
+	% Nondet procedures have a failure continuation, but in the absence
+	% of tracing this continuation needs no code. Only semidet procedures
+	% need code for the failure continuation at all times.)
+	% code_gen__generate_epilogue.
+	%
+	% Procedures defined by nondet pragma C codes are a special case.
+	% Pragma_c_gen__generate_pragma_c_code handles XXX
+
+:- pred generate_category_code(code_model, hlds_goal, proc_info, code_tree,
+	maybe(label), frame_info, code_info, code_info).
+:- mode generate_category_code(in, in, in, out, out, out, in, out) is det.
 
-generate_category_code(model_det, Goal, Code, FrameInfo) -->
+generate_category_code(model_det, Goal, ProcInfo, Code,
+		MaybeTraceCallLabel, FrameInfo) -->
 		% generate the code for the body of the clause
 	(
 		code_info__get_globals(Globals),
@@ -265,6 +312,7 @@
 		middle_rec__match_and_generate(Goal, MiddleRecCode)
 	->
 		{ Code = MiddleRecCode },
+		{ MaybeTraceCallLabel = no },
 		{ FrameInfo = frame(0, no, no) }
 	;
 		% make a new failure cont (not model_non);
@@ -272,83 +320,147 @@
 		% but is a place holder
 		code_info__manufacture_failure_cont(no),
 
-		code_gen__generate_goal(model_det, Goal, BodyCode),
-		code_info__get_instmap(Instmap),
-
-		code_gen__generate_prolog(model_det, Goal, FrameInfo,
-			PrologCode),
-		(
-			{ instmap__is_reachable(Instmap) }
-		->
-			code_gen__generate_epilog(model_det,
-				FrameInfo, EpilogCode)
+		code_info__get_maybe_trace_info(MaybeTraceInfo),
+		( { MaybeTraceInfo = yes(TraceInfo) } ->
+			{ trace__fail_vars(ProcInfo, ResumeVars) },
+				% Protect these vars from being forgotten,
+				% so they will be around for the exit trace.
+			code_info__push_resume_point_vars(ResumeVars),
+			trace__generate_event_code(call, TraceInfo,
+				TraceCallLabel, _TypeInfos, TraceCallCode),
+			{ MaybeTraceCallLabel = yes(TraceCallLabel) }
 		;
-			{ EpilogCode = empty }
+			{ TraceCallCode = empty },
+			{ MaybeTraceCallLabel = no }
 		),
-
-		{ Code = tree(PrologCode, tree(BodyCode, EpilogCode)) }
+		code_gen__generate_goal(model_det, Goal, BodyCode),
+		code_gen__generate_entry(model_det, Goal, FrameInfo,
+			EntryCode),
+		code_gen__generate_exit(model_det, FrameInfo, _, ExitCode),
+		{ Code =
+			tree(EntryCode,
+			tree(TraceCallCode,
+			tree(BodyCode,
+			     ExitCode)))
+		}
 	).
 
-generate_category_code(model_semi, Goal, Code, FrameInfo) -->
+generate_category_code(model_semi, Goal, ProcInfo, Code,
+		MaybeTraceCallLabel, FrameInfo) -->
 		% make a new failure cont (not model_non)
 	code_info__manufacture_failure_cont(no),
+	code_info__get_maybe_trace_info(MaybeTraceInfo),
+	{ set__singleton_set(FailureLiveRegs, reg(r, 1)) },
+	{ FailCode = node([
+		assign(reg(r, 1), const(false)) - "Fail",
+		livevals(FailureLiveRegs) - "",
+		goto(succip) - "Return from procedure call"
+	]) },
+	( { MaybeTraceInfo = yes(TraceInfo) } ->
+		{ trace__fail_vars(ProcInfo, ResumeVars) },
+		code_info__make_known_failure_cont(ResumeVars, orig_and_stack,
+			no, SetupCode),
+		code_info__push_resume_point_vars(ResumeVars),
+		trace__generate_event_code(call, TraceInfo,
+			TraceCallLabel, _TypeInfos, TraceCallCode),
+		{ MaybeTraceCallLabel = yes(TraceCallLabel) },
+		code_gen__generate_goal(model_semi, Goal, BodyCode),
+		code_gen__generate_entry(model_semi, Goal, FrameInfo,
+			EntryCode),
+		code_gen__generate_exit(model_semi, FrameInfo,
+			RestoreDeallocCode, ExitCode),
+		code_info__pop_resume_point_vars,
+		code_info__restore_failure_cont(ResumeCode),
+		code_info__set_forward_live_vars(ResumeVars),
+		trace__generate_event_code(fail, TraceInfo, TraceFailCode),
+		{ Code =
+			tree(EntryCode,
+			tree(SetupCode,
+			tree(TraceCallCode,
+			tree(BodyCode,
+			tree(ExitCode,
+			tree(ResumeCode,
+			tree(TraceFailCode,
+			tree(RestoreDeallocCode,
+			     FailCode))))))))
+		}
+	;
+		{ MaybeTraceCallLabel = no },
+		code_gen__generate_goal(model_semi, Goal, BodyCode),
+		code_gen__generate_entry(model_semi, Goal, FrameInfo,
+			EntryCode),
+		code_gen__generate_exit(model_semi, FrameInfo,
+			RestoreDeallocCode, ExitCode),
+		code_info__restore_failure_cont(ResumeCode),
+		{ Code =
+			tree(EntryCode,
+			tree(BodyCode,
+			tree(ExitCode,
+			tree(ResumeCode,
+			tree(RestoreDeallocCode,
+			     FailCode)))))
+		}
+	).
 
-		% generate the code for the body of the clause
-	code_gen__generate_goal(model_semi, Goal, BodyCode),
-	code_gen__generate_prolog(model_semi, Goal, FrameInfo, PrologCode),
-	code_gen__generate_epilog(model_semi, FrameInfo, EpilogCode),
-	{ Code = tree(PrologCode, tree(BodyCode, EpilogCode)) }.
-
-generate_category_code(model_non, Goal, Code, FrameInfo) -->
+generate_category_code(model_non, Goal, ProcInfo, Code,
+		MaybeTraceCallLabel, FrameInfo) -->
 		% make a new failure cont (yes, it is model_non)
 	code_info__manufacture_failure_cont(yes),
 		% we must arrange the tracing of failure out of this proc
 	code_info__get_maybe_trace_info(MaybeTraceInfo),
 	( { MaybeTraceInfo = yes(TraceInfo) } ->
-		{ set__init(ResumeVars) },
-		code_info__make_known_failure_cont(ResumeVars, stack_only, yes,
-			SetupCode),
-
-			% generate the code for the body of the clause
+		{ trace__fail_vars(ProcInfo, ResumeVars) },
+		code_info__make_known_failure_cont(ResumeVars, orig_and_stack,
+			yes, SetupCode),
 		code_info__push_resume_point_vars(ResumeVars),
+		trace__generate_event_code(call, TraceInfo,
+			TraceCallLabel, _TypeInfos, TraceCallCode),
+		{ MaybeTraceCallLabel = yes(TraceCallLabel) },
 		code_gen__generate_goal(model_non, Goal, BodyCode),
-		code_gen__generate_prolog(model_non, Goal, FrameInfo,
+		code_gen__generate_entry(model_non, Goal, FrameInfo,
 			PrologCode),
-		code_gen__generate_epilog(model_non, FrameInfo, EpilogCode),
-		{ MainCode = tree(PrologCode, tree(BodyCode, EpilogCode)) },
+		code_gen__generate_exit(model_non, FrameInfo, _, EpilogCode),
 
 		code_info__pop_resume_point_vars,
 		code_info__restore_failure_cont(RestoreCode),
-		trace__generate_event_code(fail, TraceInfo, TraceEventCode),
+		code_info__set_forward_live_vars(ResumeVars),
+		trace__generate_event_code(fail, TraceInfo, TraceFailCode),
 		code_info__generate_failure(FailCode),
 		{ Code =
-			tree(MainCode,
+			tree(PrologCode,
 			tree(SetupCode,
+			tree(TraceCallCode,
+			tree(BodyCode,
+			tree(EpilogCode,
 			tree(RestoreCode,
-			tree(TraceEventCode,
-			     FailCode))))
+			tree(TraceFailCode,
+			     FailCode)))))))
 		}
 	;
-			% generate the code for the body of the clause
+		{ MaybeTraceCallLabel = no },
 		code_gen__generate_goal(model_non, Goal, BodyCode),
-		code_gen__generate_prolog(model_non, Goal, FrameInfo,
+		code_gen__generate_entry(model_non, Goal, FrameInfo,
 			PrologCode),
-		code_gen__generate_epilog(model_non, FrameInfo, EpilogCode),
-		{ Code = tree(PrologCode, tree(BodyCode, EpilogCode)) }
+		code_gen__generate_exit(model_non, FrameInfo, _, EpilogCode),
+		{ Code =
+			tree(PrologCode,
+			tree(BodyCode,
+			     EpilogCode))
+		}
 	).
 
 %---------------------------------------------------------------------------%
 
-	% Generate the prolog for a procedure.
+	% Generate the prologue for a procedure.
 	%
-	% The prolog will contain
+	% The prologue will contain
 	%
-	%	a comment to mark prolog start
+	%	a comment to mark prologue start
 	%	a comment explaining the stack layout
 	%	the procedure entry label
 	%	code to allocate a stack frame
 	%	code to fill in some special slots in the stack frame
-	%	a comment to mark prolog end
+	%	a comment to mark prologue end
 	%
 	% At the moment the only special slot is the succip slot.
 	%
@@ -357,11 +469,11 @@
 	% need a stack frame, and if the procedure is nondet, then the code
 	% to fill in the succip slot is subsumed by the mkframe.
 
-:- pred code_gen__generate_prolog(code_model, hlds_goal, frame_info, code_tree, 
-	code_info, code_info).
-:- mode code_gen__generate_prolog(in, in, out, out, in, out) is det.
+:- pred code_gen__generate_entry(code_model, hlds_goal, frame_info,
+	code_tree, code_info, code_info).
+:- mode code_gen__generate_entry(in, in, out, out, in, out) is det.
 
-code_gen__generate_prolog(CodeModel, Goal, FrameInfo, PrologCode) -->
+code_gen__generate_entry(CodeModel, Goal, FrameInfo, PrologCode) -->
 	code_info__get_stack_slots(StackSlots),
 	code_info__get_varset(VarSet),
 	{ code_aux__explain_stack_slots(StackSlots, VarSet, SlotsComment) },
@@ -399,38 +511,9 @@
 	),
 	code_info__get_maybe_trace_info(MaybeTraceInfo),
 	( { MaybeTraceInfo = yes(TraceInfo) } ->
-		{ trace__generate_slot_fill_code(TraceInfo, TraceFillCode) },
-		trace__generate_event_code(call, TraceInfo, TraceEventCode),
-		{ TraceCode = tree(TraceFillCode, TraceEventCode) }
-	;
-		{ TraceCode = empty }
-	),
-
-		% Generate live value information and put
-		% it into the continuation info if we are doing
-		% execution tracing.
-	code_info__get_globals(Globals),
-	(
-		{ globals__lookup_bool_option(Globals, trace_stack_layout,
-			yes) }
-	->
-		code_info__get_arginfo(ArgModes),
-		code_info__get_headvars(HeadVars),
-		{ assoc_list__from_corresponding_lists(HeadVars, ArgModes,
-			Args) },
-		{ code_gen__select_args_with_mode(Args, top_in, InVars,
-			InLvals) },
-
-		code_gen__generate_var_infos(InVars, InLvals, VarInfos),
-		code_gen__generate_typeinfos_on_entry(InVars, InLvals,
-			TypeInfos),
-		
-		code_info__get_continuation_info(ContInfo0),
-		{ continuation_info__add_proc_entry_info(proc(PredId, ProcId),
-			VarInfos, TypeInfos, ContInfo0, ContInfo) },
-		code_info__set_continuation_info(ContInfo)
+		{ trace__generate_slot_fill_code(TraceInfo, TraceFillCode) }
 	;
-		[]
+		{ TraceFillCode = empty }
 	),
 
 	{ predicate_module(ModuleInfo, PredId, ModuleName) },
@@ -492,28 +575,23 @@
 		tree(LabelCode,
 		tree(AllocCode,
 		tree(SaveSuccipCode,
-		tree(TraceCode,
+		tree(TraceFillCode,
 		     EndComment)))))
 	}.
 
 %---------------------------------------------------------------------------%
 
-	% Generate the epilog for a procedure.
+	% Generate the success epilogue for a procedure.
 	%
-	% The epilog will contain
+	% The epilogue will contain
 	%
-	%	a comment to mark epilog start
+	%	a comment to mark epilogue start
 	%	code to place the output arguments where their caller expects
-	%	the success continuation
-	%	the faulure continuation (for semidet procedures only)
-	%	a comment to mark epilog end.
-	%
-	% The success continuation will contain
-	%
 	%	code to restore registers from some special slots
 	%	code to deallocate the stack frame
 	%	code to set r1 to TRUE (for semidet procedures only)
 	%	a jump back to the caller, including livevals information
+	%	a comment to mark epilogue end
 	%
 	% The failure continuation will contain
 	%
@@ -523,7 +601,8 @@
 	%	code to set r1 to FALSE
 	%	a jump back to the caller, including livevals information
 	%
-	% At the moment the only special slot is the succip slot.
+	% At the moment the only special slots are the succip slot, and
+	% the slots holding the call number and call depth for tracing.
 	%
 	% Not all frames will have all these components. For example, for
 	% nondet procedures we don't deallocate the stack frame before
@@ -531,14 +610,15 @@
 	%
 	% Epilogs for procedures defined by nondet pragma C codes do not
 	% follow the rules above. For such procedures, the normal functions
-	% of the epilog are handled when traversing the pragma C code goal;
-	% we need only #undef a macro defined by the procedure prolog.
+	% of the epilogue are handled when traversing the pragma C code goal;
+	% we need only #undef a macro defined by the procedure prologue.
 
-:- pred code_gen__generate_epilog(code_model, frame_info, code_tree,
+:- pred code_gen__generate_exit(code_model, frame_info, code_tree, code_tree,
 	code_info, code_info).
-:- mode code_gen__generate_epilog(in, in, out, in, out) is det.
+:- mode code_gen__generate_exit(in, in, out, out, in, out) is det.
 
-code_gen__generate_epilog(CodeModel, FrameInfo, EpilogCode) -->
+code_gen__generate_exit(CodeModel, FrameInfo, RestoreDeallocCode, EpilogCode)
+		-->
 	{ StartComment = node([
 		comment("Start of procedure epilogue") - ""
 	]) },
@@ -554,6 +634,7 @@
 				will_not_call_mercury, no)
 				- ""
 		]) },
+		{ RestoreDeallocCode = empty }, % XXX
 		{ EpilogCode =
 			tree(StartComment,
 			tree(UndefCode,
@@ -592,51 +673,25 @@
 			]) }
 		),
 		{ RestoreDeallocCode = tree(RestoreSuccipCode, DeallocCode ) },
+
 		code_info__get_maybe_trace_info(MaybeTraceInfo),
 		( { MaybeTraceInfo = yes(TraceInfo) } ->
 			trace__generate_event_code(exit, TraceInfo,
-				SuccessTraceCode),
-			( { CodeModel = model_semi } ->
-				trace__generate_event_code(fail, TraceInfo,
-					FailureTraceCode)
-			;
-				{ FailureTraceCode = empty }
-			)
+				_, TypeInfoDatas, TraceExitCode),
+			{ assoc_list__values(TypeInfoDatas, TypeInfoLvals) }
 		;
-			{ SuccessTraceCode = empty },
-			{ FailureTraceCode = empty }
+			{ TraceExitCode = empty },
+			{ TypeInfoLvals = [] }
 		),
-			% Generate live value information and put
-			% it into the continuation info if we are doing
-			% execution tracing.
-		{ code_gen__select_args_with_mode(Args, top_out, OutVars,
+
+			% Find out which locations should be mentioned
+			% in the success path livevals(...) annotation,
+			% so that value numbering doesn't optimize them away.
+		{ code_gen__select_args_with_mode(Args, top_out, _OutVars,
 			OutLvals) },
-		code_info__get_globals(Globals),
-		(
-			{ globals__lookup_bool_option(Globals,
-				trace_stack_layout, yes) }
-		->
-			code_gen__generate_var_infos(OutVars, OutLvals,
-				VarInfos),
-			code_gen__generate_typeinfos_on_exit(OutVars,
-				TypeInfos),
-			code_info__get_continuation_info(ContInfo0),
-			code_info__get_pred_id(PredId),
-			code_info__get_proc_id(ProcId),
-			{ continuation_info__add_proc_exit_info(
-				proc(PredId, ProcId), VarInfos, TypeInfos,
-				ContInfo0, ContInfo) },
-			code_info__set_continuation_info(ContInfo),
-
-				% Make sure typeinfos are in livevals(...)
-				% so that value numbering doesn't mess
-				% with them.
-			{ assoc_list__values(TypeInfos, ExtraLvals) },
-			{ list__append(ExtraLvals, OutLvals, LiveArgLvals) }
-		;
-			{ LiveArgLvals = OutLvals }
-		),
+		{ list__append(TypeInfoLvals, OutLvals, LiveArgLvals) },
 		{ set__list_to_set(LiveArgLvals, LiveArgs) },
+
 		(
 			{ CodeModel = model_det },
 			{ SuccessCode = node([
@@ -644,14 +699,12 @@
 				goto(succip) - "Return from procedure call"
 			]) },
 			{ AllSuccessCode =
-				tree(SuccessTraceCode,
+				tree(TraceExitCode,
 				tree(RestoreDeallocCode,
 				     SuccessCode))
-			},
-			{ AllFailureCode = empty }
+			}
 		;
 			{ CodeModel = model_semi },
-			code_info__restore_failure_cont(ResumeCode),
 			{ set__insert(LiveArgs, reg(r, 1), SuccessLiveRegs) },
 			{ SuccessCode = node([
 				assign(reg(r, 1), const(true)) - "Succeed",
@@ -659,21 +712,9 @@
 				goto(succip) - "Return from procedure call"
 			]) },
 			{ AllSuccessCode =
-				tree(SuccessTraceCode,
+				tree(TraceExitCode,
 				tree(RestoreDeallocCode,
 				     SuccessCode))
-			},
-			{ set__singleton_set(FailureLiveRegs, reg(r, 1)) },
-			{ FailureCode = node([
-				assign(reg(r, 1), const(false)) - "Fail",
-				livevals(FailureLiveRegs) - "",
-				goto(succip) - "Return from procedure call"
-			]) },
-			{ AllFailureCode =
-				tree(ResumeCode,
-				tree(FailureTraceCode,
-				tree(RestoreDeallocCode,
-				     FailureCode)))
 			}
 		;
 			{ CodeModel = model_non },
@@ -683,105 +724,20 @@
 					- "Return from procedure call"
 			]) },
 			{ AllSuccessCode =
-				tree(SuccessTraceCode,
+				tree(TraceExitCode,
 				     SuccessCode)
-			},
-			{ AllFailureCode = empty }
+			}
 		),
 		{ EpilogCode =
 			tree(StartComment,
 			tree(FlushCode,
 			tree(AllSuccessCode,
-			tree(AllFailureCode,
-			     EndComment))))
+			     EndComment)))
 		}
 	).
 
 %---------------------------------------------------------------------------%
 
-	% Generate the list of lval - live_value_type pairs for the
-	% the given variables.
-
-:- pred code_gen__generate_var_infos(list(var), list(lval),
-		list(var_info), code_info, code_info).
-:- mode code_gen__generate_var_infos(in, in, out, in, out) is det.
-code_gen__generate_var_infos(Vars, Lvals, VarInfos) -->
-		% Add the variable names, insts, types and lvals.
-	code_info__get_varset(VarSet),
-	code_info__get_instmap(InstMap),
-	{ map__from_corresponding_lists(Vars, Lvals, VarLvalMap) },
-	=(CodeInfo),
-	{ MakeVarInfo = lambda([Var::in, VarInfo::out] is det, (
-		map__lookup(VarLvalMap, Var, Lval),
-		code_info__variable_type(Var, Type, CodeInfo, _),
-		instmap__lookup_var(InstMap, Var, Inst),
-		LiveType = var(Type, Inst),
-		varset__lookup_name(VarSet, Var, "V_", Name),
-		VarInfo = var_info(Lval, LiveType, Name)
-	)) }, 
-	{ list__map(MakeVarInfo, Vars, VarInfos) }.
-
-
-	% Generate the tvar - lval pairs for the typeinfos of the
-	% given variables on entry to the procedure (we find the
-	% lval location by looking in the input registers).
-	
-:- pred code_gen__generate_typeinfos_on_entry(list(var), list(lval),
-		assoc_list(tvar, lval), code_info, code_info).
-:- mode code_gen__generate_typeinfos_on_entry(in, in, out, in, out) is det.
-code_gen__generate_typeinfos_on_entry(Vars, Lvals, TypeInfos) -->
-
-	code_gen__find_typeinfos_for_vars(Vars, TVars, TypeInfoVars),
-
-		% Find the locations of the TypeInfoVars.
-	{ map__from_corresponding_lists(Vars, Lvals, VarLvalMap) },
-	{ map__apply_to_list(TypeInfoVars, VarLvalMap, TypeInfoLvals) },
-	{ assoc_list__from_corresponding_lists(TVars, TypeInfoLvals,
-		TypeInfos) }.
-
-	% Generate the tvar - lval pairs for the typeinfos of the
-	% given variables on exit from the procedure (we use code_exprn
-	% to find the lvals).
-
-:- pred code_gen__generate_typeinfos_on_exit(list(var), assoc_list(var, lval),
-		code_info, code_info).
-:- mode code_gen__generate_typeinfos_on_exit(in, out, in, out) is det.
-code_gen__generate_typeinfos_on_exit(Vars, TypeInfos) -->
-
-	code_gen__find_typeinfos_for_vars(Vars, TVars, TypeInfoVars),
-
-		% Find the locations of the TypeInfoVars.
-	code_info__variable_locations(VarLocs),
-	{ map__apply_to_list(TypeInfoVars, VarLocs, TypeInfoLvalSets) },
-	{ FindSingleLval = lambda([Set::in, Lval::out] is det, (
-		(
-			set__remove_least(Set, Value, _),
-			Value = lval(Lval0)
-		->
-			Lval = Lval0
-		;
-			error("code_gen__generate_typeinfos_on_exit: typeinfo var not available")
-		))) },
-	{ list__map(FindSingleLval, TypeInfoLvalSets, TypeInfoLvals) },
-	{ assoc_list__from_corresponding_lists(TVars, TypeInfoLvals,
-		TypeInfos) }.
-
-:- pred code_gen__find_typeinfos_for_vars(list(var), list(tvar), list(var),
-		code_info, code_info).
-:- mode code_gen__find_typeinfos_for_vars(in, out, out, in, out) is det.
-code_gen__find_typeinfos_for_vars(Vars, TypeVars, TypeInfoVars) -->
-		% Find the TypeInfo variables
-	list__map_foldl(code_info__variable_type, Vars, Types),
-	{ list__map(type_util__vars, Types, TypeVarsList) },
-	{ list__condense(TypeVarsList, TypeVars0) },
-	{ list__sort_and_remove_dups(TypeVars0, TypeVars) },
-        code_info__get_proc_info(ProcInfo),
-	{ proc_info_typeinfo_varmap(ProcInfo, TypeInfoMap) },
-	{ map__apply_to_list(TypeVars, TypeInfoMap, TypeInfoLocns) },
-	{ list__map(type_info_locn_var, TypeInfoLocns, TypeInfoVars) }.
-
-%---------------------------------------------------------------------------%
-
 % Generate a goal. This predicate arranges for the necessary updates of
 % the generic data structures before and after the actual code generation,
 % which is delegated to context-specific predicates.
@@ -801,12 +757,12 @@
 		{ goal_info_get_code_model(GoalInfo, CodeModel) },
 		(
 			{ CodeModel = model_det },
-			code_gen__generate_det_goal_2(Goal, GoalInfo, Code0)
+			code_gen__generate_det_goal_2(Goal, GoalInfo, Code)
 		;
 			{ CodeModel = model_semi },
 			( { ContextModel \= model_det } ->
 				code_gen__generate_semi_goal_2(Goal, GoalInfo,
-					Code0)
+					Code)
 			;
 				{ error("semidet model in det context") }
 			)
@@ -814,7 +770,7 @@
 			{ CodeModel = model_non },
 			( { ContextModel = model_non } ->
 				code_gen__generate_non_goal_2(Goal, GoalInfo,
-					Code0)
+					Code)
 			;
 				{ error("nondet model in det/semidet context") }
 			)
@@ -822,17 +778,7 @@
 			% Make live any variables which subsequent goals
 			% will expect to be live, but were not generated
 		code_info__set_instmap(Instmap),
-		code_info__post_goal_update(GoalInfo),
-		code_info__get_globals(Options),
-		(
-			{ globals__lookup_bool_option(Options, lazy_code, yes) }
-		->
-			{ Code1 = empty }
-		;
-			{ error("Eager code unavailable") }
-%%%			code_info__generate_eager_flush(Code1)
-		),
-		{ Code = tree(Code0, Code1) }
+		code_info__post_goal_update(GoalInfo)
 	;
 		{ Code = empty }
 	),
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.218
diff -u -r1.218 code_info.m
--- code_info.m	1998/03/03 17:33:48	1.218
+++ code_info.m	1998/03/16 04:51:03
@@ -41,7 +41,7 @@
 :- implementation.
 
 :- import_module code_util, code_exprn, prog_out.
-:- import_module type_util, mode_util, options.
+:- import_module arg_info, type_util, mode_util, options.
 
 :- import_module set, varset, stack.
 :- import_module string, require, char, bimap, tree, int.
@@ -68,8 +68,8 @@
 		% Create a new code_info structure.
 :- pred code_info__init(varset, set(var), stack_slots, bool, globals,
 	pred_id, proc_id, proc_info, instmap, follow_vars, module_info,
-	int /* cell number */, continuation_info, code_info).
-:- mode code_info__init(in, in, in, in, in, in, in, in, in, in, in, in, in,
+	int /* cell number */, code_info).
+:- mode code_info__init(in, in, in, in, in, in, in, in, in, in, in, in,
 	out) is det.
 
 		% Get the variables for the current procedure.
@@ -118,13 +118,9 @@
 :- pred code_info__get_globals(globals, code_info, code_info).
 :- mode code_info__get_globals(out, in, out) is det.
 
-:- pred code_info__get_continuation_info(continuation_info, 
+:- pred code_info__get_layout_info(map(label, internal_layout_info), 
 		code_info, code_info).
-:- mode code_info__get_continuation_info(out, in, out) is det.
-
-:- pred code_info__set_continuation_info(continuation_info, 
-		code_info, code_info).
-:- mode code_info__set_continuation_info(in, in, out) is det.
+:- mode code_info__get_layout_info(out, in, out) is det.
 
 :- pred code_info__get_maybe_trace_info(maybe(trace_info),
 		code_info, code_info).
@@ -185,6 +181,10 @@
 	code_info, code_info).
 :- mode code_info__set_temps_in_use(in, in, out) is det.
 
+:- pred code_info__set_layout_info(map(label, internal_layout_info), 
+		code_info, code_info).
+:- mode code_info__set_layout_info(in, in, out) is det.
+
 :- pred code_info__get_zombies(set(var), code_info, code_info).
 :- mode code_info__get_zombies(out, in, out) is det.
 
@@ -240,10 +240,10 @@
 			map(lval, slot_contents),
 					% The temp locations in use on the stack
 					% and what they contain (for gc).
-			continuation_info,	
+			map(label, internal_layout_info),	
 					% Information on which values
-					% are live at continuation
-					% points, for accurate gc.
+					% are live and where at which labels,
+					% for tracing and/or accurate gc.
 			set(var),	% Zombie variables; variables that have
 					% been killed but are protected by a
 					% resume point.
@@ -287,11 +287,11 @@
 
 code_info__init(Varset, Liveness, StackSlots, SaveSuccip, Globals,
 		PredId, ProcId, ProcInfo, Requests, FollowVars,
-		ModuleInfo, CellCount, Shapes, C) :-
+		ModuleInfo, CellCount, C) :-
 	proc_info_headvars(ProcInfo, HeadVars),
 	proc_info_arg_info(ProcInfo, ArgInfos),
 	assoc_list__from_corresponding_lists(HeadVars, ArgInfos, Args),
-	code_info__build_input_arg_list(Args, ArgList),
+	arg_info__build_input_arg_list(Args, ArgList),
 	globals__get_options(Globals, Options),
 	code_exprn__init_state(ArgList, Varset, StackSlots, FollowVars,
 		Options, ExprnInfo),
@@ -300,6 +300,7 @@
 	set__init(AvailSlots0),
 	map__init(TempsInUse0),
 	set__init(Zombies0),
+	map__init(Shapes),
 	code_info__max_var_slot(StackSlots, VarSlotCount0),
 	proc_info_interface_code_model(ProcInfo, CodeModel),
 	(
@@ -334,24 +335,6 @@
 		no
 	).
 
-	% XXX This should be in arg_info.m.
-:- pred code_info__build_input_arg_list(assoc_list(var, arg_info),
-	assoc_list(var, rval)).
-:- mode code_info__build_input_arg_list(in, out) is det.
-
-code_info__build_input_arg_list([], []).
-code_info__build_input_arg_list([V - Arg | Rest0], VarArgs) :-
-	Arg = arg_info(Loc, Mode),
-	(
-		Mode = top_in
-	->
-		code_util__arg_loc_to_register(Loc, Reg),
-		VarArgs = [V - lval(Reg) | VarArgs0]
-	;
-		VarArgs = VarArgs0
-	),
-	code_info__build_input_arg_list(Rest0, VarArgs0).
-
 %---------------------------------------------------------------------------%
 
 code_info__get_var_slot_count(A, CI, CI) :-
@@ -422,7 +405,7 @@
 	CI = code_info(_, _, _, _, _, _, _, _, _, _, _, _, _, _, _, _, Q, _, _,
 		_, _, _).
 
-code_info__get_continuation_info(R, CI, CI) :-
+code_info__get_layout_info(R, CI, CI) :-
 	CI = code_info(_, _, _, _, _, _, _, _, _, _, _, _, _, _, _, _, _, R, _,
 		_, _, _).
 
@@ -475,10 +458,10 @@
 %	Q		map(lval, slot_contents),
 %					% The temp locations in use on the stack
 %					% and what they contain (for gc).
-%	R		continuation_info,	
+%	R		map(label, internal_layout_info),	
 %					% Information on which values
-%					% are live at continuation
-%					% points, for accurate gc.
+%					% are live and where at which labels,
+%					% for tracing and/or accurate gc.
 %	S		set(var),	% Zombie variables; variables that have
 %					% been killed but are protected by a
 %					% resume point.
@@ -581,7 +564,7 @@
 	CI = code_info(A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q,
 		R, S, T, U, V).
 
-code_info__set_continuation_info(R, CI0, CI) :-
+code_info__set_layout_info(R, CI0, CI) :-
 	CI0 = code_info(A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q,
 		_, S, T, U, V),
 	CI = code_info(A, B, C, D, E, F, G, H, I, J, K, L, M, N, O, P, Q,
@@ -731,6 +714,10 @@
 :- pred code_info__succip_is_used(code_info, code_info).
 :- mode code_info__succip_is_used(in, out) is det.
 
+:- pred code_info__add_layout_for_label(label, internal_layout_info,
+	code_info, code_info).
+:- mode code_info__add_layout_for_label(in, in, in, out) is det.
+
 %---------------------------------------------------------------------------%
 
 :- implementation.
@@ -967,12 +954,11 @@
 	code_info__set_fail_stack(J, C3, C4),
 	code_info__get_max_temp_slot_count(PC, C1, _),
 	code_info__set_max_temp_slot_count(PC, C4, C5),
-	code_info__get_continuation_info(ContInfo, C1, _),
-	code_info__set_continuation_info(ContInfo, C5, C6),
+	code_info__get_layout_info(LayoutInfo, C1, _),
+	code_info__set_layout_info(LayoutInfo, C5, C6),
 	code_info__get_cell_count(CellCount, C1, _),
 	code_info__set_cell_count(CellCount, C6, C).
 
-
 code_info__apply_instmap_delta(Delta) -->
 	code_info__get_instmap(InstMap0),
 	{ instmap__apply_instmap_delta(InstMap0, Delta, InstMap) },
@@ -1014,6 +1000,15 @@
 code_info__succip_is_used -->
 	code_info__set_succip_used(yes).
 
+code_info__add_layout_for_label(Label, LayoutInfo) -->
+	code_info__get_layout_info(Internals0),
+	( { map__contains(Internals0, Label) } ->
+		{ error("adding layout for already known label") }
+	;
+		{ map__det_insert(Internals0, Label, LayoutInfo, Internals) },
+		code_info__set_layout_info(Internals)
+	).
+
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
 
@@ -2504,6 +2499,11 @@
 	code_info, code_info).
 :- mode code_info__produce_variable_in_reg(in, out, out, in, out) is det.
 
+:- pred code_info__produce_variable_in_reg_or_stack(var, code_tree, rval,
+	code_info, code_info).
+:- mode code_info__produce_variable_in_reg_or_stack(in, out, out, in, out)
+	is det.
+
 :- pred code_info__materialize_vars_in_rval(rval, rval, code_tree, code_info,
 	code_info).
 :- mode code_info__materialize_vars_in_rval(in, out, out, in, out) is det.
@@ -2561,6 +2561,9 @@
 	code_info, code_info).
 :- mode code_info__save_variables_on_stack(in, out, in, out) is det.
 
+:- pred code_info__max_reg_in_use(int, code_info, code_info).
+:- mode code_info__max_reg_in_use(out, in, out) is det.
+
 %---------------------------------------------------------------------------%
 
 :- implementation.
@@ -2569,11 +2572,6 @@
 	code_info, code_info).
 :- mode code_info__place_vars(in, out, in, out) is det.
 
-:- pred code_info__produce_variable_in_reg_or_stack(var, code_tree, rval,
-	code_info, code_info).
-:- mode code_info__produce_variable_in_reg_or_stack(in, out, out, in, out)
-	is det.
-
 code_info__variable_locations(Locations) -->
 	code_info__get_exprn_info(Exprn),
 	{ code_exprn__get_varlocs(Exprn, Locations) }.
@@ -2785,6 +2783,10 @@
 	code_info__save_variable_on_stack(Var, FirstCode),
 	code_info__save_variables_on_stack(Vars, RestCode),
 	{ Code = tree(FirstCode, RestCode) }.
+
+code_info__max_reg_in_use(Max) -->
+	code_info__get_exprn_info(Exprn),
+	{ code_exprn__max_reg_in_use(Exprn, Max) }.
 
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
Index: compiler/code_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_util.m,v
retrieving revision 1.95
diff -u -r1.95 code_util.m
--- code_util.m	1998/03/03 17:33:50	1.95
+++ code_util.m	1998/03/16 04:33:34
@@ -147,6 +147,16 @@
 	int, int).
 :- mode code_util__count_recursive_calls(in, in, in, out, out) is det.
 
+	% These predicates return the set of lvals referenced in an rval
+	% and an lval respectively. Lvals referenced indirectly through
+	% lvals of the form var(_) are not counted.
+
+:- pred code_util__lvals_in_rval(rval, list(lval)).
+:- mode code_util__lvals_in_rval(in, out) is det.
+
+:- pred code_util__lvals_in_lval(lval, list(lval)).
+:- mode code_util__lvals_in_lval(in, out) is det.
+
 %---------------------------------------------------------------------------%
 
 :- implementation.
@@ -868,3 +878,56 @@
 		int__min(Min0, Min1, Min),
 		int__max(Max0, Max1, Max)
 	).
+
+%-----------------------------------------------------------------------------%
+
+code_util__lvals_in_rval(lval(Lval), [Lval | Lvals]) :-
+	code_util__lvals_in_lval(Lval, Lvals).
+code_util__lvals_in_rval(var(_), []).
+code_util__lvals_in_rval(create(_, _, _, _, _), []).
+code_util__lvals_in_rval(mkword(_, Rval), Lvals) :-
+	code_util__lvals_in_rval(Rval, Lvals).
+code_util__lvals_in_rval(const(_), []).
+code_util__lvals_in_rval(unop(_, Rval), Lvals) :-
+	code_util__lvals_in_rval(Rval, Lvals).
+code_util__lvals_in_rval(binop(_, Rval1, Rval2), Lvals) :-
+	code_util__lvals_in_rval(Rval1, Lvals1),
+	code_util__lvals_in_rval(Rval2, Lvals2),
+	list__append(Lvals1, Lvals2, Lvals).
+code_util__lvals_in_rval(mem_addr(MemRef), Lvals) :-
+	code_util__lvals_in_mem_ref(MemRef, Lvals).
+
+code_util__lvals_in_lval(reg(_, _), []).
+code_util__lvals_in_lval(stackvar(_), []).
+code_util__lvals_in_lval(framevar(_), []).
+code_util__lvals_in_lval(succip, []).
+code_util__lvals_in_lval(maxfr, []).
+code_util__lvals_in_lval(curfr, []).
+code_util__lvals_in_lval(succip(Rval), Lvals) :-
+	code_util__lvals_in_rval(Rval, Lvals).
+code_util__lvals_in_lval(redoip(Rval), Lvals) :-
+	code_util__lvals_in_rval(Rval, Lvals).
+code_util__lvals_in_lval(succfr(Rval), Lvals) :-
+	code_util__lvals_in_rval(Rval, Lvals).
+code_util__lvals_in_lval(prevfr(Rval), Lvals) :-
+	code_util__lvals_in_rval(Rval, Lvals).
+code_util__lvals_in_lval(hp, []).
+code_util__lvals_in_lval(sp, []).
+code_util__lvals_in_lval(field(_, Rval1, Rval2), Lvals) :-
+	code_util__lvals_in_rval(Rval1, Lvals1),
+	code_util__lvals_in_rval(Rval2, Lvals2),
+	list__append(Lvals1, Lvals2, Lvals).
+code_util__lvals_in_lval(lvar(_), []).
+code_util__lvals_in_lval(temp(_, _), []).
+code_util__lvals_in_lval(mem_ref(Rval), Lvals) :-
+	code_util__lvals_in_rval(Rval, Lvals).
+
+:- pred code_util__lvals_in_mem_ref(mem_ref, list(lval)).
+:- mode code_util__lvals_in_mem_ref(in, out) is det.
+
+code_util__lvals_in_mem_ref(stackvar_ref(_), []).
+code_util__lvals_in_mem_ref(framevar_ref(_), []).
+code_util__lvals_in_mem_ref(heap_ref(Rval, _, _), Lvals) :-
+	code_util__lvals_in_rval(Rval, Lvals).
+
+%-----------------------------------------------------------------------------%
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.10
diff -u -r1.10 continuation_info.m
--- continuation_info.m	1998/03/03 17:33:54	1.10
+++ continuation_info.m	1998/03/18 00:55:48
@@ -6,37 +6,38 @@
 %
 % File: continuation_info.m.
 % Main author: trd.
+% Extensive modifications by zs.
 %
-% This file defines the continuation_info data structure, which is used
-% to hold the information we need to output stack_layout tables, 
-% are for
-% accurate garbage collection.
+% This file defines the continuation_info data structure, which the code
+% generator uses to collect information that will later be converted into
+% stack_layout tables for accurate garbage collection, for stack tracing,
+% execution tracing and perhaps other purposes.
 %
 % Information is collected in several passes. 
-%	- If trace_stack_layouts are needed, 
-%		- during the generation of the procedure's prolog code 
-%		  (in code_gen.m) we add the information about live values
-%		  at entry.
-%		- during the generation of the procedure's epilog code 
-%		  (in code_gen.m) we add the information about live
-%		  values at exit.
 %
-% 	- If basic_stack_layouts are needed, after code for a procedure
-% 	  has been generated, the proc_layout_general_info is added to
-% 	  the continuation_info, and some internal label information
-% 	  is initialized (but not filled in with live values).
+% 	- Before we start generating code for a procedure,
+%	  we initialize the set of internal labels for which we have
+%	  layout information to the empty set. This set is stored in
+%	  the code generator state.
 %
-% 	- If agc_stack_layouts are needed, after the code has been
-% 	  optimized a pass is made over the final LLDS instructions.
-% 	  Information about internal labels, is collected.  The liveness
-% 	  information in call instructions is stored with the
-% 	  corresponding continuation label.
+%	- During code generation for the procedure, provided the option
+%	  trace_stack_layouts is set, we add layout information for labels
+%	  that represent trace ports to the code generator state.
+%
+% 	- After we finish generating code for a procedure, we record
+%	  all the static information about the procedure (some of which
+%	  is available only after code generation), and the info about
+%	  internal labels accumulated in the code generator state,
+%	  in the continuation_info structure (which is part of HLDS).
+%
+% 	- If agc_stack_layouts is set, we make a pass over the
+% 	  optimized code recorded in the final LLDS instructions.
+%	  In this pass, we collect information from call instructions
+%	  about the internal labels to which calls can return.
+%	  This info will also go straight into the HLDS.
 %
 % stack_layout.m converts the information collected in this module into
 % stack_layout tables.
-%		
-% The data structures in this module could do with a re-design when it
-% becomes more stable.
 
 %-----------------------------------------------------------------------------%
 
@@ -45,7 +46,7 @@
 :- interface.
 
 :- import_module llds, hlds_pred, prog_data, hlds_data.
-:- import_module set, map, list, assoc_list, term, std_util.
+:- import_module set, map, list, std_util.
 
 	%
 	% Information used by the continuation_info module.
@@ -59,60 +60,43 @@
 	% Information for any procedure, includes information about the
 	% procedure itself, and any internal labels within it.
 	%
-	% The maybe(data) are needed because the data is collected
-	% in a roundabout fashion from various phases of compilation.
-	% In some compilation grades, they are not even needed.
-	% Before data is collected, the field is set to `no'. If
-	% the data is needed (according to various stack_layout
-	% options) it will later be set to a `yes(....)'.
-	% The map is initialized to an empty map, and is later filled
-	% with entries (if required).
-	%
 :- type proc_layout_info
 	--->	proc_layout_info(
-			maybe(proc_layout_general_info),
-					% information on the procedure,
-					% needed for basic_stack_layouts
-			map(label, internal_layout_info),
-					% info for each internal label,
-					% needed for basic_stack_layouts
-			maybe(continuation_label_info),  % entry
-			maybe(continuation_label_info)	 % exit
-					% live data information about
-					% entry and exit points,
-					% needed for trace_stack_layouts
-		).
-
-:- type proc_layout_general_info
-	--->	proc_layout_general_info(
 			proc_label,	% the proc label
 			determinism,	% which stack is used
 			int,		% number of stack slots
-			maybe(int)	% location of succip on stack
+			maybe(int),	% location of succip on stack
+			maybe(label),	% name of the label of the call event
+			proc_label_layout_info
+					% info for each internal label,
+					% needed for basic_stack_layouts
 		).
 
 	%
+	% Information about the labels internal to a procedure.
+	%
+:- type proc_label_layout_info	==	map(label, internal_layout_info).
+
+	%
 	% Information for any internal label.
-	% (Continuation labels are a special case of internal labels).
+	% At some labels, we are interested in the layout of live data;
+	% at others, we are not. The layout_label_info will be present
+	% only for labels of the first kind.
 	%
-:- type internal_layout_info
-	--->	internal_layout_info(
-			maybe(continuation_label_info)
-				% needed for agc_stack_layouts
-		).
+:- type internal_layout_info	==	maybe(layout_label_info).
 
 	%
-	% Information for a label that is a continuation.
+	% Information about the layout of live data for a label.
 	%
 	% Different calls can assign slightly
 	% different liveness annotations to the labels after the call.
 	% (Two different paths of computation can leave different
 	% information live).
 	% We take the intersection of these annotations.  Intersecting
-	% is easy if we represent the live values and type infos as
-	% sets.
-:- type continuation_label_info
-	--->	continuation_label_info(
+	% is easy if we represent the live values and type infos as sets.
+	%
+:- type layout_label_info
+	--->	layout_label_info(
 			set(var_info),
 				% live vars and their locations/names
 			set(pair(tvar, lval))
@@ -128,8 +112,7 @@
 
 	% Return an initialized continuation info structure.
 
-:- pred continuation_info__init(continuation_info).
-:- mode continuation_info__init(out) is det.
+:- pred continuation_info__init(continuation_info::out) is det.
 
 	%
 	% Add the information for a single proc.
@@ -138,44 +121,30 @@
 	% the code model for this proc, and the stack slot of the succip
 	% in this proc (if there is one).
 	%
-:- pred continuation_info__add_proc_layout_info(pred_proc_id, proc_label,
-		int, determinism, maybe(int), continuation_info,
-		continuation_info).
-:- mode continuation_info__add_proc_layout_info(in, in, in, in, in, in,
-		out) is det.
-
-:- pred continuation_info__add_proc_entry_info(pred_proc_id, 
-		list(var_info), assoc_list(var, lval),
-		continuation_info, continuation_info).
-:- mode continuation_info__add_proc_entry_info(in, in, in, in, out) is det.
-
-:- pred continuation_info__add_proc_exit_info(pred_proc_id, 
-		list(var_info), assoc_list(var, lval),
-		continuation_info, continuation_info).
-:- mode continuation_info__add_proc_exit_info(in, in, in, in, out) is det.
-
-:- pred continuation_info__process_llds(list(c_procedure),
-		continuation_info, continuation_info) is det.
-:- mode continuation_info__process_llds(in, in, out) is det.
-
-	%
-	% Add the information for all the labels within a
-	% proc.
-	%
-	% Takes the list of instructions for this proc, the
-	% proc_label, the number of stack slots, the code model for this
-	% proc, and the stack slot of the succip in this proc.
-	%
-:- pred continuation_info__process_instructions(pred_proc_id,
-	list(instruction), continuation_info, continuation_info).
-:- mode continuation_info__process_instructions(in, in, in, out) is det.
+:- pred continuation_info__add_proc_info(pred_proc_id::in, proc_label::in,
+	int::in, determinism::in, maybe(int)::in, maybe(label)::in,
+	proc_label_layout_info::in, continuation_info::in,
+	continuation_info::out) is det.
+
+	%
+	% Call continuation_info__process_instructions on the code
+	% of every procedure in the list.
+	%
+:- pred continuation_info__process_llds(list(c_procedure)::in,
+	continuation_info::in, continuation_info::out) is det.
+
+	%
+	% Add the information for all the continuation labels within a proc.
+	%
+:- pred continuation_info__process_instructions(pred_proc_id::in,
+	list(instruction)::in, continuation_info::in, continuation_info::out)
+	is det.
 
 	%
 	% Get the finished list of proc_layout_infos.
 	%
-:- pred continuation_info__get_all_proc_layouts(list(proc_layout_info),
-		continuation_info, continuation_info).
-:- mode continuation_info__get_all_proc_layouts(out, in, out) is det.
+:- pred continuation_info__get_all_proc_layouts(continuation_info::in,
+	list(proc_layout_info)::out) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -185,16 +154,7 @@
 :- import_module require.
 
 	% The continuation_info data structure
-
-:- type continuation_info
-	--->	continuation_info(
-			map(pred_proc_id, proc_layout_info),
-				% A proc_layout_info for every procedure
-				% processed
-			map(label, internal_layout_info)
-				% internal labels processed so far
-				% in the current procedure
-			).
+:- type continuation_info	==	map(pred_proc_id, proc_layout_info).
 
 %-----------------------------------------------------------------------------%
 
@@ -205,34 +165,31 @@
 	%
 
 continuation_info__init(ContInfo) :-
-	map__init(LabelMap),
-	map__init(Internals),
-	ContInfo = continuation_info(LabelMap, Internals).
-
-continuation_info__add_proc_entry_info(PredProcId, TypeLvals, TypeInfos) -->
-	continuation_info__get_proc_layout(PredProcId, ProcLayout0),
-	{ ProcLayout0 = proc_layout_info(MaybeProcGeneral, InternalMap, _,
-		ExitInfo) },
-	{ set__list_to_set(TypeLvals, TypeLvalSet) },
-	{ set__list_to_set(TypeInfos, TypeInfoSet) },
-	{ EntryInfo = yes(continuation_label_info(TypeLvalSet, TypeInfoSet)) },
-	{ ProcLayout = proc_layout_info(MaybeProcGeneral, InternalMap, 
-		EntryInfo, ExitInfo) },
-	continuation_info__update_proc_layout(PredProcId, ProcLayout).
-
-continuation_info__add_proc_exit_info(PredProcId, TypeLvals, TypeInfos) -->
-	continuation_info__get_proc_layout(PredProcId, ProcLayout0),
-	{ ProcLayout0 = proc_layout_info(MaybeProcGeneral, InternalMap, 
-		EntryInfo, _) },
-	{ set__list_to_set(TypeLvals, TypeLvalSet) },
-	{ set__list_to_set(TypeInfos, TypeInfoSet) },
-	{ ExitInfo = yes(continuation_label_info(TypeLvalSet, TypeInfoSet)) },
-	{ ProcLayout = proc_layout_info(MaybeProcGeneral, InternalMap, 
-		EntryInfo, ExitInfo) },
-	continuation_info__update_proc_layout(PredProcId, ProcLayout).
-	
+	map__init(ContInfo).
+
+	%
+	% Add the info for this proc (a proc_layout_info) to the
+	% continuation_info. 
+	%
+continuation_info__add_proc_info(PredProcId, ProcLabel, StackSize,
+		Detism, SuccipLocation, MaybeTraceCallLabel, InternalMap,
+		ContInfo0, ContInfo) :-
+	( map__contains(ContInfo0, PredProcId) ->
+		error("duplicate continuation_info for proc.")
+	;
+		LayoutInfo = proc_layout_info(ProcLabel, Detism, StackSize,
+			SuccipLocation, MaybeTraceCallLabel, InternalMap),
+		map__det_insert(ContInfo0, PredProcId, LayoutInfo, ContInfo)
+	).
+
+	%
+	% Get all the proc_layout_infos.
+	%
+continuation_info__get_all_proc_layouts(ContInfo, Entries) :-
+	map__values(ContInfo, Entries).
+
 continuation_info__process_llds([]) --> [].
-continuation_info__process_llds([Proc|Procs]) -->
+continuation_info__process_llds([Proc | Procs]) -->
 	{ Proc = c_procedure(_, _, PredProcId, Instrs) },
 	continuation_info__process_instructions(PredProcId, Instrs),
 	continuation_info__process_llds(Procs).
@@ -241,103 +198,51 @@
 	% Process the list of instructions for this proc, adding
 	% all internal label information to the continuation_info.
 	%
-continuation_info__process_instructions(PredProcId, Instructions) -->
+continuation_info__process_instructions(PredProcId, Instructions,
+		ContInfo0, ContInfo) :-
 
-		% Get all the continuation info from the call instructions
-	continuation_info__initialize_internal_info,
-	{ GetCallLivevals = lambda([Instr::in, Pair::out] is semidet, (
+		% Get all the continuation info from the call instructions.
+	map__lookup(ContInfo0, PredProcId, ProcLayoutInfo0),
+	ProcLayoutInfo0 = proc_layout_info(A, B, C, D, E, Internals0),
+	GetCallLivevals = lambda([Instr::in, Pair::out] is semidet, (
 		Instr = call(_, label(Label), LiveInfo, _) - _Comment,
 		Pair = Label - LiveInfo
-		)) },
-	{ list__filter_map(GetCallLivevals, Instructions, Calls) },
+	)),
+	list__filter_map(GetCallLivevals, Instructions, Calls),
 
-		% Process the continuation label info
-	list__foldl(continuation_info__process_internal_info,
-		Calls),
-
-		% Get all internal labels.
-		% (Some labels are not used as continuations).
-	{ GetAllInternalLabels = lambda([Instr::in, Label::out] is semidet, (
+		% Process the continuation label info.
+	list__foldl(continuation_info__process_continuation, Calls,
+		Internals0, Internals1),
+
+		% Add empty entries for the labels that do not have real info,
+		% since if continuation_info__process_instructions is invoked
+		% then MR_USE_STACK_LAYOUTS will be defined, and this demands
+		% a stack layout data structure for every label, even if it
+		% is not used. When this aspect of the runtime is fixed,
+		% we will be able to remove this step.
+	GetAllInternalLabels = lambda([Instr::in, Label::out] is semidet, (
 		Instr = label(Label) - _Comment,
 		Label = local(_, _)
-		)) },
-	{ list__filter_map(GetAllInternalLabels, Instructions, Labels) },
-
-		% Insert all non-continuation internal labels into the
-		% internals, then add the internals to the information
-		% for this proc.
-	continuation_info__add_non_continuation_labels(Labels),
-	continuation_info__get_internal_info(InternalInfo),
-	continuation_info__add_internal_info_to_proc(PredProcId, InternalInfo).
-
-	%
-	% Add the info for this proc (a proc_layout_info) to the
-	% continuation_info. 
-	%
-continuation_info__add_proc_layout_info(PredProcId, ProcLabel, StackSize,
-		Detism, SuccipLocation) -->
-	continuation_info__get_proc_layout(PredProcId, ProcLayoutInfo0),
-	{ 
-		ProcLayoutInfo0 = proc_layout_info(no, InternalMap, 
-			EntryInfo, ExitInfo) 
-	->
-		ProcLayoutInfo = proc_layout_info(yes(proc_layout_general_info(
-			ProcLabel, Detism, StackSize, SuccipLocation)), 
-			InternalMap, EntryInfo, ExitInfo)
-	;
-		error("continuation_info__add_proc_layout_info: general information already done.")
-	},
-	continuation_info__update_proc_layout(PredProcId, ProcLayoutInfo).
+	)),
+	list__filter_map(GetAllInternalLabels, Instructions, Labels),
+	list__foldl(continuation_info__ensure_label_is_present, Labels,
+		Internals1, Internals),
 
-	%
-	% Get all the proc_layout_infos.
-	%
-continuation_info__get_all_proc_layouts(Entries, ContInfo, ContInfo) :-
-	ContInfo = continuation_info(Map, _),
-	map__values(Map, Entries).
+	ProcLayoutInfo = proc_layout_info(A, B, C, D, E, Internals),
+	map__det_update(ContInfo0, PredProcId, ProcLayoutInfo, ContInfo).
 
 %-----------------------------------------------------------------------------%
 
 	%
-	% Add the list of internal labels to the internal_info
-	% in the continuation_info.
-	%
-:- pred continuation_info__add_non_continuation_labels(list(label),
-		continuation_info, continuation_info).
-:- mode continuation_info__add_non_continuation_labels(in, in, out) is det.
-
-continuation_info__add_non_continuation_labels(Labels) -->
-	continuation_info__get_internal_info(InternalInfo0),
-	{ list__foldl(continuation_info__ensure_label_is_present, Labels,
-		InternalInfo0, InternalInfo) },
-	continuation_info__set_internal_info(InternalInfo).
-
-	%
-	% Add a label to the internals, if it isn't already there.
-	%
-:- pred continuation_info__ensure_label_is_present(label,
-		map(label, internal_layout_info),
-		map(label, internal_layout_info)).
-:- mode continuation_info__ensure_label_is_present(in, in, out) is det.
-continuation_info__ensure_label_is_present(Label, InternalMap0, InternalMap) :-
-	( map__contains(InternalMap0, Label) ->
-		InternalMap = InternalMap0
-	;
-		Internal = internal_layout_info(no),
-		map__det_insert(InternalMap0, Label,
-			Internal, InternalMap)
-	).
-
-	%
 	% Collect the liveness information from a single label and add
 	% it to the internals.
 	%
-:- pred continuation_info__process_internal_info(pair(label,
-		list(liveinfo)), continuation_info, continuation_info).
-:- mode continuation_info__process_internal_info(in, in, out) is det.
+:- pred continuation_info__process_continuation(
+	pair(label, list(liveinfo))::in,
+	proc_label_layout_info::in, proc_label_layout_info::out) is det.
 
-continuation_info__process_internal_info(Label - LiveInfoList, ContInfo0,
-		ContInfo) :-
+continuation_info__process_continuation(Label - LiveInfoList,
+		Internals0, Internals) :-
 	GetVarInfo = lambda([LiveLval::in, VarInfo::out] is det, (
 		LiveLval = live_lvalue(Lval, LiveValueType, Name, _),
 		VarInfo = var_info(Lval, LiveValueType, Name)
@@ -351,10 +256,40 @@
 	list__sort_and_remove_dups(TypeInfoList, SortedTypeInfoList),
 	set__sorted_list_to_set(SortedTypeInfoList, TypeInfoSet),
 	set__list_to_set(VarInfoList, VarInfoSet),
-	NewInternal = internal_layout_info(
-		yes(continuation_label_info(VarInfoSet, TypeInfoSet))),
+	NewInternal = yes(layout_label_info(VarInfoSet, TypeInfoSet)),
 	continuation_info__add_internal_info(Label, NewInternal,
-		ContInfo0, ContInfo).
+		Internals0, Internals).
+
+:- pred continuation_info__ensure_label_is_present(label::in,
+	proc_label_layout_info::in, proc_label_layout_info::out) is det.
+
+continuation_info__ensure_label_is_present(Label, InternalMap0, InternalMap) :-
+	( map__contains(InternalMap0, Label) ->
+		InternalMap = InternalMap0
+	;
+		map__det_insert(InternalMap0, Label, no, InternalMap)
+	).
+
+%-----------------------------------------------------------------------------%
+
+	%
+	% Add an internal info to the list of internal infos.
+	%
+:- pred continuation_info__add_internal_info(label::in,
+	internal_layout_info::in,
+	proc_label_layout_info::in, proc_label_layout_info::out) is det.
+
+continuation_info__add_internal_info(Label, Internal1,
+		Internals0, Internals) :-
+	(
+		map__search(Internals0, Label, Internal0)
+	->
+		continuation_info__merge_internal_labels(Internal0, Internal1,
+			Internal),
+		map__set(Internals0, Label, Internal, Internals)
+	;
+		map__det_insert(Internals0, Label, Internal1, Internals)
+	).
 
 	%
 	% Merge the continuation label information of two labels.
@@ -367,157 +302,24 @@
 	% label is guaranteed not to depend on it.
 	% XXX Is this true for non-det code?
 
-:- pred continuation_info__merge_internal_labels(maybe(continuation_label_info),
-	maybe(continuation_label_info), maybe(continuation_label_info)).
-:- mode continuation_info__merge_internal_labels(in, in, out) is det.
+:- pred continuation_info__merge_internal_labels(
+	maybe(layout_label_info)::in, maybe(layout_label_info)::in,
+	maybe(layout_label_info)::out) is det.
 
 continuation_info__merge_internal_labels(no, no, no).
 continuation_info__merge_internal_labels(no,
-		yes(continuation_label_info(LV0, TV0)),
-		yes(continuation_label_info(LV0, TV0))).
+		yes(layout_label_info(LV0, TV0)),
+		yes(layout_label_info(LV0, TV0))).
 continuation_info__merge_internal_labels(
-		yes(continuation_label_info(LV0, TV0)),
+		yes(layout_label_info(LV0, TV0)),
 		no,
-		yes(continuation_label_info(LV0, TV0))).
+		yes(layout_label_info(LV0, TV0))).
 continuation_info__merge_internal_labels(
-		yes(continuation_label_info(LV0, TV0)),
-		yes(continuation_label_info(LV1, TV1)),
-		yes(continuation_label_info(LV, TV))) :-
+		yes(layout_label_info(LV0, TV0)),
+		yes(layout_label_info(LV1, TV1)),
+		yes(layout_label_info(LV, TV))) :-
 	set__intersect(LV0, LV1, LV),
 	set__intersect(TV0, TV1, TV).
-
-%-----------------------------------------------------------------------------%
-
-	% Procedures to manipulate continuation_info
-
-	%
-	% Add the given proc_layout_info to the continuation_info.
-	%
-:- pred continuation_info__insert_proc_layout(pred_proc_id, proc_layout_info,
-		continuation_info, continuation_info).
-:- mode continuation_info__insert_proc_layout(in, in, in, out) is det.
-
-continuation_info__insert_proc_layout(PredProcId, ProcLayoutInfo,
-		ContInfo0, ContInfo) :-
-	ContInfo0 = continuation_info(ProcLayoutMap0, Internals),
-	map__det_insert(ProcLayoutMap0, PredProcId, ProcLayoutInfo,
-		ProcLayoutMap),
-	ContInfo = continuation_info(ProcLayoutMap, Internals).
-
-	%
-	% Get the proc layout if it exists, otherwise return an 
-	% empty one.
-	%
-:- pred continuation_info__get_proc_layout(pred_proc_id, proc_layout_info,
-		continuation_info, continuation_info).
-:- mode continuation_info__get_proc_layout(in, out, in, out) is det.
-
-continuation_info__get_proc_layout(PredProcId, ProcLayoutInfo,
-		ContInfo, ContInfo) :-
-	ContInfo = continuation_info(ProcLayoutMap, _Internals),
-	( 
-		map__search(ProcLayoutMap, PredProcId, ProcLayoutInfo0)
-	->
-		ProcLayoutInfo = ProcLayoutInfo0
-	;
-		map__init(InternalMap),
-		ProcLayoutInfo = proc_layout_info(no, InternalMap, no, no)
-	).
-
-	%
-	% Update a proc layout.
-	%
-:- pred continuation_info__update_proc_layout(pred_proc_id, proc_layout_info,
-		continuation_info, continuation_info).
-:- mode continuation_info__update_proc_layout(in, in, in, out) is det.
-
-continuation_info__update_proc_layout(PredProcId, ProcLayoutInfo,
-		ContInfo0, ContInfo) :-
-	ContInfo0 = continuation_info(ProcLayoutMap0, Internals),
-	map__set(ProcLayoutMap0, PredProcId, ProcLayoutInfo, ProcLayoutMap),
-	ContInfo = continuation_info(ProcLayoutMap, Internals).
-
-	%
-	% Add the given internal_info to the given procedure in
-	% the continuation_info.
-	%
-	% (The procedure proc_layout_info has already been processed and
-	% added, but at that time the internal_info wasn't available).
-	%
-:- pred continuation_info__add_internal_info_to_proc(pred_proc_id,
-		map(label, internal_layout_info), continuation_info,
-		continuation_info).
-:- mode continuation_info__add_internal_info_to_proc(in, in, in, out) is det.
-
-continuation_info__add_internal_info_to_proc(PredProcId, InternalLayout,
-		ContInfo0, ContInfo) :-
-	ContInfo0 = continuation_info(ProcLayoutMap0, Internals),
-	map__lookup(ProcLayoutMap0, PredProcId, ProcLayoutInfo0),
-	ProcLayoutInfo0 = proc_layout_info(MaybeProcGeneral, _, EntryInfo,
-		ExitInfo),
-	ProcLayoutInfo = proc_layout_info(MaybeProcGeneral, InternalLayout,
-		EntryInfo, ExitInfo),
-	map__set(ProcLayoutMap0, PredProcId, ProcLayoutInfo, ProcLayoutMap),
-	ContInfo = continuation_info(ProcLayoutMap, Internals).
-
-	%
-	% Add an internal info to the list of internal infos.
-	%
-:- pred continuation_info__add_internal_info(label,
-		internal_layout_info, continuation_info, continuation_info).
-:- mode continuation_info__add_internal_info(in, in, in, out) is det.
-
-continuation_info__add_internal_info(Label, Internal, ContInfo0, ContInfo) :-
-	ContInfo0 = continuation_info(ProcLayoutMap, Internals0),
-	Internal = internal_layout_info(ContLabelInfo0),
-	(
-		map__search(Internals0, Label, Existing)
-	->
-		Existing = internal_layout_info(ContLabelInfo1),
-		continuation_info__merge_internal_labels(ContLabelInfo0,
-			ContLabelInfo1, ContLabelInfo),
-		New = internal_layout_info(ContLabelInfo),
-		map__set(Internals0, Label, New, Internals)
-		
-	;
-		map__det_insert(Internals0, Label, Internal, Internals)
-	),
-	ContInfo = continuation_info(ProcLayoutMap, Internals).
-
-	%
-	% Initialize the internal info.
-	%
-:- pred continuation_info__initialize_internal_info(
-	continuation_info, continuation_info).
-:- mode continuation_info__initialize_internal_info(in, out) is det.
-
-continuation_info__initialize_internal_info(ContInfo0, ContInfo) :-
-	ContInfo0 = continuation_info(ProcLayoutMap, _),
-	map__init(Internals),
-	ContInfo = continuation_info(ProcLayoutMap, Internals).
-
-	%
-	% Set the internal info.
-	%
-:- pred continuation_info__set_internal_info(
-	map(label, internal_layout_info), continuation_info,
-	continuation_info).
-:- mode continuation_info__set_internal_info(in, in, out) is det.
-
-continuation_info__set_internal_info(Internals, ContInfo0, ContInfo) :-
-	ContInfo0 = continuation_info(ProcLayoutMap, _),
-	ContInfo = continuation_info(ProcLayoutMap, Internals).
-
-	%
-	% Get the internal_info.
-	%
-:- pred continuation_info__get_internal_info(
-		map(label, internal_layout_info),
-		continuation_info, continuation_info).
-:- mode continuation_info__get_internal_info(out, in, out) is det.
-
-continuation_info__get_internal_info(InternalMap, ContInfo, ContInfo) :-
-	ContInfo = continuation_info(_, InternalMap).
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
Index: compiler/dense_switch.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/dense_switch.m,v
retrieving revision 1.32
diff -u -r1.32 dense_switch.m
--- dense_switch.m	1998/03/03 17:33:59	1.32
+++ dense_switch.m	1998/03/18 05:41:23
@@ -242,8 +242,9 @@
 		( { MaybeTraceInfo = yes(TraceInfo) } ->
 			{ Goal = _ - GoalInfo },
 			{ goal_info_get_goal_path(GoalInfo, Path) },
-			trace__generate_event_code(switch(Path), TraceInfo,
-				TraceCode)
+			{ goal_info_get_pre_deaths(GoalInfo, PreDeaths) },
+			trace__generate_event_code(switch(Path, PreDeaths),
+				TraceInfo, TraceCode)
 		;
 			{ TraceCode = empty }
 		),
Index: compiler/disj_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/disj_gen.m,v
retrieving revision 1.62
diff -u -r1.62 disj_gen.m
--- disj_gen.m	1998/03/03 17:34:07	1.62
+++ disj_gen.m	1998/03/18 05:59:46
@@ -170,8 +170,9 @@
 		code_info__get_maybe_trace_info(MaybeTraceInfo),
 		( { MaybeTraceInfo = yes(TraceInfo) } ->
 			{ goal_info_get_goal_path(GoalInfo, Path) },
-			trace__generate_event_code(disj(Path), TraceInfo,
-				TraceCode)
+			{ goal_info_get_pre_deaths(GoalInfo, PreDeaths) },
+			trace__generate_event_code(disj(Path, PreDeaths),
+				TraceInfo, TraceCode)
 		;
 			{ TraceCode = empty }
 		),
@@ -216,9 +217,10 @@
 			% Generate the goal
 		code_info__get_maybe_trace_info(MaybeTraceInfo),
 		( { MaybeTraceInfo = yes(TraceInfo) } ->
-			{ goal_info_get_goal_path(GoalInfo0, Path) },
-			trace__generate_event_code(disj(Path), TraceInfo,
-				TraceCode)
+			{ goal_info_get_goal_path(GoalInfo0, Path0) },
+			{ goal_info_get_pre_deaths(GoalInfo0, PreDeaths0) },
+			trace__generate_event_code(disj(Path0, PreDeaths0),
+				TraceInfo, TraceCode)
 		;
 			{ TraceCode = empty }
 		),
@@ -332,8 +334,9 @@
 		code_info__get_maybe_trace_info(MaybeTraceInfo),
 		( { MaybeTraceInfo = yes(TraceInfo) } ->
 			{ goal_info_get_goal_path(GoalInfo, Path) },
-			trace__generate_event_code(disj(Path), TraceInfo,
-				TraceCode)
+			{ goal_info_get_pre_deaths(GoalInfo, PreDeaths) },
+			trace__generate_event_code(disj(Path, PreDeaths),
+				TraceInfo, TraceCode)
 		;
 			{ TraceCode = empty }
 		),
@@ -391,9 +394,10 @@
 
 		code_info__get_maybe_trace_info(MaybeTraceInfo),
 		( { MaybeTraceInfo = yes(TraceInfo) } ->
-			{ goal_info_get_goal_path(GoalInfo0, Path) },
-			trace__generate_event_code(disj(Path), TraceInfo,
-				TraceCode)
+			{ goal_info_get_goal_path(GoalInfo0, Path0) },
+			{ goal_info_get_pre_deaths(GoalInfo0, PreDeaths0) },
+			trace__generate_event_code(disj(Path0, PreDeaths0),
+				TraceInfo, TraceCode)
 		;
 			{ TraceCode = empty }
 		),
Index: compiler/goal_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/goal_util.m,v
retrieving revision 1.43
diff -u -r1.43 goal_util.m
--- goal_util.m	1998/03/03 17:34:19	1.43
+++ goal_util.m	1998/03/18 07:11:03
@@ -61,6 +61,21 @@
 :- pred goal_util__goal_vars(hlds_goal, set(var)).
 :- mode goal_util__goal_vars(in, out) is det.
 
+	%
+	% A type-info variable may be non-local to a goal if any of 
+	% the ordinary non-local variables for that goal are
+	% polymorphically typed with a type that depends on that
+	% type-info variable.
+	%
+	% In addition, a typeclass-info may be non-local to a goal if
+	% any of the non-local variables for that goal are
+	% polymorphically typed and are constrained by the typeclass
+	% constraints for that typeclass-info variable
+	%
+:- pred goal_util__extra_nonlocal_typeinfos(map(var, type_info_locn),
+		map(var, type), hlds_goal, set(var)).
+:- mode goal_util__extra_nonlocal_typeinfos(in, in, in, out) is det.
+
 	% See whether the goal is a branched structure.
 :- pred goal_util__goal_is_branched(hlds_goal_expr).
 :- mode goal_util__goal_is_branched(in) is semidet.
@@ -485,6 +500,23 @@
 	set__insert_list(Set0, NonLocals, Set1),
 	set__insert_list(Set1, LambdaVars, Set2),
 	goal_util__goal_vars_2(Goal, Set2, Set).
+
+%-----------------------------------------------------------------------------%
+
+goal_util__extra_nonlocal_typeinfos(TypeVarMap, VarTypes,
+		Goal0, NonLocalTypeInfos) :-
+	Goal0 = _ - GoalInfo0,
+	goal_info_get_nonlocals(GoalInfo0, NonLocals),
+	set__to_sorted_list(NonLocals, NonLocalsList),
+	map__apply_to_list(NonLocalsList, VarTypes, NonLocalsTypes),
+	term__vars_list(NonLocalsTypes, NonLocalTypeVars),
+		% Find all the type-infos and typeclass-infos that are
+		% non-local
+	solutions_set(lambda([Var::out] is nondet, (
+			list__member(TheVar, NonLocalTypeVars),
+			map__search(TypeVarMap, TheVar, Location),
+			type_info_locn_var(Location, Var)
+		)), NonLocalTypeInfos).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.45
diff -u -r1.45 handle_options.m
--- handle_options.m	1998/03/03 17:34:21	1.45
+++ handle_options.m	1998/03/20 07:45:43
@@ -268,6 +268,10 @@
 	% 	- enabling typeinfo liveness
 	globals__io_lookup_bool_option(generate_trace, Trace),
 	( { Trace = yes } ->
+			% The following options modify the structure
+			% of the program, which makes it difficult to
+			% relate the trace to the source code (although
+			% it can be easily related to the transformed HLDS).
 		globals__io_set_option(inline_simple, bool(no)),
 		globals__io_set_option(inline_single_use, bool(no)),
 		globals__io_set_option(inline_compound_threshold, int(0)),
@@ -276,7 +280,22 @@
 		globals__io_set_option(optimize_duplicate_calls, bool(no)),
 		globals__io_set_option(optimize_constructor_last_call,
 			bool(no)),
+
+			% The following option prevents useless variables
+			% from cluttering the trace. Its explicit setting
+			% removes a source of variability in the goal paths
+			% reported by tracing.
 		globals__io_set_option(excess_assign, bool(yes)),
+			% The following option selects a special-case
+			% code generator that cannot (yet) implement tracing.
+		globals__io_set_option(middle_rec, bool(no)),
+			% Tracing inserts C code into the generated LLDS.
+			% Value numbering cannot optimize such LLDS code.
+			% We turn value numbering off now so that we don't
+			% have to discover this fact anew for each procedure.
+		globals__io_set_option(optimize_value_number, bool(no)),
+			% The following options cause the info required
+			% by tracing to be generated.
 		globals__io_set_option(trace_stack_layout, bool(yes)),
 		globals__io_set_option(typeinfo_liveness, bool(yes))
 	;
Index: compiler/ite_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ite_gen.m,v
retrieving revision 1.53
diff -u -r1.53 ite_gen.m
--- ite_gen.m	1998/01/23 12:56:38	1.53
+++ ite_gen.m	1998/03/18 06:00:37
@@ -119,8 +119,9 @@
 	( { MaybeTraceInfo = yes(TraceInfoThen) } ->
 		{ ThenGoal = _ - ThenGoalInfo },
 		{ goal_info_get_goal_path(ThenGoalInfo, ThenPath) },
-		trace__generate_event_code(ite_then(ThenPath), TraceInfoThen,
-			ThenTraceCode)
+		{ goal_info_get_pre_deaths(ThenGoalInfo, ThenPreDeaths) },
+		trace__generate_event_code(ite_then(ThenPath, ThenPreDeaths),
+			TraceInfoThen, ThenTraceCode)
 	;
 		{ ThenTraceCode = empty }
 	),
@@ -138,8 +139,9 @@
 	( { MaybeTraceInfo = yes(TraceInfoElse) } ->
 		{ ElseGoal = _ - ElseGoalInfo },
 		{ goal_info_get_goal_path(ElseGoalInfo, ElsePath) },
-		trace__generate_event_code(ite_else(ElsePath), TraceInfoElse,
-			ElseTraceCode)
+		{ goal_info_get_pre_deaths(ElseGoalInfo, ElsePreDeaths) },
+		trace__generate_event_code(ite_else(ElsePath, ElsePreDeaths),
+			TraceInfoElse, ElseTraceCode)
 	;
 		{ ElseTraceCode = empty }
 	),
@@ -276,8 +278,9 @@
 	( { MaybeTraceInfo = yes(TraceInfoThen) } ->
 		{ ThenGoal = _ - ThenGoalInfo },
 		{ goal_info_get_goal_path(ThenGoalInfo, ThenPath) },
-		trace__generate_event_code(ite_then(ThenPath), TraceInfoThen,
-			ThenTraceCode)
+		{ goal_info_get_pre_deaths(ThenGoalInfo, ThenPreDeaths) },
+		trace__generate_event_code(ite_then(ThenPath, ThenPreDeaths),
+			TraceInfoThen, ThenTraceCode)
 	;
 		{ ThenTraceCode = empty }
 	),
@@ -295,8 +298,9 @@
 	( { MaybeTraceInfo = yes(TraceInfoElse) } ->
 		{ ElseGoal = _ - ElseGoalInfo },
 		{ goal_info_get_goal_path(ElseGoalInfo, ElsePath) },
-		trace__generate_event_code(ite_else(ElsePath), TraceInfoElse,
-			ElseTraceCode)
+		{ goal_info_get_pre_deaths(ElseGoalInfo, ElsePreDeaths) },
+		trace__generate_event_code(ite_else(ElsePath, ElsePreDeaths),
+			TraceInfoElse, ElseTraceCode)
 	;
 		{ ElseTraceCode = empty }
 	),
Index: compiler/lambda.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/lambda.m,v
retrieving revision 1.40
diff -u -r1.40 lambda.m
--- lambda.m	1998/03/03 17:34:45	1.40
+++ lambda.m	1998/03/18 07:12:16
@@ -41,28 +41,28 @@
 :- interface. 
 
 :- import_module hlds_module, hlds_pred, hlds_goal, hlds_data, prog_data.
-:- import_module list, map, term, varset.
+:- import_module list, map, set, term, varset.
 
 :- pred lambda__process_pred(pred_id, module_info, module_info).
 :- mode lambda__process_pred(in, in, out) is det.
 
 :- pred lambda__transform_lambda(pred_or_func, string, list(var), list(mode), 
-		determinism, list(var), hlds_goal, unification,
+		determinism, list(var), set(var), hlds_goal, unification,
 		varset, map(var, type), list(class_constraint), tvarset,
 		map(tvar, type_info_locn), map(class_constraint, var),
 		module_info, unify_rhs, unification, module_info).
-:- mode lambda__transform_lambda(in, in, in, in, in, in, in, in, in, in, in, in,
-		in, in, in, out, out, out) is det.
+:- mode lambda__transform_lambda(in, in, in, in, in, in, in, in, in, in, in,
+		in, in, in, in, in, out, out, out) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
 :- implementation.
 
-:- import_module make_hlds.
-:- import_module prog_util, mode_util, inst_match, llds, arg_info.
+:- import_module make_hlds, globals, options.
+:- import_module goal_util, prog_util, mode_util, inst_match, llds, arg_info.
 
-:- import_module bool, set, string, std_util, require.
+:- import_module bool, string, std_util, require.
 
 :- type lambda_info --->
 		lambda_info(
@@ -238,17 +238,19 @@
 		Unification0, Functor, Unification, LambdaInfo0, LambdaInfo) :-
 	LambdaInfo0 = lambda_info(VarSet, VarTypes, Constraints, TVarSet,
 			TVarMap, TCVarMap, POF, PredName, ModuleInfo0),
+	goal_util__extra_nonlocal_typeinfos(TVarMap, VarTypes,
+		LambdaGoal, ExtraTypeInfos),
 	lambda__transform_lambda(PredOrFunc, PredName, Vars, Modes, Det,
-		OrigNonLocals0, LambdaGoal, Unification0, VarSet, VarTypes,
-		Constraints, TVarSet, TVarMap, TCVarMap, ModuleInfo0, Functor,
-		Unification, ModuleInfo),
+		OrigNonLocals0, ExtraTypeInfos, LambdaGoal, Unification0,
+		VarSet, VarTypes, Constraints, TVarSet, TVarMap, TCVarMap,
+		ModuleInfo0, Functor, Unification, ModuleInfo),
 	LambdaInfo = lambda_info(VarSet, VarTypes, Constraints, TVarSet,
 			TVarMap, TCVarMap, POF, PredName, ModuleInfo).
 
 lambda__transform_lambda(PredOrFunc, OrigPredName, Vars, Modes, Detism,
-		OrigVars, LambdaGoal, Unification0, VarSet, VarTypes,
-		Constraints, TVarSet, TVarMap, TCVarMap, ModuleInfo0, Functor,
-		Unification, ModuleInfo) :-
+		OrigVars, ExtraTypeInfos, LambdaGoal, Unification0,
+		VarSet, VarTypes, Constraints, TVarSet, TVarMap, TCVarMap,
+		ModuleInfo0, Functor, Unification, ModuleInfo) :-
 	(
 		Unification0 = construct(Var0, _, _, UniModes0)
 	->
@@ -270,7 +272,20 @@
 
 	LambdaGoal = _ - LambdaGoalInfo,
 	goal_info_get_nonlocals(LambdaGoalInfo, NonLocals0),
-	set__delete_list(NonLocals0, Vars, NonLocals),
+	set__delete_list(NonLocals0, Vars, NonLocals1),
+	module_info_globals(ModuleInfo0, Globals),
+
+	% If typeinfo_liveness is set, all type_infos for the
+	% arguments should be included, not just the ones
+	% that are used.
+	globals__lookup_bool_option(Globals,
+		typeinfo_liveness, TypeInfoLiveness),
+	( TypeInfoLiveness = yes ->
+		set__union(NonLocals1, ExtraTypeInfos, NonLocals)
+	;
+		NonLocals = NonLocals1
+	),
+
 	set__to_sorted_list(NonLocals, ArgVars1),
 	( 
 		LambdaGoal = call(PredId0, ProcId0, CallVars,
@@ -376,7 +391,6 @@
 		% inputs came before outputs, but that resulted in the
 		% HLDS not being type or mode correct which caused problems
 		% for some transformations and for rerunning mode analysis.
-		module_info_globals(ModuleInfo1, Globals),
 		arg_info__ho_call_args_method(Globals, ArgsMethod),
 
 		% Now construct the proc_info and pred_info for the new
Index: compiler/live_vars.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/live_vars.m,v
retrieving revision 1.72
diff -u -r1.72 live_vars.m
--- live_vars.m	1998/02/03 08:18:22	1.72
+++ live_vars.m	1998/03/16 07:58:03
@@ -36,6 +36,7 @@
 
 :- import_module llds, arg_info, prog_data, hlds_goal, hlds_data, mode_util.
 :- import_module liveness, code_aux, globals, graph_colour, instmap, options.
+:- import_module trace.
 :- import_module list, map, set, std_util, assoc_list, bool.
 :- import_module int, term, require.
 
@@ -47,8 +48,16 @@
 
 	initial_liveness(ProcInfo0, ModuleInfo, Liveness0),
 	set__init(LiveSets0),
-	set__init(ResumeVars0),
-	build_live_sets_in_goal(Goal0, Liveness0, ResumeVars0, LiveSets0,
+	module_info_globals(ModuleInfo, Globals),
+	globals__lookup_bool_option(Globals, generate_trace, Trace),
+	( Trace = yes ->
+		trace__fail_vars(ProcInfo0, ResumeVars0),
+		set__insert(LiveSets0, ResumeVars0, LiveSets1)
+	;
+		set__init(ResumeVars0),
+		LiveSets1 = LiveSets0
+	),
+	build_live_sets_in_goal(Goal0, Liveness0, ResumeVars0, LiveSets1,
 		ModuleInfo, ProcInfo0, _Liveness, _ResumeVars, LiveSets),
 	graph_colour__group_elements(LiveSets, ColourSets),
 	set__to_sorted_list(ColourSets, ColourList),
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.91
diff -u -r1.91 liveness.m
--- liveness.m	1998/03/03 17:34:49	1.91
+++ liveness.m	1998/03/11 07:36:18
@@ -145,7 +145,7 @@
 
 :- import_module hlds_goal, hlds_data, llds, quantification, (inst), instmap.
 :- import_module hlds_out, mode_util, code_util, quantification, options.
-:- import_module prog_data, globals, passes_aux.
+:- import_module prog_data, trace, globals, passes_aux.
 
 :- import_module bool, map, std_util, list, assoc_list, require.
 :- import_module varset, string.
@@ -164,7 +164,13 @@
 	initial_deadness(ProcInfo1, ModuleInfo, Deadness0),
 	detect_deadness_in_goal(Goal1, Deadness0, LiveInfo, _, Goal2),
 
-	set__init(ResumeVars0),
+	module_info_globals(ModuleInfo, Globals),
+	globals__lookup_bool_option(Globals, generate_trace, Trace),
+	( Trace = yes ->
+		trace__fail_vars(ProcInfo0, ResumeVars0)
+	;
+		set__init(ResumeVars0)
+	),
 	detect_resume_points_in_goal(Goal2, Liveness0, LiveInfo,
 		ResumeVars0, Goal, _),
 
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.79
diff -u -r1.79 mercury_compile.m
--- mercury_compile.m	1998/03/20 02:58:08	1.79
+++ mercury_compile.m	1998/03/20 08:19:01
@@ -996,13 +996,13 @@
 	;
 		{ Proc = Proc0 }
 	),
-	{ globals__lookup_bool_option(Globals, basic_stack_layout,
-		BasicStackLayout) },
-	( { BasicStackLayout = yes } ->
+	{ globals__lookup_bool_option(Globals, agc_stack_layout,
+		AgcStackLayout) },
+	( { AgcStackLayout = yes } ->
 		{ Proc = c_procedure(_, _, PredProcId, Instructions) },
 		{ module_info_get_continuation_info(ModuleInfo5, ContInfo2) },
 		write_proc_progress_message(
-		   "% Generating stack layout continuation information for ",
+			"% Generating call continuation information for ",
 				PredId, ProcId, ModuleInfo5),
 		{ continuation_info__process_instructions(PredProcId,
 			Instructions, ContInfo2, ContInfo3) },
@@ -1630,14 +1630,14 @@
 
 mercury_compile__maybe_generate_stack_layouts(ModuleInfo0, LLDS0, Verbose, 
 		Stats, ModuleInfo) -->
-	globals__io_lookup_bool_option(agc_stack_layout, StackLayout),
-	( { StackLayout = yes } ->
+	globals__io_lookup_bool_option(agc_stack_layout, AgcStackLayout),
+	( { AgcStackLayout = yes } ->
 		maybe_write_string(Verbose,
-			"% Generating stack layout continuation information..."),
+			"% Generating call continuation information..."),
 		maybe_flush_output(Verbose),
 		{ module_info_get_continuation_info(ModuleInfo0, ContInfo0) },
-		{ continuation_info__process_llds(LLDS0, ContInfo0,
-			ContInfo) },
+		{ continuation_info__process_llds(LLDS0,
+			ContInfo0, ContInfo) },
 		{ module_info_set_continuation_info(ModuleInfo0, ContInfo,
 			ModuleInfo) },
 		maybe_write_string(Verbose, " done.\n"),
Index: compiler/opt_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/opt_util.m,v
retrieving revision 1.90
diff -u -r1.90 opt_util.m
--- opt_util.m	1998/03/03 17:35:30	1.90
+++ opt_util.m	1998/03/16 04:26:50
@@ -282,16 +282,6 @@
 :- pred opt_util__rvals_free_of_lval(list(rval), lval).
 :- mode opt_util__rvals_free_of_lval(in, in) is semidet.
 
-	% Return the set of lvals referenced in an rval.
-
-:- pred opt_util__lvals_in_rval(rval, list(lval)).
-:- mode opt_util__lvals_in_rval(in, out) is det.
-
-	% Return the set of lvals referenced in an lval.
-
-:- pred opt_util__lvals_in_lval(lval, list(lval)).
-:- mode opt_util__lvals_in_lval(in, out) is det.
-
 	% Count the number of hp increments in a block of code.
 
 :- pred opt_util__count_incr_hp(list(instruction), int).
@@ -1544,59 +1534,6 @@
 opt_util__rval_free_of_lval(binop(_, Rval1, Rval2), Forbidden) :-
 	opt_util__rval_free_of_lval(Rval1, Forbidden),
 	opt_util__rval_free_of_lval(Rval2, Forbidden).
-
-%-----------------------------------------------------------------------------%
-
-opt_util__lvals_in_lval(reg(_, _), []).
-opt_util__lvals_in_lval(stackvar(_), []).
-opt_util__lvals_in_lval(framevar(_), []).
-opt_util__lvals_in_lval(succip, []).
-opt_util__lvals_in_lval(maxfr, []).
-opt_util__lvals_in_lval(curfr, []).
-opt_util__lvals_in_lval(succip(Rval), Lvals) :-
-	opt_util__lvals_in_rval(Rval, Lvals).
-opt_util__lvals_in_lval(redoip(Rval), Lvals) :-
-	opt_util__lvals_in_rval(Rval, Lvals).
-opt_util__lvals_in_lval(succfr(Rval), Lvals) :-
-	opt_util__lvals_in_rval(Rval, Lvals).
-opt_util__lvals_in_lval(prevfr(Rval), Lvals) :-
-	opt_util__lvals_in_rval(Rval, Lvals).
-opt_util__lvals_in_lval(hp, []).
-opt_util__lvals_in_lval(sp, []).
-opt_util__lvals_in_lval(field(_, Rval1, Rval2), Lvals) :-
-	opt_util__lvals_in_rval(Rval1, Lvals1),
-	opt_util__lvals_in_rval(Rval2, Lvals2),
-	list__append(Lvals1, Lvals2, Lvals).
-opt_util__lvals_in_lval(lvar(_), []).
-opt_util__lvals_in_lval(temp(_, _), []).
-opt_util__lvals_in_lval(mem_ref(Rval), Lvals) :-
-	opt_util__lvals_in_rval(Rval, Lvals).
-
-opt_util__lvals_in_rval(lval(Lval), [Lval | Lvals]) :-
-	opt_util__lvals_in_lval(Lval, Lvals).
-opt_util__lvals_in_rval(var(_), _) :-
-	error("found var in opt_util__lvals_in_rval").
-opt_util__lvals_in_rval(create(_, _, _, _, _), []).
-opt_util__lvals_in_rval(mkword(_, Rval), Lvals) :-
-	opt_util__lvals_in_rval(Rval, Lvals).
-opt_util__lvals_in_rval(const(_), []).
-opt_util__lvals_in_rval(unop(_, Rval), Lvals) :-
-	opt_util__lvals_in_rval(Rval, Lvals).
-opt_util__lvals_in_rval(binop(_, Rval1, Rval2), Lvals) :-
-	opt_util__lvals_in_rval(Rval1, Lvals1),
-	opt_util__lvals_in_rval(Rval2, Lvals2),
-	list__append(Lvals1, Lvals2, Lvals).
-opt_util__lvals_in_rval(mem_addr(MemRef), Lvals) :-
-	opt_util__lvals_in_mem_ref(MemRef, Lvals).
-
-	% XXX
-:- pred opt_util__lvals_in_mem_ref(mem_ref, list(lval)).
-:- mode opt_util__lvals_in_mem_ref(in, out) is det.
-
-opt_util__lvals_in_mem_ref(stackvar_ref(_), []).
-opt_util__lvals_in_mem_ref(framevar_ref(_), []).
-opt_util__lvals_in_mem_ref(heap_ref(Rval, _, _), Lvals) :-
-	opt_util__lvals_in_rval(Rval, Lvals).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/polymorphism.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/polymorphism.m,v
retrieving revision 1.130
diff -u -r1.130 polymorphism.m
--- polymorphism.m	1998/03/03 17:35:37	1.130
+++ polymorphism.m	1998/03/18 07:14:12
@@ -293,7 +293,7 @@
 :- import_module hlds_pred, hlds_goal, hlds_data, llds, (lambda).
 :- import_module prog_data, type_util, mode_util, quantification, instmap.
 :- import_module code_util, unify_proc, special_pred, prog_util, make_hlds.
-:- import_module (inst), hlds_out, base_typeclass_info.
+:- import_module (inst), hlds_out, base_typeclass_info, goal_util.
 
 :- import_module bool, int, string, list, set, map.
 :- import_module term, varset, std_util, require, assoc_list.
@@ -543,7 +543,7 @@
 
 	% process any polymorphic calls inside the goal
 	polymorphism__process_goal(Goal0, Goal1, Info0, Info1),
-	polymorphism__fixup_quantification(Goal1, Goal, Info1, Info),
+	polymorphism__fixup_quantification(Goal1, Goal, _, Info1, Info),
 	Info = poly_info(VarSet, VarTypes, TypeVarSet,
 				TypeInfoMap, TypeclassInfoLocations,
 				_Proofs, _PredName, ModuleInfo),
@@ -741,10 +741,11 @@
 		% lambda goal and then convert the lambda expression
 		% into a new predicate
 		polymorphism__process_goal(LambdaGoal0, LambdaGoal1),
-		polymorphism__fixup_quantification(LambdaGoal1, LambdaGoal),
+		polymorphism__fixup_quantification(LambdaGoal1,
+				LambdaGoal, NonLocalTypeInfos),
 		polymorphism__process_lambda(PredOrFunc, Vars, Modes,
-				Det, ArgVars, LambdaGoal, Unification,
-				Y1, Unification1),
+				Det, ArgVars, NonLocalTypeInfos, LambdaGoal,
+				Unification, Y1, Unification1),
 		{ Goal = unify(XVar, Y1, Mode, Unification1, Context)
 				- GoalInfo }
 	;
@@ -950,8 +951,8 @@
 	).
 
 :- pred polymorphism__fixup_quantification(hlds_goal, hlds_goal,
-		poly_info, poly_info).
-:- mode polymorphism__fixup_quantification(in, out, in, out) is det.
+		set(var), poly_info, poly_info).
+:- mode polymorphism__fixup_quantification(in, out, out, in, out) is det.
 
 %
 % If the predicate we are processing is a polymorphic predicate,
@@ -960,36 +961,18 @@
 % so that it includes the type-info variables in the non-locals set.
 %
 
-polymorphism__fixup_quantification(Goal0, Goal, Info0, Info) :-
+polymorphism__fixup_quantification(Goal0, Goal, NewOutsideVars, Info0, Info) :-
 	Info0 = poly_info(VarSet0, VarTypes0, TypeVarSet, TypeVarMap,
 			TypeClassVarMap, Proofs, PredName, ModuleInfo),
 	( map__is_empty(TypeVarMap) ->
+		set__init(NewOutsideVars),
 		Info = Info0,
 		Goal = Goal0
 	;
-		%
-		% A type-info variable may be non-local to a goal if any of 
-		% the ordinary non-local variables for that goal are
-		% polymorphically typed with a type that depends on that
-		% type-info variable.
-		%
-		% In addition, a typeclass-info may be non-local to a goal if
-		% any of the non-local variables for that goal are
-		% polymorphically typed and are constrained by the typeclass
-		% constraints for that typeclass-info variable
-		%
+		goal_util__extra_nonlocal_typeinfos(TypeVarMap,
+			VarTypes0, Goal0, NewOutsideVars),
 		Goal0 = _ - GoalInfo0,
 		goal_info_get_nonlocals(GoalInfo0, NonLocals),
-		set__to_sorted_list(NonLocals, NonLocalsList),
-		map__apply_to_list(NonLocalsList, VarTypes0, NonLocalsTypes),
-		term__vars_list(NonLocalsTypes, NonLocalTypeVars),
-			% Find all the type-infos and typeclass-infos that are
-			% non-local
-		solutions_set(lambda([Var::out] is nondet, (
-				list__member(TheVar, NonLocalTypeVars),
-				map__search(TypeVarMap, TheVar, Location),
-				type_info_locn_var(Location, Var)
-			)), NewOutsideVars),
 		set__union(NewOutsideVars, NonLocals, OutsideVars),
 		implicitly_quantify_goal(Goal0, VarSet0, VarTypes0,
 			OutsideVars, Goal, VarSet, VarTypes, _Warnings),
@@ -998,14 +981,15 @@
 	).
 
 :- pred polymorphism__process_lambda(pred_or_func, list(var),
-		list(mode), determinism, list(var), hlds_goal, unification,
-		unify_rhs, unification, poly_info, poly_info).
-:- mode polymorphism__process_lambda(in, in, in, in, in, in, in, out, out,
+		list(mode), determinism, list(var), set(var),
+		hlds_goal, unification, unify_rhs, unification,
+		poly_info, poly_info).
+:- mode polymorphism__process_lambda(in, in, in, in, in, in, in, in, out, out,
 		in, out) is det.
 
 polymorphism__process_lambda(PredOrFunc, Vars, Modes, Det, OrigNonLocals,
-		LambdaGoal, Unification0, Functor, Unification,
-		PolyInfo0, PolyInfo) :-
+		NonLocalTypeInfos, LambdaGoal, Unification0, Functor,
+		Unification, PolyInfo0, PolyInfo) :-
 	PolyInfo0 = poly_info(VarSet, VarTypes, TVarSet, TVarMap, 
 			TCVarMap, Proofs, PredName, ModuleInfo0),
 
@@ -1019,9 +1003,9 @@
 		AllConstraints, Constraints),
 
 	lambda__transform_lambda(PredOrFunc, PredName, Vars, Modes, Det,
-		OrigNonLocals, LambdaGoal, Unification0, VarSet, VarTypes,
-		Constraints, TVarSet, TVarMap, TCVarMap, ModuleInfo0, Functor,
-		Unification, ModuleInfo),
+		OrigNonLocals, NonLocalTypeInfos, LambdaGoal, Unification0,
+		VarSet, VarTypes, Constraints, TVarSet, TVarMap, TCVarMap,
+		ModuleInfo0, Functor, Unification, ModuleInfo),
 	PolyInfo = poly_info(VarSet, VarTypes, TVarSet, TVarMap, 
 			TCVarMap, Proofs, PredName, ModuleInfo).
 
Index: compiler/pragma_c_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/pragma_c_gen.m,v
retrieving revision 1.14
diff -u -r1.14 pragma_c_gen.m
--- pragma_c_gen.m	1998/03/03 17:35:38	1.14
+++ pragma_c_gen.m	1998/03/18 06:01:10
@@ -534,9 +534,10 @@
 
 	code_info__get_maybe_trace_info(MaybeTraceInfo),
 	( { MaybeTraceInfo = yes(TraceInfo) } ->
-		trace__generate_event_code(disj([disj(1)]), TraceInfo,
+		{ set__init(Empty) },
+		trace__generate_event_code(disj([disj(1)], Empty), TraceInfo,
 			FirstTraceCode),
-		trace__generate_event_code(disj([disj(2)]), TraceInfo,
+		trace__generate_event_code(disj([disj(2)], Empty), TraceInfo,
 			LaterTraceCode)
 	;
 		{ FirstTraceCode = empty },
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.9
diff -u -r1.9 stack_layout.m
--- stack_layout.m	1998/03/11 05:10:05	1.9
+++ stack_layout.m	1998/03/18 00:56:23
@@ -34,7 +34,7 @@
 % 					(the location will be set to -1
 % 					if there is no succip available).
 %
-% if the option procid_stack_layout is set, i.e. if we are doing stack
+% If the option procid_stack_layout is set, i.e. if we are doing stack
 % tracing, execution tracing or profiling, the table will also include
 % information on the identity of the procedure. This information will take
 % one of two forms. Almost all procedures use the first form:
@@ -63,36 +63,18 @@
 % The meanings of the fields in both forms are the same as in procedure labels.
 %
 % If the option trace_stack_layout is set, i.e. if we are doing execution
-% tracing, the table will also include information on the variables that are
-% live at entry to and exit from the procedure:
+% tracing, the table will also include one extra field:
 %
-% 	# of live vars at entry	(Integer)
-% 	live data pairs 	(Word *) - pointer to vector of pairs
-%				containing MR_Live_Lval and MR_Live_Type
-% 	live data names	 	(Word *) - pointer to vector of String
-%	type parameters		(Word *) - pointer to vector of MR_Live_Lval
-%
-% 	# of live vars at exit	(Integer)
-% 	live data pairs 	(Word *) - pointer to vector of pairs
-%				containing MR_Live_Lval and MR_Live_Type
-% 	live data names	 	(Word *) - pointer to vector of String
-%	type parameters		(Word *) - pointer to vector of MR_Live_Lval
-%
-% 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 (it also
-% has room for its instantiation state, but this is not filled in yet).
-%
-% The live data name vector pointer may be NULL. If it is not, the vector
-% will have an entry for each live variable, with each entry being either
-% NULL or giving the name of the variable.
+%	call trace info		(Word *) - pointer to label stack layout
 %
-% The number of type parameters is never stored as it is not needed --
-% the type parameter vector will simply be indexed by the type parameter
-% number stored within pseudo-typeinfos inside the elements of the live
-% data pairs vectors.
+% This will point to the per-label layout info for the label associated
+% with the call event at the entry to the procedure. The purpose of this
+% information 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.
 %
 % If the option basic_stack_layout is set, we generate stack layout tables
-% for all labels internal to the procedure. This table will be stored in the
+% for some labels internal to the procedure. This table will be stored in the
 % global variable whose name is
 %	mercury_data__stack_layout__mercury__<proc_label>_i<label_number>.
 % This table has the following format:
@@ -103,29 +85,42 @@
 % 	live data pairs 	(Word *) - pointer to vector of pairs
 %				containing MR_Live_Lval and MR_Live_Type
 % 	live data names	 	(Word *) - pointer to vector of String
-% 	live data names	 	(Word *) - pointer to vector of String
 %	type parameters		(Word *) - pointer to vector of MR_Live_Lval
 %
-% We need detailed information about the variables that are live at an internal
-% label in two kinds of circumstances:
+% 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. (It also
+% has room for its instantiation state, but this is not filled in yet.)
+%
+% The live data name vector pointer may be NULL. If it is not, the vector
+% will have an entry for each live variable, with each entry being either
+% NULL or giving the name of the variable.
 %
-% -	the option trace_stack_layout is set, and the label represents
-%	a traced event (with the current set of events, this means the
-%	the entrance to one branch of a branched control structure)
+% The number of type parameters is never stored as it is not needed --
+% the type parameter vector will simply be indexed 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,
+% in some cases, XXX
+%
+% 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.
+%
+% -	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 option agc_stack_layout is set, and the label represents
+% -	The option agc_stack_layout is set, and the label represents
 % 	a point where execution can resume after a procedure call or
 %	after backtracking.
 %
-% If either of these conditions holds for a given label at which there are some
-% live variables, all the fields above will be present in the stack layout
-% table for that label. However, the pointer to the live data names vector
-% will be NULL unless the first condition holds for the label (i.e. the label
-% is used in execution tracing).
-%
-% If neither condition holds for a given label, or if the number of live
-% variables at that label is zero, then the "# of live vars" field will be zero
-% and the last four fields will not be present.
+% If there are no number of live variables at a label, the "# of live vars"
+% field will be zero and the last four fields will not be present.
+% Even if there are some live variables at a label, however, the pointer
+% to the live data names vector will be NULL unless the first condition
+% holds for the label (i.e. the label is used in execution tracing).
 %
 % XXX: Presently, type parameter vectors are not created, and
 % inst information is ignored. We also do not yet enable procid stack
@@ -137,7 +132,8 @@
 
 :- interface.
 
-:- import_module hlds_module, list, llds.
+:- import_module hlds_module, llds.
+:- import_module list.
 
 :- pred stack_layout__generate_llds(module_info, module_info, list(c_module)).
 :- mode stack_layout__generate_llds(in, out, out) is det.
@@ -147,7 +143,7 @@
 :- import_module globals, options, continuation_info, llds_out.
 :- import_module hlds_data, hlds_pred, base_type_layout, prog_data, prog_out.
 :- import_module assoc_list, bool, string, int, map, std_util, require.
-:- import_module set.
+:- import_module term, set.
 
 :- type stack_layout_info 	--->	
 	stack_layout_info(
@@ -161,11 +157,13 @@
 
 %---------------------------------------------------------------------------%
 
-	% Initialize the StackLayoutInfo, and begin processing.
+	% Process all the continuation information stored in the HLDS,
+	% converting it into LLDS data structures.
+
 stack_layout__generate_llds(ModuleInfo0, ModuleInfo, CModules) :-
 	module_info_get_continuation_info(ModuleInfo0, ContinuationInfo),
-	continuation_info__get_all_proc_layouts(ProcLayoutList,
-		ContinuationInfo, _),
+	continuation_info__get_all_proc_layouts(ContinuationInfo,
+		ProcLayoutList),
 
 	module_info_name(ModuleInfo0, ModuleName),
 	module_info_get_cell_count(ModuleInfo0, CellCount),
@@ -186,42 +184,34 @@
 
 %---------------------------------------------------------------------------%
 
-	% Construct the layouts for a single procedure.
+	% Construct the layouts that concern a single procedure:
+	% the procedure-specific layout and the layouts of the labels
+	% inside that procedure.
 	
 :- pred stack_layout__construct_layouts(proc_layout_info::in,
-		stack_layout_info::in, stack_layout_info::out) is det.
+	stack_layout_info::in, stack_layout_info::out) is det.
 
 stack_layout__construct_layouts(ProcLayoutInfo) -->
-
-	{ ProcLayoutInfo = proc_layout_info(MaybeGeneralInfo, InternalMap,
-		EntryInfo, ExitInfo) },
-
-	( { MaybeGeneralInfo = yes(GeneralInfo) } ->
-		stack_layout__construct_proc_layout(GeneralInfo, EntryInfo,
-			ExitInfo),
-		{ GeneralInfo = proc_layout_general_info(ProcLabel, _, _, _) },
-		{ map__to_assoc_list(InternalMap, Internals) },
-		list__foldl(stack_layout__construct_internal_layout(ProcLabel),
-			Internals)
-	;
-		{ error("stack_layout__construct_layouts: uninitialized proc layout") }
-	).
+	{ ProcLayoutInfo = proc_layout_info(ProcLabel, Detism,
+		StackSlots, SuccipLoc, CallLabel, InternalMap) },
+	stack_layout__construct_proc_layout(ProcLabel, Detism,
+		StackSlots, SuccipLoc, CallLabel),
+	{ map__to_assoc_list(InternalMap, Internals) },
+	list__foldl(stack_layout__construct_internal_layout(ProcLabel),
+		Internals).
 
 %---------------------------------------------------------------------------%
 
-	% Construct the layout describing a single procedure.
+	% Construct a procedure-specific layout.
+
+:- pred stack_layout__construct_proc_layout(proc_label::in,
+	determinism::in, int::in, maybe(int)::in, maybe(label)::in,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred stack_layout__construct_proc_layout(proc_layout_general_info::in,
-		maybe(continuation_label_info)::in,
-		maybe(continuation_label_info)::in,
-		stack_layout_info::in, stack_layout_info::out) is det.
-
-stack_layout__construct_proc_layout(GeneralInfo, MaybeEntryInfo,
-		MaybeExitInfo) -->
-	{ GeneralInfo = proc_layout_general_info(ProcLabel, Detism,
-		StackSlots, SuccipLoc) },
+stack_layout__construct_proc_layout(ProcLabel, Detism, StackSlots,
+		MaybeSuccipLoc, MaybeCallLabel) -->
 	{
-		SuccipLoc = yes(Location0)
+		MaybeSuccipLoc = yes(Location0)
 	->
 		Location = Location0
 	;
@@ -244,27 +234,32 @@
 	{ stack_layout__represent_determinism(Detism, DetismRval) },
 	{ MaybeRvals0 = [yes(CodeAddrRval), yes(DetismRval),
 		yes(StackSlotsRval), yes(SuccipRval)] },
-	stack_layout__get_module_name(ModuleName),
 
 	stack_layout__get_procid_stack_layout(ProcIdLayout),
 	(
 		{ ProcIdLayout = yes }
 	->
 		{ stack_layout__construct_procid_rvals(ProcLabel, IdRvals) },
-		{ list__append(MaybeRvals0, IdRvals, MaybeRvals1) },
+		{ list__append(MaybeRvals0, IdRvals, MaybeRvals1) }
+	;
+		{ MaybeRvals1 = MaybeRvals0 }
+	),
 
-		stack_layout__get_trace_stack_layout(TraceLayout),
-		(
-			{ TraceLayout = yes }
-		->
-			stack_layout__construct_trace_rvals(MaybeEntryInfo,
-				MaybeExitInfo, TraceRvals),
-			{ list__append(MaybeRvals1, TraceRvals, MaybeRvals) }
+	stack_layout__get_module_name(ModuleName),
+	stack_layout__get_trace_stack_layout(TraceLayout),
+	(
+		{ TraceLayout = yes }
+	->
+		( { MaybeCallLabel = yes(CallLabel) } ->
+			{ CallRval = yes(const(data_addr_const(
+				data_addr(ModuleName,
+					stack_layout(CallLabel))))) },
+			{ list__append(MaybeRvals1, [CallRval], MaybeRvals) }
 		;
-			{ MaybeRvals = MaybeRvals1 }
+			{ error("stack_layout__construct_proc_layout: call label not present") }
 		)
 	;
-		{ MaybeRvals = MaybeRvals0 }
+		{ MaybeRvals = MaybeRvals1 }
 	),
 
 	{ CModule = c_data(ModuleName, stack_layout(Label), yes,
@@ -315,7 +310,7 @@
 
 %---------------------------------------------------------------------------%
 
-	% Construct the layout describing a single continuation label.
+	% Construct the layout describing a single internal label.
 
 :- pred stack_layout__construct_internal_layout(proc_label::in,
 	pair(label, internal_layout_info)::in,
@@ -326,74 +321,40 @@
 	stack_layout__get_module_name(ModuleName),
 	{ EntryAddrRval = const(data_addr_const(data_addr(ModuleName,
 		stack_layout(local(ProcLabel))))) },
-
-	stack_layout__construct_agc_rvals(Internal, AgcRvals),
-
-	{ LayoutRvals = [yes(EntryAddrRval) | AgcRvals] },
-
+	{ Label = local(_, LabelNum0) ->
+		LabelNum = LabelNum0
+	;
+		LabelNum = -1
+	},
+	{ LabelNumRval = const(int_const(LabelNum)) },
+	stack_layout__construct_internal_rvals(Internal, AgcRvals),
+	{ LayoutRvals = [yes(EntryAddrRval), yes(LabelNumRval) | AgcRvals] },
 	{ CModule = c_data(ModuleName, stack_layout(Label), yes,
 		LayoutRvals, []) },
 	stack_layout__add_cmodule(CModule).
 
-	% Construct the rvals required for tracing.
-
-:- pred stack_layout__construct_trace_rvals(maybe(continuation_label_info)::in,
-	maybe(continuation_label_info)::in, list(maybe(rval))::out,
-	stack_layout_info::in, stack_layout_info::out) is det.
-
-stack_layout__construct_trace_rvals(MaybeEntryInfo, MaybeExitInfo,
-		RvalList) -->
-	(
-		{ MaybeEntryInfo = yes(EntryInfo) },
-		{ MaybeExitInfo = yes(ExitInfo) }
-	->
-		{ EntryInfo = continuation_label_info(EntryLvals, EntryTVars) },
-		{ ExitInfo = continuation_label_info(ExitLvals, ExitTVars) },
-		stack_layout__construct_livelval_rvals(EntryLvals, EntryTVars,
-			EntryRvals),
-		stack_layout__construct_livelval_rvals(ExitLvals, ExitTVars,
-			ExitRvals),
-		{ list__append(EntryRvals, ExitRvals, RvalList) }
-	;
-		{ error("stack_layout__construct_trace_rvals: entry or exit information not available.") }
-	).
+	% Construct the rvals required for accurate GC or for tracing.
 
-	% Construct the rvals required for accurate GC.
-
-:- pred stack_layout__construct_agc_rvals(internal_layout_info::in,
+:- pred stack_layout__construct_internal_rvals(internal_layout_info::in,
 	list(maybe(rval))::out,
 	stack_layout_info::in, stack_layout_info::out) is det.
 
-stack_layout__construct_agc_rvals(Internal, RvalList) -->
-	stack_layout__get_agc_stack_layout(AgcStackLayout),
+stack_layout__construct_internal_rvals(Internal, RvalList) -->
 	(
-		{ AgcStackLayout = yes }
+		{ Internal = yes(layout_label_info(LiveLvalSet, TVars)) }
 	->
-		{ Internal = internal_layout_info(ContinuationLabelInfo) },
-		{
-			ContinuationLabelInfo = yes(continuation_label_info(
-				LiveLvalSet0, TVars0))
-		->
-			LiveLvalSet = LiveLvalSet0,
-			TVars = TVars0
-		;
-			% This label is not being used as a continuation,
-			% or we are not doing accurate GC, so we record
-			% no live values here.
-			% This might not be a true reflection of the
-			% liveness at this point, so the values cannot
-			% be relied upon by the runtime system unless
-			% you know you are at a continuation (and doing
-			% accurate GC).
-			
-			set__init(LiveLvalSet),
-			set__init(TVars)
-		},
 		stack_layout__construct_livelval_rvals(LiveLvalSet, TVars,
 			RvalList)
 	;
-		{ RvalList = [yes(const(int_const(0))),
-			yes(const(int_const(0)))] }
+		% This label is not being used as a continuation,
+		% or we are not doing accurate GC, so we record
+		% no live values here.
+		% This might not be a true reflection of the
+		% liveness at this point, so the values cannot
+		% be relied upon by the runtime system unless
+		% you know you are at a continuation (and doing
+		% accurate GC).
+		{ RvalList = [yes(const(int_const(0)))] }
 	).
 
 %---------------------------------------------------------------------------%
@@ -403,34 +364,60 @@
 		stack_layout_info, stack_layout_info).
 :- mode stack_layout__construct_livelval_rvals(in, in, out, in, out) is det.
 
-stack_layout__construct_livelval_rvals(LiveLvalSet, TVarSet, RvalList) -->
+stack_layout__construct_livelval_rvals(LiveLvalSet, TVarLocnSet, RvalList) -->
 	{ set__to_sorted_list(LiveLvalSet, LiveLvals) },
 	{ list__length(LiveLvals, Length) },
-	{ LengthRval = const(int_const(Length)) },
-	stack_layout__construct_liveval_pairs(LiveLvals, LiveValRval,
-		NamesRval),
-
-	{ set__to_sorted_list(TVarSet, TVars) },
-	{ assoc_list__values(TVars, TypeParamLvals) },
-	stack_layout__construct_type_parameter_locn_vector(TypeParamLvals,
-		TypeParamRval),
-
-	{ RvalList = [yes(LengthRval), yes(LiveValRval),
-		yes(NamesRval), yes(TypeParamRval)] }.
+	{ VarLengthRval = const(int_const(Length)) },
+	( { Length > 0 } ->
+		stack_layout__construct_liveval_pairs(LiveLvals, LiveValRval,
+			NamesRval),
+
+		{ set__to_sorted_list(TVarLocnSet, TVarLocns) },
+		stack_layout__construct_type_param_locn_vector(TVarLocns, 1,
+			TypeParamLocs),
+		stack_layout__get_next_cell_number(CNum1),
+		{ TypeParamRval = create(0, TypeParamLocs, no, CNum1,
+			"stack_layout_type_param_locn_vector") },
+		{ list__length(TypeParamLocs, TypeParamsLength) },
+		{ TypeParamLengthRval = const(int_const(TypeParamsLength)) },
+
+		{ RvalList = [yes(VarLengthRval), yes(LiveValRval),
+			yes(NamesRval), yes(TypeParamLengthRval),
+			yes(TypeParamRval)] }
+	;
+		{ RvalList = [yes(VarLengthRval)] }
+	).
 
 %---------------------------------------------------------------------------%
 
-:- pred stack_layout__construct_type_parameter_locn_vector(list(lval)::in,
-	rval::out, stack_layout_info::in, stack_layout_info::out) is det.
+	% Given a association list of type variables and their locations
+	% sorted on the type variables, represent them in an array of
+	% location descriptions indexed by the type variable. The next
+	% slot to fill is given by the second argument.
 
-stack_layout__construct_type_parameter_locn_vector(TypeParamLvals,
-		TypeParamVector) -->
-	{ MakeLval = lambda([Lval::in, yes(Rval)::out] is det, (
-		stack_layout__represent_lval(Lval, Rval))) },
-	{ list__map(MakeLval, TypeParamLvals, TypeParamLocs) },
-	stack_layout__get_next_cell_number(CNum1),
-	{ TypeParamVector = create(0, TypeParamLocs, no, CNum1,
-		"stack_layout_type_parameter_locn_vector") }.
+:- pred stack_layout__construct_type_param_locn_vector(
+	assoc_list(tvar, lval)::in, int::in, list(maybe(rval))::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
+
+stack_layout__construct_type_param_locn_vector([], _, []) --> [].
+stack_layout__construct_type_param_locn_vector([TVar - Locn | TVarLocns],
+		CurSlot, Vector) -->
+	{ term__var_to_int(TVar, TVarNum) },
+	{ NextSlot is CurSlot + 1 },
+	( { TVarNum = CurSlot } ->
+		{ stack_layout__represent_lval(Locn, Rval) },
+		stack_layout__construct_type_param_locn_vector(TVarLocns,
+			NextSlot, VectorTail),
+		{ Vector = [yes(Rval) | VectorTail] }
+	; { TVarNum > CurSlot } ->
+		stack_layout__construct_type_param_locn_vector(TVarLocns,
+			NextSlot, VectorTail),
+			% This slot will never be referred to.
+		{ Vector = [yes(const(int_const(0))) | VectorTail] }
+	;
+
+		{ error("unsorted tvars in construct_type_param_locn_vector") }
+	).
 
 	% Construct a vector of (lval, live_value_type) pairs,
 	% and a corresponding vector of variable names.
@@ -488,7 +475,7 @@
 	%
 	% Low integers for special values, a pointer for other values.
 	% (Remember to keep the low integers below the max varint value in
-	% runtime/type_info.h).
+	% runtime/mercury_type_info.h).
 
 :- pred stack_layout__represent_live_value_type(live_value_type, rval,
 	stack_layout_info, stack_layout_info).
@@ -509,8 +496,8 @@
 stack_layout__represent_live_value_type(var(Type, _Inst), Rval) -->
 	stack_layout__get_cell_number(CNum0),
 	{ base_type_layout__construct_pseudo_type_info(Type, Rval0,
-		CNum0, CNum) },
-	stack_layout__set_cell_number(CNum),
+		CNum0, CNum1) },
+	stack_layout__set_cell_number(CNum1),
 		% XXX hack - don't yet write out insts
 	{ Rval1 = const(int_const(-1)) },
 	stack_layout__get_next_cell_number(CNum2),
Index: compiler/store_alloc.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/store_alloc.m,v
retrieving revision 1.59
diff -u -r1.59 store_alloc.m
--- store_alloc.m	1998/02/12 01:17:46	1.59
+++ store_alloc.m	1998/03/11 06:58:15
@@ -37,7 +37,7 @@
 :- implementation.
 
 :- import_module follow_vars, liveness, hlds_goal, llds.
-:- import_module options, globals, goal_util, mode_util, instmap.
+:- import_module options, globals, goal_util, mode_util, instmap, trace.
 :- import_module list, map, set, std_util, assoc_list.
 :- import_module bool, int, require, term.
 
@@ -60,7 +60,12 @@
 		proc_info_goal(ProcInfo0, Goal2)
 	),
 	initial_liveness(ProcInfo0, ModuleInfo, Liveness0),
-	set__init(ResumeVars0),
+	globals__lookup_bool_option(Globals, generate_trace, Trace),
+	( Trace = yes ->
+		trace__fail_vars(ProcInfo0, ResumeVars0)
+	;
+		set__init(ResumeVars0)
+	),
 	store_alloc_in_goal(Goal2, Liveness0, ResumeVars0, ModuleInfo, Goal, _),
 	proc_info_set_goal(ProcInfo0, Goal, ProcInfo).
 
Index: compiler/string_switch.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/string_switch.m,v
retrieving revision 1.28
diff -u -r1.28 string_switch.m
--- string_switch.m	1998/03/03 17:36:05	1.28
+++ string_switch.m	1998/03/18 05:43:15
@@ -307,8 +307,9 @@
 		( { MaybeTraceInfo = yes(TraceInfo) } ->
 			{ Goal = _ - GoalInfo },
 			{ goal_info_get_goal_path(GoalInfo, Path) },
-			trace__generate_event_code(switch(Path), TraceInfo,
-				TraceCode)
+			{ goal_info_get_pre_deaths(GoalInfo, PreDeaths) },
+			trace__generate_event_code(switch(Path, PreDeaths),
+				TraceInfo, TraceCode)
 		;
 			{ TraceCode = empty }
 		),
Index: compiler/switch_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/switch_gen.m,v
retrieving revision 1.64
diff -u -r1.64 switch_gen.m
--- switch_gen.m	1998/03/03 17:36:06	1.64
+++ switch_gen.m	1998/03/18 05:43:36
@@ -311,7 +311,8 @@
 	( { MaybeTraceInfo = yes(TraceInfo) } ->
 		{ Goal = _ - GoalInfo },
 		{ goal_info_get_goal_path(GoalInfo, Path) },
-		trace__generate_event_code(switch(Path), TraceInfo,
+		{ goal_info_get_pre_deaths(GoalInfo, PreDeaths) },
+		trace__generate_event_code(switch(Path, PreDeaths), TraceInfo,
 			TraceCode)
 	;
 		{ TraceCode = empty }
Index: compiler/tag_switch.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/tag_switch.m,v
retrieving revision 1.43
diff -u -r1.43 tag_switch.m
--- tag_switch.m	1998/03/03 17:36:08	1.43
+++ tag_switch.m	1998/03/18 05:45:10
@@ -663,7 +663,10 @@
 			( { MaybeTraceInfo = yes(TraceInfo) } ->
 				{ Goal = _ - GoalInfo },
 				{ goal_info_get_goal_path(GoalInfo, Path) },
-				trace__generate_event_code(switch(Path),
+				{ goal_info_get_pre_deaths(GoalInfo,
+					PreDeaths) },
+				trace__generate_event_code(
+					switch(Path, PreDeaths),
 					TraceInfo, TraceCode)
 			;
 				{ TraceCode = empty }
@@ -807,8 +810,9 @@
 	( { MaybeTraceInfo = yes(TraceInfo) } ->
 		{ Goal = _ - GoalInfo },
 		{ goal_info_get_goal_path(GoalInfo, Path) },
-		trace__generate_event_code(switch(Path), TraceInfo,
-			TraceCode)
+		{ goal_info_get_pre_deaths(GoalInfo, PreDeaths) },
+		trace__generate_event_code(switch(Path, PreDeaths),
+			TraceInfo, TraceCode)
 	;
 		{ TraceCode = empty }
 	),
@@ -884,8 +888,9 @@
 	( { MaybeTraceInfo = yes(TraceInfo) } ->
 		{ Goal = _ - GoalInfo },
 		{ goal_info_get_goal_path(GoalInfo, Path) },
-		trace__generate_event_code(switch(Path), TraceInfo,
-			TraceCode)
+		{ goal_info_get_pre_deaths(GoalInfo, PreDeaths) },
+		trace__generate_event_code(switch(Path, PreDeaths),
+			TraceInfo, TraceCode)
 	;
 		{ TraceCode = empty }
 	),
@@ -980,7 +985,10 @@
 			( { MaybeTraceInfo = yes(TraceInfo) } ->
 				{ Goal = _ - GoalInfo },
 				{ goal_info_get_goal_path(GoalInfo, Path) },
-				trace__generate_event_code(switch(Path),
+				{ goal_info_get_pre_deaths(GoalInfo,
+					PreDeaths) },
+				trace__generate_event_code(
+					switch(Path, PreDeaths),
 					TraceInfo, TraceCode)
 			;
 				{ TraceCode = empty }
@@ -1063,7 +1071,10 @@
 			( { MaybeTraceInfo = yes(TraceInfo) } ->
 				{ Goal = _ - GoalInfo },
 				{ goal_info_get_goal_path(GoalInfo, Path) },
-				trace__generate_event_code(switch(Path),
+				{ goal_info_get_pre_deaths(GoalInfo,
+					PreDeaths) },
+				trace__generate_event_code(
+					switch(Path, PreDeaths),
 					TraceInfo, TraceCode)
 			;
 				{ TraceCode = empty }
Index: compiler/termination.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/termination.m,v
retrieving revision 1.11
diff -u -r1.11 termination.m
--- termination.m	1998/03/18 08:07:47	1.11
+++ termination.m	1998/03/19 06:27:21
@@ -47,8 +47,8 @@
 
 :- interface.
 
-:- import_module io, bool, std_util, list.
 :- import_module prog_data, hlds_module, hlds_pred, term_util.
+:- import_module list, io, bool, std_util.
 
 	% Perform termination analysis on the module.
 
@@ -84,7 +84,7 @@
 :- import_module mercury_to_mercury, varset, type_util, special_pred.
 :- import_module modules.
 
-:- import_module map, int, char, string, relation.
+:- import_module list, map, int, char, string, relation.
 :- import_module require, bag, set, term.
 
 %----------------------------------------------------------------------------%
Index: compiler/trace.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/trace.m,v
retrieving revision 1.7
diff -u -r1.7 trace.m
--- trace.m	1998/02/03 08:18:35	1.7
+++ trace.m	1998/03/18 06:01:46
@@ -25,35 +25,53 @@
 
 :- interface.
 
-:- import_module hlds_goal, llds, code_info.
+:- import_module prog_data, hlds_goal, hlds_pred, llds, code_info.
+:- import_module list, assoc_list, set, term.
 
 :- type trace_port	--->	call
 			;	exit
 			;	fail
-			;	ite_then(goal_path)
-			;	ite_else(goal_path)
-			;	switch(goal_path)
-			;	disj(goal_path).
+			;	ite_then(goal_path, set(var))
+			;	ite_else(goal_path, set(var))
+			;	switch(goal_path, set(var))
+			;	disj(goal_path, set(var)).
 
 :- type trace_info.
 
+	% Return the set of input variables whose values should be preserved
+	% until the exit and fail ports. This should be all input variables,
+	% except those that may be clobbered during the evaluation of the
+	% procedure.
+:- pred trace__fail_vars(proc_info::in, set(var)::out) is det.
+
+	% Set up the code generator state for tracing, by reserving
+	% slots for the call number and call depth.
 :- pred trace__setup(code_info::in, code_info::out) is det.
 
+	% Generate code to fill in the slots for the call number and depth.
 :- pred trace__generate_slot_fill_code(trace_info::in, code_tree::out) is det.
 
+	% Generate code to reset the call depth before a call.
 :- pred trace__generate_depth_reset_code(trace_info::in, code_tree::out) is det.
 
+	% Generate code for a trace event.
 :- pred trace__generate_event_code(trace_port::in, trace_info::in,
 	code_tree::out, code_info::in, code_info::out) is det.
 
+	% Generate code for a trace event, returning the
+:- pred trace__generate_event_code(trace_port::in, trace_info::in,
+	label::out, assoc_list(tvar, lval)::out, code_tree::out,
+	code_info::in, code_info::out) is det.
+
 :- pred trace__path_to_string(goal_path::in, string::out) is det.
 
 %-----------------------------------------------------------------------------%
 
 :- implementation.
 
-:- import_module hlds_module, hlds_pred, llds_out, code_util, tree.
-:- import_module bool, int, list, std_util, string, require.
+:- import_module hlds_module, llds_out, code_util, type_util.
+:- import_module arg_info, continuation_info, instmap, tree.
+:- import_module bool, int, string, map, std_util, varset, require.
 
 :- type trace_info
 	--->	trace_info(
@@ -61,6 +79,18 @@
 			lval	% stack slot of call depth
 		).
 
+trace__fail_vars(ProcInfo, FailVars) :-
+	proc_info_headvars(ProcInfo, HeadVars),
+	proc_info_arg_info(ProcInfo, ArgInfos),
+	assoc_list__from_corresponding_lists(HeadVars, ArgInfos, Args),
+	arg_info__build_input_arg_list(Args, ArgList),
+	assoc_list__keys(ArgList, InputArgs),
+		% We do not yet delete input vars that have any components
+		% that could be clobbered, because the modules of the mode
+		% system do not have any utility predicates for testing for
+		% this.
+	set__list_to_set(InputArgs, FailVars).
+
 trace__setup -->
 	code_info__get_trace_slot(CallNumSlot),
 	code_info__get_trace_slot(CallDepthSlot),
@@ -89,13 +119,30 @@
 		c_code(Stmt) - ""
 	]).
 
-trace__generate_event_code(Port, TraceInfo, TraceCode) -->
-	code_info__get_pred_id(PredId),
-	code_info__get_proc_id(ProcId),
-	code_info__get_module_info(ModuleInfo),
+trace__generate_event_code(Port, TraceInfo, Code) -->
+	trace__generate_event_code(Port, TraceInfo, _, _, Code).
+
+trace__generate_event_code(Port, TraceInfo, Label, TvarDataList, Code) -->
+	code_info__get_next_label(Label),
+	code_info__get_known_variables(LiveVars0),
+	{ trace__apply_pre_deaths(Port, LiveVars0, LiveVars) },
+	code_info__get_varset(VarSet),
+	code_info__get_instmap(InstMap),
+	{ set__init(TvarSet0) },
+	trace__produce_vars(LiveVars, VarSet, InstMap, TvarSet0, TvarSet,
+		VarInfoList, ProduceCode),
+	{ set__to_sorted_list(TvarSet, TvarList) },
+	code_info__variable_locations(VarLocs),
+        code_info__get_proc_info(ProcInfo),
+	{ proc_info_typeinfo_varmap(ProcInfo, TypeInfoMap) },
+	{ trace__find_typeinfos_for_tvars(TvarList, VarLocs, TypeInfoMap,
+		TvarDataList) },
+	code_info__max_reg_in_use(MaxReg),
 	{
-	code_util__make_proc_label(ModuleInfo, PredId, ProcId, ProcLabel),
-	llds_out__get_label(local(ProcLabel), yes, LabelStr),
+	set__list_to_set(VarInfoList, VarInfoSet),
+	set__list_to_set(TvarDataList, TvarDataSet),
+	LayoutLabelInfo = layout_label_info(VarInfoSet, TvarDataSet),
+	llds_out__get_label(Label, yes, LabelStr),
 	TraceInfo = trace_info(CallNumLval, CallDepthLval),
 	trace__stackref_to_string(CallNumLval, CallNumStr),
 	trace__stackref_to_string(CallDepthLval, CallDepthStr),
@@ -107,35 +154,136 @@
 	;
 		PathStr = ""
 	),
+	IfStmt = "\tif (MR_trace_enabled) {\n",
+	EndStmt = "\t}\n",
+	SaveStmt = "\t\tsave_transient_registers();\n",
+	RestoreStmt = "\t\trestore_transient_registers();\n",
+	string__int_to_string(MaxReg, MaxRegStr),
 	string__append_list([
-		"MR_trace(",
-		"(const Word *) &mercury_data__stack_layout__", LabelStr, Comma,
-		PortStr, Comma,
+		"\t\tMR_trace((const MR_Stack_Layout_Label *)\n",
+		"\t\t\t&mercury_data__stack_layout__", LabelStr, Comma, "\n",
+		"\t\t\t", PortStr, Comma,
 		CallNumStr, Comma,
 		CallDepthStr, Comma,
-		Quote, PathStr, Quote, ");\n"],
+		Quote, PathStr, Quote, Comma,
+		MaxRegStr, ");\n"],
+		CallStmt),
+	string__append_list([IfStmt, SaveStmt, CallStmt, RestoreStmt, EndStmt],
 		TraceStmt),
-	TraceCode = node([c_code(TraceStmt) - ""])
-	}.
+	TraceCode =
+		node([
+			pragma_c([], [pragma_c_raw_code(TraceStmt)],
+				may_call_mercury, yes(Label))
+				- "",
+			label(Label)
+				- "A label to hang trace liveness on"
+				% Referring to the label from the pragma_c
+				% prevents the label from being renamed
+				% or optimized away.
+		]),
+	Code = tree(ProduceCode, TraceCode)
+	},
+	code_info__add_layout_for_label(Label, yes(LayoutLabelInfo)).
+
+:- pred trace__produce_vars(list(var)::in, varset::in, instmap::in,
+	set(tvar)::in, set(tvar)::out, list(var_info)::out, code_tree::out,
+	code_info::in, code_info::out) is det.
+
+trace__produce_vars([], _, _, Tvars, Tvars, [], empty) --> [].
+trace__produce_vars([Var | Vars], VarSet, InstMap, Tvars0, Tvars,
+		[VarInfo | VarInfos], tree(VarCode, VarsCode)) -->
+	code_info__produce_variable_in_reg_or_stack(Var, VarCode, Rval),
+	code_info__variable_type(Var, Type),
+	{
+	( Rval = lval(LvalPrime) ->
+		Lval = LvalPrime
+	;
+		error("var not an lval in trace__produce_vars")
+		% If the value of the variable is known,
+		% we record it as living in a nonexistent location, r0.
+		% The code that interprets layout information must know this.
+		% Lval = reg(r, 0)
+	),
+	varset__lookup_name(VarSet, Var, "V_", Name),
+	instmap__lookup_var(InstMap, Var, Inst),
+	LiveType = var(Type, Inst),
+	VarInfo = var_info(Lval, LiveType, Name),
+	type_util__vars(Type, TypeVars),
+	set__insert_list(Tvars0, TypeVars, Tvars1)
+	},
+	trace__produce_vars(Vars, VarSet, InstMap, Tvars1, Tvars,
+		VarInfos, VarsCode).
+
+	% For each type variable in the given list, find out where the
+	% typeinfo var for that type variable is.
+
+:- pred trace__find_typeinfos_for_tvars(list(tvar)::in,
+	map(var, set(rval))::in, map(tvar, type_info_locn)::in,
+	assoc_list(tvar, lval)::out) is det.
+
+trace__find_typeinfos_for_tvars(TypeVars, VarLocs, TypeInfoMap, TypeInfoDatas)
+		:-
+	map__apply_to_list(TypeVars, TypeInfoMap, TypeInfoLocns),
+	list__map(type_info_locn_var, TypeInfoLocns, TypeInfoVars),
+
+	map__apply_to_list(TypeInfoVars, VarLocs, TypeInfoLvalSets),
+	FindSingleLval = lambda([Set::in, Lval::out] is det, (
+		(
+			set__remove_least(Set, Value, _),
+			Value = lval(Lval0)
+		->
+			Lval = Lval0
+		;
+			error("trace__find_typeinfos_for_tvars: typeinfo var not available")
+		))
+	),
+	list__map(FindSingleLval, TypeInfoLvalSets, TypeInfoLvals),
+	assoc_list__from_corresponding_lists(TypeVars, TypeInfoLvals,
+		TypeInfoDatas).
+
+%-----------------------------------------------------------------------------%
+
+:- pred trace__apply_pre_deaths(trace_port::in, list(var)::in, list(var)::out)
+	is det.
+
+trace__apply_pre_deaths(call, LiveVars, LiveVars).
+trace__apply_pre_deaths(exit, LiveVars, LiveVars).
+trace__apply_pre_deaths(fail, LiveVars, LiveVars).
+trace__apply_pre_deaths(ite_then(_, PreDeaths), LiveVars0, LiveVars) :-
+	set__list_to_set(LiveVars0, LiveVars0Set),
+	set__difference(LiveVars0Set, PreDeaths, LiveVarsSet),
+	set__to_sorted_list(LiveVarsSet, LiveVars).
+trace__apply_pre_deaths(ite_else(_, PreDeaths), LiveVars0, LiveVars) :-
+	set__list_to_set(LiveVars0, LiveVars0Set),
+	set__difference(LiveVars0Set, PreDeaths, LiveVarsSet),
+	set__to_sorted_list(LiveVarsSet, LiveVars).
+trace__apply_pre_deaths(switch(_, PreDeaths), LiveVars0, LiveVars) :-
+	set__list_to_set(LiveVars0, LiveVars0Set),
+	set__difference(LiveVars0Set, PreDeaths, LiveVarsSet),
+	set__to_sorted_list(LiveVarsSet, LiveVars).
+trace__apply_pre_deaths(disj(_, PreDeaths), LiveVars0, LiveVars) :-
+	set__list_to_set(LiveVars0, LiveVars0Set),
+	set__difference(LiveVars0Set, PreDeaths, LiveVarsSet),
+	set__to_sorted_list(LiveVarsSet, LiveVars).
 
 %-----------------------------------------------------------------------------%
 
 :- pred trace__port_path(trace_port::in, goal_path::out) is semidet.
 
-trace__port_path(ite_then(Path), Path).
-trace__port_path(ite_else(Path), Path).
-trace__port_path(switch(Path),   Path).
-trace__port_path(disj(Path),     Path).
+trace__port_path(ite_then(Path, _), Path).
+trace__port_path(ite_else(Path, _), Path).
+trace__port_path(switch(Path, _), Path).
+trace__port_path(disj(Path, _), Path).
 
 :- pred trace__port_to_string(trace_port::in, string::out) is det.
 
 trace__port_to_string(call, "MR_PORT_CALL").
 trace__port_to_string(exit, "MR_PORT_EXIT").
 trace__port_to_string(fail, "MR_PORT_FAIL").
-trace__port_to_string(ite_then(_), "MR_PORT_THEN").
-trace__port_to_string(ite_else(_), "MR_PORT_ELSE").
-trace__port_to_string(switch(_),   "MR_PORT_SWITCH").
-trace__port_to_string(disj(_),     "MR_PORT_DISJ").
+trace__port_to_string(ite_then(_, _), "MR_PORT_THEN").
+trace__port_to_string(ite_else(_, _), "MR_PORT_ELSE").
+trace__port_to_string(switch(_, _),   "MR_PORT_SWITCH").
+trace__port_to_string(disj(_, _),     "MR_PORT_DISJ").
 
 :- pred trace__code_model_to_string(code_model::in, string::out) is det.
 
Index: compiler/vn_filter.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/vn_filter.m,v
retrieving revision 1.15
diff -u -r1.15 vn_filter.m
--- vn_filter.m	1998/01/13 10:14:09	1.15
+++ vn_filter.m	1998/03/16 04:30:41
@@ -25,7 +25,7 @@
 
 :- implementation.
 
-:- import_module opt_util.
+:- import_module code_util, opt_util.
 :- import_module require, std_util.
 
 	% Look for assignments to temp variables. If possible and profitable,
@@ -38,7 +38,7 @@
 		Instr0 = Uinstr0 - _,
 		Uinstr0 = assign(Temp, Defn),
 		Temp = temp(_, _),
-		opt_util__lvals_in_rval(Defn, Deps),
+		code_util__lvals_in_rval(Defn, Deps),
 		vn_filter__can_substitute(Instrs0, Temp, Defn, Deps,
 			Instrs1)
 	->
@@ -73,7 +73,7 @@
 	Instr0 = Uinstr0 - Comment,
 	(
 		vn_filter__user_instr(Uinstr0, yes(Rval)),
-		opt_util__lvals_in_rval(Rval, Lvals),
+		code_util__lvals_in_rval(Rval, Lvals),
 		list__delete_first(Lvals, Temp, OtherLvals)
 	->
 		% We don't want to perform the subsitution
@@ -81,7 +81,7 @@
 		\+ list__member(Temp, OtherLvals),
 		\+ (
 			vn_filter__defining_instr(Uinstr0, yes(Lval)),
-			opt_util__lvals_in_lval(Lval, AccessLvals),
+			code_util__lvals_in_lval(Lval, AccessLvals),
 			list__member(Temp, AccessLvals)
 		),
 		vn_filter__replace_in_user_instr(Uinstr0, Temp, Defn, Uinstr1),
@@ -99,7 +99,7 @@
 		->
 			fail
 		;
-			opt_util__lvals_in_lval(Lval, AccessLvals),
+			code_util__lvals_in_lval(Lval, AccessLvals),
 			list__delete_first(AccessLvals, Temp, OtherAccessLvals)
 		->
 			\+ list__member(Temp, OtherAccessLvals),
Index: library/require.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/require.m,v
retrieving revision 1.18
diff -u -r1.18 require.m
--- require.m	1998/03/11 05:57:41	1.18
+++ require.m	1998/03/20 08:06:15
@@ -58,6 +58,7 @@
 :- pragma c_code(error(Message::in), "
 	fflush(stdout);
 	fprintf(stderr, ""Software error: %s\\n"", Message);
+	MR_trace_report();
 	MR_dump_stack(MR_succip, MR_sp);
 	exit(1);
 #ifndef USE_GCC_NONLOCAL_GOTOS
Index: runtime/mercury_misc.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_misc.c,v
retrieving revision 1.4
diff -u -r1.4 mercury_misc.c
--- mercury_misc.c	1998/03/16 12:23:33	1.4
+++ mercury_misc.c	1998/03/20 08:06:01
@@ -468,6 +468,7 @@
 void 
 fatal_error(const char *message) {
 	fprintf(stderr, "Mercury runtime: %s\n", message);
+	MR_trace_report();
 	exit(1);
 }
 
Index: runtime/mercury_regorder.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_regorder.h,v
retrieving revision 1.2
diff -u -r1.2 mercury_regorder.h
--- mercury_regorder.h	1997/11/23 07:21:32	1.2
+++ mercury_regorder.h	1998/03/16 05:06:30
@@ -55,6 +55,11 @@
 #define r31		count_usage(R_RN(31), mr35)
 #define r32		count_usage(R_RN(32), mr36)
 
+/*
+** If you modify the following block, make sure that you update
+** the definitions of MR_NUM_SPECIAL_REG and MR_MAX_SPECIAL_REG_MR.
+*/
+
 #define MR_succip	LVALUE_CAST(Code *, count_usage(MR_SI_RN, mr1))
 #define succip		MR_succip
 #define MR_hp		LVALUE_CAST(Word *, count_usage(MR_HP_RN, mr5))
@@ -73,6 +78,12 @@
 #define MR_trail_ptr	count_usage(MR_TRAIL_PTR_RN, MR_trail_ptr_var)
 #define MR_ticket_counter	 \
 		count_usage(MR_TICKET_COUNTER_RN, MR_ticket_counter_var)
+
+/* the number of special, non rN registers */
+#define MR_NUM_SPECIAL_REG	10
+
+/* the maximum mrN number of special, non rN registers */
+#define	MR_MAX_SPECIAL_REG_MR	39
 
 #define VIRTUAL_REG_MAP_BODY	{ \
 	2, \
Index: runtime/mercury_stack_layout.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_layout.h,v
retrieving revision 1.2
diff -u -r1.2 mercury_stack_layout.h
--- mercury_stack_layout.h	1998/03/11 22:07:30	1.2
+++ mercury_stack_layout.h	1998/03/18 05:05:54
@@ -10,6 +10,10 @@
 /*
 ** mercury_stack_layout.h -
 **	Definitions for the stack layout data structures. 
+**
+** NOTE: The constants and data-structures used here need to be kept in
+** sync with the ones generated in the compiler. If you change anything here,
+** you may need to change compiler/stack_layout.m as well.
 */
 
 /*
@@ -49,7 +53,8 @@
 
 #define MR_DETISM_FIRST_SOLN(d)		(((d) & 8) != 0)
 
-#define MR_DETISM_DET_CODE_MODEL(d)	(((d) & 1) == 0)
+#define MR_DETISM_DET_CODE_MODEL(d)	(!MR_DETISM_AT_MOST_MANY(d) \
+					|| MR_DETISM_FIRST_SOLN(d))
 
 /*
 ** Definitions for "MR_Live_Lval"
@@ -112,7 +117,7 @@
 ** The data is encoded such that low values (less than
 ** TYPELAYOUT_MAX_VARINT) represent succip, hp, etc.  Higher values
 ** represent data variables, and are pointers to a 2 word cell, 
-** containing a type_info and an instantiation represention.
+** containing a pseudo type_info and an instantiation represention.
 **
 ** This data is generated in compiler/stack_layout.m, which must be kept
 ** in sync with the constants defined here.
@@ -130,7 +135,7 @@
 } MR_Lval_NonVar;
 
 typedef struct { 
-	Word	type;	/* contains a type_info */
+	Word	*pseudo_type_info;
 	Word	inst;	/* not yet used; currently always -1 */
 } MR_Var_Shape_Info;
 
@@ -140,10 +145,10 @@
 		((MR_Lval_NonVar) T)
 
 #define MR_LIVE_TYPE_GET_VAR_TYPE(T)   			\
-		((Word) ((MR_Var_Shape_Info *) T)->type)
+		(((MR_Var_Shape_Info *) T)->pseudo_type_info)
 
 #define MR_LIVE_TYPE_GET_VAR_INST(T)   			\
-		((Word) ((MR_Var_Shape_Info *) T)->inst)
+		(((MR_Var_Shape_Info *) T)->inst)
 
 /*
 ** Macros to support hand-written C code.
@@ -151,9 +156,10 @@
 
 /*
 ** Define a stack layout for a label that you know very little about.
-** It's just a generic entry label, no useful information, except
+** It is just a generic entry label, no useful information, except
 ** the code address for the label.
 */ 
+
 #ifdef MR_USE_STACK_LAYOUTS
  #define MR_MAKE_STACK_LAYOUT_ENTRY(l) 					\
  const struct mercury_data__stack_layout__##l##_struct {		\
@@ -178,6 +184,7 @@
 ** The only useful information in this structure is the code address
 ** and the reference to the entry for this label.
 */ 
+
 #ifdef MR_USE_STACK_LAYOUTS
  #define MR_MAKE_STACK_LAYOUT_INTERNAL_WITH_ENTRY(l, e)			\
  const struct mercury_data__stack_layout__##l##_struct {		\
@@ -208,6 +215,7 @@
 ** The only useful information in this structure is the code address
 ** and the reference to the entry for this label.
 */ 
+
 #ifdef MR_USE_STACK_LAYOUTS
  #define MR_MAKE_STACK_LAYOUT_INTERNAL(e, x)				\
  const struct mercury_data__stack_layout__##e##_i##x##_struct {		\
@@ -227,18 +235,25 @@
 ** Structs and macros to support stack layouts.
 */
 
-typedef	struct MR_stack_layout_var_struct {
+typedef	struct MR_Stack_Layout_Var_Struct {
 	MR_Live_Lval		MR_slv_locn;
 	MR_Live_Type		MR_slv_live_type;
-} MR_stack_layout_var;
+} MR_Stack_Layout_Var;
 
-typedef	struct MR_stack_layout_vars_struct {
-	MR_stack_layout_var	*MR_slvs_pairs;
+typedef	struct MR_Stack_Layout_Vars_Struct {
+	MR_Stack_Layout_Var	*MR_slvs_pairs;
 	String			*MR_slvs_names;
-	Word			*MR_slvs_tvars;
-} MR_stack_layout_vars;
+	Integer			MR_slvs_tvar_count;
+	MR_Live_Lval		*MR_slvs_tvars;
+} MR_Stack_Layout_Vars;
+
+#define	MR_name_if_present(vars, i)					\
+				((vars->MR_slvs_names != NULL		\
+				&& vars->MR_slvs_names[(i)] != NULL)	\
+				? vars->MR_slvs_names[(i)]		\
+				: "")
 
-typedef	struct MR_stack_layout_entry_struct {
+typedef	struct MR_Stack_Layout_Entry_Struct {
 	Code			*MR_sle_code_addr;
 	MR_Determinism		MR_sle_detism;
 	Integer			MR_sle_stack_slots;
@@ -251,18 +266,17 @@
 	Integer			MR_sle_arity;
 	Integer			MR_sle_mode;
 	/* the fields from here onwards are present only with trace layouts */
-	Integer			MR_sle_in_arg_count;
-	MR_stack_layout_vars	MR_sle_in_arg_info;
-	Integer			MR_sle_out_arg_count;
-	MR_stack_layout_vars	MR_sle_out_arg_info;
-} MR_stack_layout_entry;
-
-typedef	struct MR_stack_layout_label_struct {
-	MR_stack_layout_entry	*MR_sll_entry;
+	struct MR_Stack_Layout_Label_Struct
+				*MR_sle_call_label;
+} MR_Stack_Layout_Entry;
+
+typedef	struct MR_Stack_Layout_Label_Struct {
+	MR_Stack_Layout_Entry	*MR_sll_entry;
+	Integer			MR_sll_label_num;
 	Integer			MR_sll_var_count;
 	/* the last field is present only if MR_sll_var_count > 0 */
-	MR_stack_layout_vars	MR_sll_var_info;
-} MR_stack_layout_label;
+	MR_Stack_Layout_Vars	MR_sll_var_info;
+} MR_Stack_Layout_Label;
 
 /* The following macros support obsolete code. */
 #define MR_ENTRY_STACK_LAYOUT_GET_LABEL_ADDRESS(s)		\
@@ -282,4 +296,3 @@
 
 /*---------------------------------------------------------------------------*/
 #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.2
diff -u -r1.2 mercury_stack_trace.c
--- mercury_stack_trace.c	1998/03/16 12:23:37	1.2
+++ mercury_stack_trace.c	1998/03/20 08:11:17
@@ -17,13 +17,12 @@
 void
 MR_dump_stack(Code *success_pointer, Word *det_stack_pointer)
 {
-	Label *label;
-	MR_Live_Lval location;
-	MR_stack_layout_label *layout;
-	MR_stack_layout_entry *entry_layout;
-	MR_Lval_Type type;
-	int number, determinism;
-
+	Label			*label;
+	MR_Live_Lval		location;
+	MR_Stack_Layout_Label	*layout;
+	MR_Stack_Layout_Entry	*entry_layout;
+	MR_Lval_Type		type;
+	int			number, determinism;
 
 #ifndef MR_STACK_TRACE
 	fprintf(stderr, "Stack dump not available in this grade.\n");
@@ -36,7 +35,7 @@
 			fatal_error("internal label not found");
 		}
 
-		layout = (MR_stack_layout_label *) label->e_layout;
+		layout = (MR_Stack_Layout_Label *) label->e_layout;
 		entry_layout = layout->MR_sll_entry;
 		
 		label = lookup_label_addr(
@@ -65,4 +64,3 @@
 	} while (MR_DETISM_DET_CODE_MODEL(determinism));
 #endif /* MR_STACK_TRACE */
 }
-
Index: runtime/mercury_trace.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace.c,v
retrieving revision 1.8
diff -u -r1.8 mercury_trace.c
--- mercury_trace.c	1998/03/11 22:07:31	1.8
+++ mercury_trace.c	1998/03/20 08:11:37
@@ -18,7 +18,29 @@
 #include "mercury_trace.h"
 #include "mercury_engine.h"
 #include "mercury_wrapper.h"
+#include "mercury_misc.h"
 #include <stdio.h>
+#include <ctype.h>
+
+/*
+** Do we want to use the debugger within this process, or do want to use
+** the Opium-style trace analyzer debugger implemented by an external process.
+** This variable is set in mercury_wrapper.c and never modified afterwards.
+*/
+
+MR_trace_type	MR_trace_handler = MR_TRACE_INTERNAL;
+
+/*
+** Compiler generated tracing code will check whether MR_trace_enabled is true,
+** before calling MR_trace. For now, and until we implement interface tracing,
+** MR_trace_enabled should keep the same value throughout the execution of
+** the entire program after being set in mercury_wrapper.c. There is one
+** exception to this: the Mercury routines called as part of the functionality
+** of the tracer itself (e.g. the term browser) should always be executed
+** with MR_trace_enabled set to FALSE.
+*/
+
+bool	MR_trace_enabled = FALSE;
 
 /*
 ** MR_trace_call_seqno counts distinct calls. The prologue of every
@@ -42,11 +64,13 @@
 int	MR_trace_call_depth = 0;
 
 /*
-** MR_trace_event_number is a simple counter of events; currently we only
-** use it for display.
+** MR_trace_event_number is a simple counter of events. This is used in
+** two places: here, for display to the user and for skipping a given number
+** of events, and when printing an abort message, so that the programmer
+** can zero in on the source of the problem more quickly.
 */
 
-static	int	MR_trace_event_number = 0;
+int	MR_trace_event_number = 0;
 
 /*
 ** MR_trace_cmd and MR_trace_seqno are globals variables that we use
@@ -61,17 +85,16 @@
 */
 
 typedef enum {
-	MR_CMD_CONT,	/* c: continue to end, not printing the trace	  */
-	MR_CMD_DUMP,	/* d: continue to end, printing the trace	  */
-	MR_CMD_NEXT,	/* n: go to the next trace event		  */
-	MR_CMD_SKIP,	/* s: skip the current call, not printing trace	  */
-	MR_CMD_JUMP	/* j: jump to end of current call, printing trace */
+	MR_CMD_GOTO,
+	MR_CMD_FINISH,
+	MR_CMD_TO_END
 } MR_trace_cmd_type;
 
 /*
 ** This type must match the definition of classify_request in
 ** library/debugger_interface.m.
 */
+
 typedef enum {
 	MR_REQUEST_HELLO_REPLY = 0,  /* initiate debugging session	    */
 	MR_REQUEST_FORWARD_MOVE = 1, /* go to the next matching trace event */
@@ -81,8 +104,10 @@
 	MR_REQUEST_ERROR = 5         /* something went wrong                */
 } MR_debugger_request_type;
 
-static	MR_trace_cmd_type	MR_trace_cmd = MR_CMD_NEXT;
-static	int			MR_trace_seqno = 0;
+static	MR_trace_cmd_type	MR_trace_cmd = MR_CMD_GOTO;
+static	int			MR_trace_stop_seqno = 0;
+static	int			MR_trace_stop_event = 0;
+static	bool			MR_trace_print_intermediate = FALSE;
 
 typedef	enum {
 	MR_INTERACT,
@@ -90,25 +115,28 @@
 } MR_trace_interact;
 
 static void	MR_trace_event(MR_trace_interact interact,
-			const MR_stack_layout_entry *layout,
+			const MR_Stack_Layout_Label *layout,
 			MR_trace_port port, int seqno, int depth,
-			const char *path);
+			const char *path, int max_r_num);
+static void	MR_copy_saved_regs_to_regs(int max_mr_num);
+static void	MR_copy_regs_to_saved_regs(int max_mr_num);
 static void	MR_trace_display_user(MR_trace_interact interact,
-			const MR_stack_layout_entry *layout,
+			const MR_Stack_Layout_Label *layout,
 			MR_trace_port port, int seqno, int depth,
 			const char *path);
 static void	MR_trace_browse(int var_count,
-			const MR_stack_layout_vars *var_info);
-static void	MR_trace_browse_var(char *name,
-			const MR_stack_layout_var *var);
-static int	MR_trace_get_cmd(void);
+			const MR_Stack_Layout_Vars *var_info);
+static void	MR_trace_browse_var(const char *name,
+			const MR_Stack_Layout_Var *var, Word *type_params);
+static int	MR_trace_skip_spaces(int c);
+static void	MR_trace_discard_to_eol(int c);
 static void	MR_trace_help(void);
 
 static Word	MR_trace_make_var_list(MR_trace_port port,
-			const MR_stack_layout_entry *layout);
+			const MR_Stack_Layout_Label *layout);
 static Word	MR_trace_lookup_live_lval(MR_Live_Lval locn, bool *succeeded);
-static bool	MR_trace_get_type_and_value(const MR_stack_layout_var *var,
-			Word *type_info, Word *value);
+static bool	MR_trace_get_type_and_value(const MR_Stack_Layout_Var *var,
+			Word *type_params, Word *type_info, Word *value);
 
 /*
 We could use
@@ -118,7 +146,7 @@
 check for an additional flag in the MERCURY_OPTIONS
 environment variable and set MR_use_debugger accordingly.
 */
-#ifdef MR_USE_DEBUGGER
+#ifdef MR_USE_EXTERNAL_DEBUGGER
 
 static MercuryFile MR_debugger_socket_in;
 static MercuryFile MR_debugger_socket_out;
@@ -129,21 +157,18 @@
 			Integer *debugger_request_type_ptr);
 	
 static void	MR_debugger_step(MR_trace_interact interact,
-			const MR_stack_layout_entry *layout,
+			const MR_Stack_Layout_Label *layout,
 			MR_trace_port port, int seqno, int depth,
 			const char *path);
-static bool	MR_found_match(const MR_stack_layout_entry *layout,
+static bool	MR_found_match(const MR_Stack_Layout_Label *layout,
 			MR_trace_port port, int seqno, int depth,
 			/* XXX registers */
 			const char *path, Word search_data);
-static void	MR_output_current(const MR_stack_layout_entry *layout,
+static void	MR_output_current(const MR_Stack_Layout_Label *layout,
 			MR_trace_port port, int seqno, int depth,
 			Word var_list,
 			const char *path, Word current_request);
 
-static void	MR_copy_saved_regs_to_regs(void);
-static void	MR_copy_regs_to_saved_regs(void);
-
 #endif
 
 #define	MR_port_is_final(port)	(port == MR_PORT_EXIT || port == MR_PORT_FAIL)
@@ -154,72 +179,167 @@
 */
 
 void
-MR_trace(const Word *layout_word, MR_trace_port port,
-	int seqno, int depth, const char *path)
+MR_trace(const MR_Stack_Layout_Label *layout, MR_trace_port port,
+	int seqno, int depth, const char *path, int max_r_num)
 {
-	const MR_stack_layout_entry	*layout;
 	MR_trace_interact		interact;
 
-	layout = (const MR_stack_layout_entry *) layout_word;
-
 	MR_trace_event_number++;
 	switch (MR_trace_cmd) {
-		case MR_CMD_NEXT:
-			MR_trace_event(MR_INTERACT, layout,
-				port, seqno, depth, path);
-			break;
+		case MR_CMD_FINISH:
+			if (MR_trace_stop_seqno == seqno
+			&& MR_port_is_final(port)) {
+				MR_trace_event(MR_INTERACT, layout,
+					port, seqno, depth, path, max_r_num);
 
-		case MR_CMD_JUMP:
-			if (MR_trace_seqno == seqno && MR_port_is_final(port))
-			{
-				interact = MR_INTERACT;
-			} else {
-				interact = MR_NO_INTERACT;
+			} else if (MR_trace_print_intermediate) {
+				MR_trace_event(MR_NO_INTERACT, layout,
+					port, seqno, depth, path, max_r_num);
 			}
 
-			MR_trace_event(interact, layout,
-				port, seqno, depth, path);
-
 			break;
 
-		case MR_CMD_SKIP:
-			if (MR_trace_seqno == seqno && MR_port_is_final(port))
-			{
+		case MR_CMD_GOTO:
+			if (MR_trace_event_number >= MR_trace_stop_event) {
 				MR_trace_event(MR_INTERACT, layout,
-					port, seqno, depth, path);
+					port, seqno, depth, path, max_r_num);
+			} else if (MR_trace_print_intermediate) {
+				MR_trace_event(MR_NO_INTERACT, layout,
+					port, seqno, depth, path, max_r_num);
 			}
 
-			break;
-
-		case MR_CMD_CONT:
-			break;
+		case MR_CMD_TO_END:
+			if (MR_trace_print_intermediate) {
+				MR_trace_event(MR_NO_INTERACT, layout,
+					port, seqno, depth, path, max_r_num);
+			}
 
-		case MR_CMD_DUMP:
-			MR_trace_event(MR_NO_INTERACT, layout,
-				port, seqno, depth, path);
 			break;
 
 		default:
-			fatal_error("MR_trace called with inappropriate port");
+			fatal_error("invalid cmd in MR_trace");
 			break;
 	}
 }
 
 static void
 MR_trace_event(MR_trace_interact interact,
-	const MR_stack_layout_entry *layout,
-	MR_trace_port port, int seqno, int depth, const char *path)
+	const MR_Stack_Layout_Label *layout, MR_trace_port port,
+	int seqno, int depth, const char *path, int max_r_num)
 {
-#ifdef MR_USE_DEBUGGER
-	MR_copy_regs_to_saved_regs();
-	MR_debugger_step(interact, layout, port, seqno, depth, path);
-	MR_copy_saved_regs_to_regs();
+	int	max_mr_num;
+
+	if (max_r_num + MR_NUM_SPECIAL_REG > MR_MAX_SPECIAL_REG_MR)
+		max_mr_num = max_r_num + MR_NUM_SPECIAL_REG;
+	else
+		max_mr_num = MR_MAX_SPECIAL_REG_MR;
+
+	MR_copy_regs_to_saved_regs(max_mr_num);
+#ifdef MR_USE_EXTERNAL_DEBUGGER
+	if (MR_trace_debugger == MR_TRACE_EXTERNAL)
+		MR_debugger_step(interact, layout, port, seqno, depth, path);
+	else
+		MR_trace_display_user(interact, layout, port, seqno, depth,
+			path);
 #else
+	/*
+	** We should get here only if MR_trace_debugger == MR_TRACE_INTERNAL.
+	** This is enforced by mercury_wrapper.c.
+	*/
+
 	MR_trace_display_user(interact, layout, port, seqno, depth, path);
 #endif
+	MR_copy_saved_regs_to_regs(max_mr_num);
+}
+
+static Word	MR_saved_regs[MAX_FAKE_REG];
+
+static void
+MR_copy_regs_to_saved_regs(int max_mr_num)
+{
+	/*
+	** In the process of browsing, we call Mercury code,
+	** which may clobber the contents of the virtual machine registers,
+	** both control and general purpose, and both real and virtual
+	** registers. We must therefore save and restore these.
+	** We store them in the MR_saved_regs array.
+	**
+	** The call to MR_trace will clobber the transient registers
+	** on architectures that have them. The compiler generated code
+	** will therefore call save_transient_registers to save the transient
+	** registers in the fake_reg array. We here restore them to the
+	** real registers, save them with the other registers back in
+	** fake_reg, and then copy all fake_reg entries to MR_saved_regs.
+	**
+	** If any code invoked by MR_trace is itself traced,
+	** MR_saved_regs will be overwritten, leading to a crash later on.
+	** This is one reason (but not the only one) why we turn off
+	** tracing when we call back Mercury code from this file.
+	*/
+
+	int i;
+
+	restore_transient_registers();
+	save_registers();
+
+	for (i = 0; i < max_mr_num; i++) {
+		MR_saved_regs[i] = fake_reg[i];
+	}
+}
+
+static void
+MR_copy_saved_regs_to_regs(int max_mr_num)
+{
+	/*
+	** We execute the converse procedure to MR_copy_regs_to_saved_regs.
+	** The save_transient_registers is there so that a call to the
+	** restore_transient_registers macro after MR_trace will do the
+	** right thing.
+	*/
+
+	int i;
+
+	for (i = 0; i < max_mr_num; i++) {
+		fake_reg[i] = MR_saved_regs[i];
+	}
+
+	restore_registers();
+	save_transient_registers();
+}
+
+void
+MR_trace_report(void)
+{
+	if (MR_trace_event_number > 0) {
+		/*
+		** This means that the executable was compiled with tracing,
+		** which implies that the user wants trace info on abort.
+		*/
+
+		fprintf(stderr, "Last event was event #%d.\n",
+			MR_trace_event_number);
+	}
+}
+
+void
+MR_trace_init(void)
+{
+#ifdef MR_USE_EXTERNAL_DEBUGGER
+	if (MR_trace_handler == MR_TRACE_EXTERNAL)
+		MR_trace_init_external();
+#endif
 }
 
-#ifdef MR_USE_DEBUGGER
+void
+MR_trace_end(void)
+{
+#ifdef MR_USE_EXTERNAL_DEBUGGER
+	if (MR_trace_handler == MR_TRACE_EXTERNAL)
+		MR_trace_end_external();
+#endif
+}
+
+#ifdef MR_USE_EXTERNAL_DEBUGGER
 
 #include <errno.h>
 #include <sys/types.h>
@@ -289,7 +409,7 @@
 static bool MR_debug_socket = FALSE;
 
 void
-MR_trace_init(void)
+MR_trace_init_external(void)
 {
 	int fd;
 	int len;
@@ -446,7 +566,7 @@
 }
 
 void
-MR_trace_end(void)
+MR_trace_end_external(void)
 {
 	/*
 	** This can only happen during a forward_move(),
@@ -466,7 +586,7 @@
 
 static void
 MR_debugger_step(MR_trace_interact interact,
-	const MR_stack_layout_entry *layout,
+	const MR_Stack_Layout_Label *layout,
 	MR_trace_port port, int seqno, int depth, const char *path)
 {
 	static bool searching = FALSE;
@@ -519,7 +639,7 @@
 				break;
 				
 			case MR_REQUEST_NO_TRACE:
-				MR_trace_cmd = MR_CMD_CONT;
+				MR_trace_cmd = MR_CMD_TO_END;
 				return;
 
 			default:
@@ -530,7 +650,7 @@
 }
 
 static void
-MR_output_current(const MR_stack_layout_entry *layout,
+MR_output_current(const MR_Stack_Layout_Label *layout,
 	MR_trace_port port, int seqno, int depth,
 	Word var_list,
 	const char *path, Word current_request)
@@ -540,11 +660,11 @@
 		seqno,
 		depth,
 		port,
-		layout->MR_sle_def_module,
-		layout->MR_sle_name,
-		layout->MR_sle_arity,
-		layout->MR_sle_mode,
-		layout->MR_sle_detism,
+		layout->MR_sll_entry->MR_sle_def_module,
+		layout->MR_sll_entry->MR_sle_name,
+		layout->MR_sll_entry->MR_sle_arity,
+		layout->MR_sll_entry->MR_sle_mode,
+		layout->MR_sll_entry->MR_sle_detism,
 		var_list,
 		(String) (Word) path,
 		current_request,
@@ -565,7 +685,7 @@
  
 
 static bool
-MR_found_match(const MR_stack_layout_entry *layout,
+MR_found_match(const MR_Stack_Layout_Label *layout,
 	MR_trace_port port, int seqno, int depth,
 	/* XXX live vars */
 	const char *path, Word search_data)
@@ -579,11 +699,11 @@
 		seqno,
 		depth,
 		port,
-		layout->MR_sle_def_module,
-		layout->MR_sle_name,
-		layout->MR_sle_arity,
-		layout->MR_sle_mode,
-		layout->MR_sle_detism,
+		layout->MR_sll_entry->MR_sle_def_module,
+		layout->MR_sll_entry->MR_sle_name,
+		layout->MR_sll_entry->MR_sle_arity,
+		layout->MR_sll_entry->MR_sle_mode,
+		layout->MR_sll_entry->MR_sle_detism,
 		arguments,
 		(String) (Word) path,
 		search_data);
@@ -598,27 +718,21 @@
 	MR_debugger_socket_out.line_number++;
 }
 
-#else /* !MR_USE_DEBUGGER */
-
-void MR_trace_init(void) {}
-void MR_trace_end(void) {}
-
-#endif /* MR_USE_DEBUGGER */
+#endif /* MR_USE_EXTERNAL_DEBUGGER */
 
 static void
 MR_trace_display_user(MR_trace_interact interact,
-	const MR_stack_layout_entry *layout,
+	const MR_Stack_Layout_Label *layout,
 	MR_trace_port port, int seqno, int depth, const char *path)
 {
 	int	i;
+	int	c;
+	int	count;
+	bool	count_given;
 
 	fflush(stdout);
 	fprintf(stderr, "%8d: %6d %2d ", MR_trace_event_number, seqno, depth);
 
-	for (i = 0; i < depth; i++) {
-		putc(' ', stderr);
-	}
-
 	switch (port) {
 		case MR_PORT_CALL:
 			fprintf(stderr, "CALL ");
@@ -653,7 +767,7 @@
 					"with bad port");
 	}
 
-	switch ((int) layout->MR_sle_detism) {
+	switch ((int) layout->MR_sll_entry->MR_sle_detism) {
 		case MR_DETISM_DET:
 			fprintf(stderr, "DET   ");
 			break;
@@ -698,81 +812,122 @@
 	*/
 
 	fprintf(stderr, "%s:%s/%ld-%ld %s\n",
-		layout->MR_sle_def_module,
-		layout->MR_sle_name,
-		(long) layout->MR_sle_arity,
-		(long) layout->MR_sle_mode,
+		layout->MR_sll_entry->MR_sle_def_module,
+		layout->MR_sll_entry->MR_sle_name,
+		(long) layout->MR_sll_entry->MR_sle_arity,
+		(long) layout->MR_sll_entry->MR_sle_mode,
 		path);
 
 	while (interact == MR_INTERACT) {
 		fprintf(stderr, "mtrace> ");
 
-		switch (MR_trace_get_cmd()) {
-			case 'n':
-			case '\n':
-				MR_trace_cmd = MR_CMD_NEXT;
-				break;
+		count = 1;
+		count_given = FALSE;
+		MR_trace_print_intermediate = FALSE;
+
+		c = MR_trace_skip_spaces(' ');
+		if (isdigit(c)) {
+			count_given = TRUE;
+			count = c - '0';
+			c = getchar();
+			while (c != EOF && isdigit(c)) {
+				count = (count * 10) + c - '0';
+				c = getchar();
+			}
 
-			case 'c':
-				MR_trace_cmd = MR_CMD_CONT;
-				break;
+			c = MR_trace_skip_spaces(c);
+		}
 
-			case 'd':
-				MR_trace_cmd = MR_CMD_DUMP;
+		switch (c) {
+			case 'S':
+				MR_trace_print_intermediate = TRUE;
+				/* fall through */
+
+			case 's':
+			case '\n':
+				MR_trace_cmd = MR_CMD_GOTO;
+				MR_trace_stop_event =
+					MR_trace_event_number + count;
+				MR_trace_discard_to_eol(c);
 				break;
 
-			case 'j':
-				if (MR_port_is_final(port)) {
-					fprintf(stderr, "mtrace: cannot jump"
-							" from this port\n");
+			case 'G':
+				MR_trace_print_intermediate = TRUE;
+				/* fall through */
+
+			case 'g':
+				if (! count_given) {
+					MR_trace_discard_to_eol(c);
+					fprintf(stderr, "mtrace: "
+						"no count given\n");
 					continue;
-				} else {
-					MR_trace_cmd = MR_CMD_JUMP;
-					MR_trace_seqno = seqno;
 				}
 
+				MR_trace_cmd = MR_CMD_GOTO;
+				MR_trace_stop_event = count;
+				MR_trace_discard_to_eol(c);
 				break;
 
-			case 'p':
-				if (port == MR_PORT_CALL) {
-					MR_trace_browse((int)
-						layout->MR_sle_in_arg_count,
-						&layout->MR_sle_in_arg_info);
-				} else if (port == MR_PORT_EXIT) {
-					MR_trace_browse((int)
-						layout->MR_sle_out_arg_count,
-						&layout->MR_sle_out_arg_info);
-				} else {
-					fprintf(stderr, "mtrace: cannot print"
-							" from this port\n");
-				}
-
-				continue;
+			case 'F':
+				MR_trace_print_intermediate = TRUE;
+				/* fall through */
 
-			case 's':
+			case 'f':
 				if (MR_port_is_final(port)) {
-					fprintf(stderr, "mtrace: cannot skip"
-							" from this port\n");
+					MR_trace_discard_to_eol(c);
+					fprintf(stderr, "mtrace: this port"
+						"is already final\n");
 					continue;
 				} else {
-					MR_trace_cmd = MR_CMD_SKIP;
-					MR_trace_seqno = seqno;
+					MR_trace_cmd = MR_CMD_FINISH;
+					MR_trace_stop_seqno = seqno;
 				}
 
+				MR_trace_discard_to_eol(c);
 				break;
 
-			case EOF:
+			case 'C':
+				MR_trace_print_intermediate = TRUE;
+				/* fall through */
+
+			case 'c':
+				if (count_given)
+					fprintf(stderr, "mtrace: "
+						"count ignored\n");
+
+				MR_trace_cmd = MR_CMD_TO_END;
+				MR_trace_discard_to_eol(c);
+				break;
+
+			case 'p':
+				if (count_given)
+					fprintf(stderr, "mtrace: "
+						"count ignored\n");
+
+				MR_trace_discard_to_eol(c);
+				MR_trace_browse((int)
+					layout->MR_sll_var_count,
+					&layout->MR_sll_var_info);
+
+				continue;
+
 			case 'a':
+			case EOF:
+				MR_trace_discard_to_eol(c);
 				fprintf(stderr, "mtrace: are you sure"
 						" you want to abort? ");
 
-				if (MR_trace_get_cmd() == 'y') {
+				c = MR_trace_skip_spaces(' ');
+				if (c == 'y' | c == EOF) {
 					fatal_error("aborting the execution "
 						"on user request");
 				}
+
+				MR_trace_discard_to_eol(c);
 				continue;
 
 			default:
+				MR_trace_discard_to_eol(c);
 				MR_trace_help();
 				continue;
 		}
@@ -781,71 +936,24 @@
 	}
 }
 
-static Word	MR_saved_regs[MAX_FAKE_REG];
-
-static void
-MR_copy_regs_to_saved_regs(void)
-{
-	/*
-	** In the process of browsing, we call Mercury code,
-	** which may clobber the contents of the registers,
-	** both the control registers and the general purpose registers.
-	** We must therefore save and restore these.
-	**
-	** XXX This is very inefficient!
-	**
-	** Some are in real machine registers; others in the fake_reg array.
-	** We need to copy them all to the fake_reg array, because the
-	** calling convention for calling Mercury functions exported to C
-	** assumes that they will be in the fake_reg array.
-	*/
-
-	int i;
-
-	restore_transient_registers();
-	save_registers();
-	for (i = 0; i < MAX_FAKE_REG; i++) {
-		MR_saved_regs[i] = fake_reg[i];
-	}
-}
-
-static void
-MR_copy_saved_regs_to_regs(void)
-{
-	int i;
-
-	for (i = 0; i < MAX_FAKE_REG; i++) {
-		fake_reg[i] = MR_saved_regs[i];
-	}
-	restore_registers();
-	save_transient_registers();
-}
-
 static Word
-MR_trace_make_var_list(MR_trace_port port, const MR_stack_layout_entry *layout)
+MR_trace_make_var_list(MR_trace_port port, const MR_Stack_Layout_Label *layout)
 {
 	int 				var_count;
-	const MR_stack_layout_vars 	*vars;
+	const MR_Stack_Layout_Vars 	*vars;
 	int				i;
 	const char			*name;
 
 	Word				univ_list;
-	MR_stack_layout_var*		var;
+	MR_Stack_Layout_Var*		var;
 	Word				univ, value;
 	MR_Live_Type			live_type;
 	Word				type_info;
 
 	restore_transient_registers();
 
-	if (port == MR_PORT_CALL) {
-		var_count = layout->MR_sle_in_arg_count;
-		vars = &layout->MR_sle_in_arg_info;
-	} else if (port == MR_PORT_EXIT) {
-		var_count = layout->MR_sle_out_arg_count;
-		vars = &layout->MR_sle_out_arg_info;
-	} else {
-		return list_empty();
-	}
+	var_count = layout->MR_sll_var_count;
+	vars = &layout->MR_sll_var_info;
 
 	/* build up the live variable list, starting from the end */
 	univ_list = list_empty();
@@ -855,15 +963,22 @@
 		** (XXX we don't include the name or the inst
 		** in the list that we return)
 		*/
-		if (vars->MR_slvs_names != NULL &&
-				vars->MR_slvs_names[i] != NULL)
-		{
-			name = vars->MR_slvs_names[i];
-		} else {
-			name = "";
-		}
+
+		name = MR_name_if_present(vars, i);
 		var = &vars->MR_slvs_pairs[i];
-		if (!MR_trace_get_type_and_value(var, &type_info, &value)) {
+
+		/*
+		** XXX The printing of type_infos is buggy at the moment
+		** due to the fake arity of mercury_builtin:typeinfo/1.
+		**
+		** "variables" representing the saved values of succip, hp etc,
+		** which are the "variables" for which get_type_and_value
+		** fails, are not of interest to the trace analyzer.
+		*/
+
+		if (strncmp(name, "TypeInfo", 8) == 0
+		|| !MR_trace_get_type_and_value(var, NULL, &type_info, &value))
+		{
 			continue;
 		}
 
@@ -881,31 +996,34 @@
 }
 
 static void
-MR_trace_browse(int var_count, const MR_stack_layout_vars *vars)
+MR_trace_browse(int var_count, const MR_Stack_Layout_Vars *vars)
 {
+	Word	*type_params;
+	bool	succeeded;
 	int	i;
-	char	*name;
 
 	if (var_count == 0) {
 		printf("mtrace: no live variables\n");
 		return;
 	}
 
-	MR_copy_regs_to_saved_regs();
-
-	for (i = 0; i < var_count; i++) {
-		if (vars->MR_slvs_names != NULL &&
-				vars->MR_slvs_names[i] != NULL)
-		{
-			name = vars->MR_slvs_names[i];
-		} else {
-			name = NULL;
+	type_params = checked_malloc((vars->MR_slvs_tvar_count + 1)
+		* sizeof(Word));
+	/* type_params should look like a typeinfo; type_params[0] is empty */
+	for (i = 0; i < vars->MR_slvs_tvar_count; i++) {
+		type_params[i+1] = MR_trace_lookup_live_lval(
+			vars->MR_slvs_tvars[i], &succeeded);
+		if (!succeeded) {
+			fatal_error("missing type param in MR_trace_browse");
 		}
+	}
 
-		MR_trace_browse_var(name, &vars->MR_slvs_pairs[i]);
+	for (i = 0; i < var_count; i++) {
+		MR_trace_browse_var(MR_name_if_present(vars, i),
+			&vars->MR_slvs_pairs[i], type_params);
 	}
 
-	MR_copy_saved_regs_to_regs();
+	free(type_params);
 }
 
 /* if you want to debug this code, you may want to set this var to TRUE */
@@ -991,26 +1109,44 @@
 	return value;
 }
 
+/* XXX fix this ref to the library */
+extern	Word	*ML_create_type_info(Word *term_type_info,
+			Word *arg_pseudo_type_info);
+
 static bool
-MR_trace_get_type_and_value(const MR_stack_layout_var *var,
-	Word *type_info, Word *value)
+MR_trace_get_type_and_value(const MR_Stack_Layout_Var *var,
+	Word *type_params, Word *type_info, Word *value)
 {
-	bool succeeded;
+	bool	succeeded;
+	Word	*pseudo_type_info;
+	int	i;
 
-	if (MR_LIVE_TYPE_IS_VAR(var->MR_slv_live_type)) {
-		*type_info = MR_LIVE_TYPE_GET_VAR_TYPE(var->MR_slv_live_type);
-	} else {
+	if (!MR_LIVE_TYPE_IS_VAR(var->MR_slv_live_type)) {
 		return FALSE;
 	}
-	*value = MR_trace_lookup_live_lval(var->MR_slv_locn, &succeeded);
+
+	pseudo_type_info = MR_LIVE_TYPE_GET_VAR_TYPE(var->MR_slv_live_type);
+	*type_info = (Word) ML_create_type_info(type_params, pseudo_type_info);
+	*value = MR_trace_lookup_live_lval(var->MR_slv_locn,
+		&succeeded);
 	return succeeded;
 }
 
 static void
-MR_trace_browse_var(char *name, const MR_stack_layout_var *var)
+MR_trace_browse_var(const char *name, const MR_Stack_Layout_Var *var,
+	Word *type_params)
 {
-	Word			value, type_info;
-	bool			print_value;
+	Word	value, type_info;
+	bool	print_value;
+	int	i;
+
+	/*
+	** XXX The printing of type_infos is buggy at the moment
+	** due to the fake arity of the type mercury_builtin:typeinfo/1.
+	*/
+
+	if (strncmp(name, "TypeInfo", 8) == 0)
+		return;
 
 	/* The initial blanks are to visually separate */
 	/* the variable names from the prompt. */
@@ -1021,7 +1157,14 @@
 		printf("%10s%-21s\t", "", "anonymous variable");
 	}
 
-	if (MR_trace_get_type_and_value(var, &type_info, &value)) {
+	/*
+	** "variables" representing the saved values of succip, hp etc,
+	** which are the "variables" for which get_type_and_value fails,
+	** are not of interest to the user.
+	*/
+
+	if (MR_trace_get_type_and_value(var, type_params, &type_info, &value))
+	{
 		printf("\t");
 
 		/*
@@ -1030,42 +1173,72 @@
 		** avoid going through call_engine, but for some unknown
 		** reason, that seemed to cause the Mercury code in the
 		** browser to clobber part of the C stack.
+		**
 		** Probably that was due to a bug which has since been
 		** fixed, so we should change the code below back again...
+		**
+		** call_engine expects the transient registers to be
+		** in fake_reg, others in their normal homes.
+		** The code below works by placing r1, r2 and all other
+		** transient registers both in their normal homes and
+		** and in fake_reg as well.
 		*/
+
+		MR_trace_enabled = FALSE;
+		for (i = 0; i < MAX_FAKE_REG; i++) {
+			fake_reg[i] = MR_saved_regs[i];
+		}
+		restore_registers();
 		r1 = type_info;
 		r2 = value;
+		save_transient_registers(); /* XXX probably redundant now */
 		call_engine(MR_library_trace_browser);
+		MR_trace_enabled = TRUE;
 	}
 
 	printf("\n");
 }
 
 static int
-MR_trace_get_cmd(void)
+MR_trace_skip_spaces(int c)
 {
-	int	cmd;
-	int	c;
+	while (c != EOF && c != '\n' && isspace(c))
+		c = getchar();
 
-	cmd = getchar();	/* read the trace command */
+	return c;
+}
 
-	/* skip the rest of the line */
-	c = cmd;
+static void
+MR_trace_discard_to_eol(int c)
+{
 	while (c != EOF && c != '\n')
 		c = getchar();
-
-	return cmd;
 }
 
+
 static void
 MR_trace_help(void)
 {
 	fprintf(stderr, "valid commands are:\n"
-			" a: abort the current execution.\n"
-			" c: continue to end, not printing the trace.\n"
-			" d: continue to end, printing the trace.\n"
-			" n: go to the next trace event.\n"
-			" s: skip the current call, not printing trace.\n"
-			" j: jump to end of current call, printing trace.\n"
-			" p: print the variables live at this point.\n");
+		"a, EOF:\t\t"
+		"\tabort the current execution.\n"
+		"c:\t\t"
+		"\tcontinue to end of program, not printing the trace.\n"
+		"C:\t\t"
+		"\tcontinue to end of program, printing the trace.\n"
+		"f:\t\t"
+		"\tfinish this call, not printing the trace.\n"
+		"F:\t\t"
+		"\tfinish this call, printing the trace.\n"
+		"<N> g:\t\t"
+		"\tgo to event #N, not printing the trace.\n"
+		"<N> G:\t\t"
+		"\tgo to event #N, printing the trace.\n"
+		"p:\t\t"
+		"\tprint the variables live at this point.\n"
+		"[<N>] s, [N] CR:"
+		"\tskip N events, not printing the trace.\n"
+		"[<N>] S:\t"
+		"\tskip N events, printing the trace.\n"
+	);
 }
Index: runtime/mercury_trace.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace.h,v
retrieving revision 1.6
diff -u -r1.6 mercury_trace.h
--- mercury_trace.h	1998/03/11 22:07:32	1.6
+++ mercury_trace.h	1998/03/20 08:13:07
@@ -8,9 +8,9 @@
 ** mercury_trace.h - defines the interface between
 ** the tracing subsystem and compiled code.
 **
-** The macros and the function defined in this module are intended to be
-** called only from code generated by the Mercury compiler, and from
-** hand-compiled code in the Mercury runtime or the Mercury standard library.
+** The macros and functions defined in this module are intended to be called
+** only from code generated by the Mercury compiler, and from hand-written
+** code in the Mercury runtime or the Mercury standard library.
 */
 
 #ifndef MERCURY_TRACE_H
@@ -27,6 +27,7 @@
 ** This enum should exactly match the definition of the `trace_port' type in
 ** library/debugger_interface.
 */
+
 typedef	enum {
 	MR_PORT_CALL,
 	MR_PORT_EXIT,
@@ -38,11 +39,19 @@
 } MR_trace_port;
 
 extern	void	MR_trace(
-	const Word *,		/* pointer to stack layout info */
+	const MR_Stack_Layout_Label *,	/* layout info for the event */
 	MR_trace_port,
 	int,			/* call sequence number */
 	int,			/* call depth */
-	const char *);		/* path to event goal within procedure */
+	const char *,		/* path to event goal within procedure */
+	int);			/* highest numbered rN register in use */
+
+/*
+** This function will report the number of the last event,
+** if there have been some events, and will do nothing otherwise.
+*/
+
+extern	void	MR_trace_report(void);
 
 /*
 ** MR_trace_init() is called from mercury_runtime_init()
@@ -50,7 +59,18 @@
 ** MR_trace_end() is called from mercury_runtime_terminate()
 ** when the debuggee programs is exiting.
 */
+
 extern	void	MR_trace_init(void);
 extern	void	MR_trace_end(void);
+
+typedef	enum {
+	MR_TRACE_INTERNAL,
+	MR_TRACE_EXTERNAL
+} MR_trace_type;
+
+extern	MR_trace_type	MR_trace_handler;
+extern	bool		MR_trace_enabled;
+
+extern	int		MR_trace_event_number;
 
 #endif /* MERCURY_TRACE_H */
Index: runtime/mercury_wrapper.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_wrapper.c,v
retrieving revision 1.8
diff -u -r1.8 mercury_wrapper.c
--- mercury_wrapper.c	1998/03/16 12:23:40	1.8
+++ mercury_wrapper.c	1998/03/18 01:11:31
@@ -443,7 +443,7 @@
 	unsigned long size;
 	int c;
 
-	while ((c = getopt(argc, argv, "acC:d:hLlP:pr:s:tT:w:xz:1:2:3:")) != EOF)
+	while ((c = getopt(argc, argv, "acC:d:D:hLlP:pr:s:tT:w:xz:")) != EOF)
 	{
 		switch (c)
 		{
@@ -512,6 +512,21 @@
 			use_own_timer = FALSE;
 			break;
 
+		case 'D':
+			MR_trace_enabled = TRUE;
+
+			if (streq(optarg, "i"))
+				MR_trace_handler = MR_TRACE_INTERNAL;
+#ifdef	MR_USE_EXTERNAL_DEBUGGER
+			else if (streq(optarg, "e"))
+				MR_trace_handler = MR_TRACE_EXTERNAL;
+#endif
+
+			else
+				usage();
+
+			break;
+
 		case 'h':
 			usage();
 			break;
@@ -647,24 +662,6 @@
 
 			break;
 
-		case '1':	
-			if (sscanf(optarg, "%d", &r1val) != 1)
-				usage();
-
-			break;
-
-		case '2':	
-			if (sscanf(optarg, "%d", &r2val) != 1)
-				usage();
-
-			break;
-
-		case '3':	
-			if (sscanf(optarg, "%d", &r3val) != 1)
-				usage();
-
-			break;
-
 		default:	
 			usage();
 
@@ -698,6 +695,10 @@
 		"-dm \t\tdebug memory allocation\n"
 		"-dG \t\tdebug garbage collection\n"
 		"-dd \t\tdetailed debug\n"
+		"-Di \t\tdebug the program using the internal debugger\n"
+#ifdef MR_USE_EXTERNAL_DEBUGGER
+		"-De \t\tdebug the program using the external debugger\n"
+#endif
 		"-sh<n> \t\tallocate n kb for the heap\n"
 		"-sd<n> \t\tallocate n kb for the det stack\n"
 		"-sn<n> \t\tallocate n kb for the nondet stack\n"
@@ -718,9 +719,7 @@
 #endif
 		"-r<n> \t\trepeat n times\n"
 		"-w<name> \tcall predicate with given name (default: main/2)\n"
-		"-1<x> \t\tinitialize register r1 with value x\n"
-		"-2<x> \t\tinitialize register r2 with value x\n"
-		"-3<x> \t\tinitialize register r3 with value x\n");
+		);
 	fflush(stdout);
 	exit(1);
 } /* end usage() */
Index: scripts/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/mercury/scripts/Mmakefile,v
retrieving revision 1.6
diff -u -r1.6 Mmakefile
--- Mmakefile	1997/11/21 07:11:00	1.6
+++ Mmakefile	1998/03/14 06:07:48
@@ -14,7 +14,7 @@
 
 #-----------------------------------------------------------------------------#
 
-SCRIPTS = mmake mmc c2init mgnuc ml mprof mprof_merge_runs mint \
+SCRIPTS = mmake mmc mmd c2init mgnuc ml mprof mprof_merge_runs mint \
 	  sicstus_conv mtags vpath_find mercury_update_interface \
 	  mkfifo_using_mknod
 NUPROLOG_SCRIPTS = mnc mnl mnp
Index: tests/misc_tests/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/tests/misc_tests/Mmakefile,v
retrieving revision 1.6
diff -u -r1.6 Mmakefile
--- Mmakefile	1998/02/16 17:23:15	1.6
+++ Mmakefile	1998/03/18 00:57:55
@@ -9,41 +9,14 @@
 mdemangle_test.out: mdemangle_test.inp
 	mdemangle < mdemangle_test.inp > mdemangle_test.out 2>&1
 
-debugger_regs.out: debugger_regs debugger_regs.inp
-	./debugger_regs debugger_regs.m < debugger_regs.inp \
-		> debugger_regs.out 2>&1
-
-debugger_test.out: debugger_test debugger_test.inp
-	./debugger_test debugger_test.m < debugger_test.inp \
-		> debugger_test.out 2>&1
-
 pretty_print_test.out: pretty_print_test.ugly
 	cp pretty_print_test.ugly pretty_print_test.out
 
 #-----------------------------------------------------------------------------#
 
-STACK_LAYOUT_PROGS=	\
-	debugger_regs	\
-	debugger_test
-
-OTHER_PROGS =
+PROGS =
 
 OTHER_TESTS = mdemangle_test pretty_print_test
-
-MCFLAGS-debugger_regs = --generate-trace
-MCFLAGS-debugger_test = --generate-trace
-
-# Not all grades can be used with stack layouts
-#
-ifeq ($(GRADE),jump) 
-	PROGS=$(OTHER_PROGS)
-else
-	ifeq ($(GRADE),fast)
-		PROGS=$(OTHER_PROGS)
-	else
-		PROGS=$(STACK_LAYOUT_PROGS) $(OTHER_PROGS)
-	endif
-endif
 
 #-----------------------------------------------------------------------------#
 

New File: scripts/mmd
===================================================================
#!/bin/sh
case $# in
	0)	echo "Usage: mmd <executable> [<arg> ...]"
		exit 1;;
esac

MERCURY_OPTIONS="$MERCURY_OPTIONS -Di"
export MERCURY_OPTIONS
exec "$@"

New File: tests/debugger/Mmakefile
===================================================================
#-----------------------------------------------------------------------------#

MMD_WRAPPER = yes

main_target: check

include ../Mmake.common

#-----------------------------------------------------------------------------#

DEBUGGER_PROGS=	\
	debugger_regs	\
	interpreter	\
	queens

MCFLAGS = --generate-trace

# Not all grades can be used with stack layouts
#
ifeq ($(GRADE),jump) 
	PROGS=
else
	ifeq ($(GRADE),fast)
		PROGS=
	else
		PROGS=$(DEBUGGER_PROGS)
	endif
endif

#-----------------------------------------------------------------------------#

debugger_regs.out: debugger_regs debugger_regs.inp
	mmd ./debugger_regs < debugger_regs.inp > debugger_regs.out 2>&1

interpreter.out: interpreter interpreter.inp
	mmd ./interpreter interpreter.m < interpreter.inp \
		> interpreter.out 2>&1

queens.out: queens queens.inp
	mmd ./queens < queens.inp > queens.out 2>&1

#-----------------------------------------------------------------------------#

DEPS=	$(PROGS:%=%.dep)
DEPENDS=$(PROGS:%=%.depend)
OUTS=	$(PROGS:%=%.out)
RESS=	$(PROGS:%=%.res)
MODS=	$(PROGS:%=%.mod)

#-----------------------------------------------------------------------------#

dep:	$(DEPS)

depend:	$(DEPENDS)

check:	$(OUTS) $(RESS)

mods:	$(MODS)

all:	$(PROGS)

#-----------------------------------------------------------------------------#

New File: tests/debugger/debugger_regs.exp
===================================================================
       1:      1  1 CALL DET   debugger_regs:main/2-0 
mtrace>        2:      2  2 CALL DET   debugger_regs:data/41-0 
mtrace>        3:      2  2 EXIT DET   debugger_regs:data/41-0 
mtrace> mtrace>           HeadVar__1           		[1, 2, 3, 4, 5]
          HeadVar__2           		a0
          HeadVar__3           		a1
          HeadVar__4           		a2
          HeadVar__5           		a3
          HeadVar__6           		a4
          HeadVar__7           		a5
          HeadVar__8           		a6
          HeadVar__9           		a7
          HeadVar__10          		a8
          HeadVar__11          		a9
          HeadVar__12          		b0
          HeadVar__13          		b1
          HeadVar__14          		b2
          HeadVar__15          		b3
          HeadVar__16          		b4
          HeadVar__17          		b5
          HeadVar__18          		b6
          HeadVar__19          		b7
          HeadVar__20          		b8
          HeadVar__21          		b9
          HeadVar__22          		c0
          HeadVar__23          		c1
          HeadVar__24          		c2
          HeadVar__25          		c3
          HeadVar__26          		c4
          HeadVar__27          		c5
          HeadVar__28          		c6
          HeadVar__29          		c7
          HeadVar__30          		c8
          HeadVar__31          		c9
          HeadVar__32          		d0
          HeadVar__33          		d1
          HeadVar__34          		d2
          HeadVar__35          		d3
          HeadVar__36          		d4
          HeadVar__37          		d5
          HeadVar__38          		d6
          HeadVar__39          		d7
          HeadVar__40          		d8
          HeadVar__41          		d9
a0a1a2a3a4a5a6a7a8a9
b0b1b2b3b4b5b6b7b8b9
c0c1c2c3c4c5c6c7c8c9
d0d1d2d3d4d5d6d7d8d9

New File: tests/debugger/debugger_regs.inp
===================================================================


p
c

New File: tests/debugger/debugger_regs.m
===================================================================
% This program tests whether the tracer works for procedures with
% lots of arguments (beyond NUM_REAL_REGS and MAX_REAL_REGS).
% At the moment, MAX_REAL_REGS is 32, so a procedure with 41 args
% is a full test.

:- module debugger_regs.

:- interface.

:- import_module io.

:- pred main(io__state, io__state).
:- mode main(di, uo) is det.

:- implementation.

:- import_module list, int.

main -->
	% The purpose of list is to force the tracer to call the Mercury
	% code to print a list of integers, when the input script asks
	% for the outputs of data to be printed. In the past this was
	% sufficed to cause part of the C stack to be overwritten.
	% It also tests whether the values of A0 etc that the tracer prints
	% are derived from the register contents produced by data,
	% or from the register contents left there by the code that
	% prints _List.
	{ data(_List,
		A0, A1, A2, A3, A4, A5, A6, A7, A8, A9,
		B0, B1, B2, B3, B4, B5, B6, B7, B8, B9,
		C0, C1, C2, C3, C4, C5, C6, C7, C8, C9,
		D0, D1, D2, D3, D4, D5, D6, D7, D8, D9) },
	io__write_string(A0),
	io__write_string(A1),
	io__write_string(A2),
	io__write_string(A3),
	io__write_string(A4),
	io__write_string(A5),
	io__write_string(A6),
	io__write_string(A7),
	io__write_string(A8),
	io__write_string(A9),
	io__write_string("\n"),
	io__write_string(B0),
	io__write_string(B1),
	io__write_string(B2),
	io__write_string(B3),
	io__write_string(B4),
	io__write_string(B5),
	io__write_string(B6),
	io__write_string(B7),
	io__write_string(B8),
	io__write_string(B9),
	io__write_string("\n"),
	io__write_string(C0),
	io__write_string(C1),
	io__write_string(C2),
	io__write_string(C3),
	io__write_string(C4),
	io__write_string(C5),
	io__write_string(C6),
	io__write_string(C7),
	io__write_string(C8),
	io__write_string(C9),
	io__write_string("\n"),
	io__write_string(D0),
	io__write_string(D1),
	io__write_string(D2),
	io__write_string(D3),
	io__write_string(D4),
	io__write_string(D5),
	io__write_string(D6),
	io__write_string(D7),
	io__write_string(D8),
	io__write_string(D9),
	io__write_string("\n").

:- pred data(list(int)::out,
	string::out, string::out, string::out, string::out, string::out,
	string::out, string::out, string::out, string::out, string::out,
	string::out, string::out, string::out, string::out, string::out,
	string::out, string::out, string::out, string::out, string::out,
	string::out, string::out, string::out, string::out, string::out,
	string::out, string::out, string::out, string::out, string::out,
	string::out, string::out, string::out, string::out, string::out,
	string::out, string::out, string::out, string::out, string::out) is det.

data([1, 2, 3, 4, 5],
	"a0", "a1", "a2", "a3", "a4", "a5", "a6", "a7", "a8", "a9",
	"b0", "b1", "b2", "b3", "b4", "b5", "b6", "b7", "b8", "b9",
	"c0", "c1", "c2", "c3", "c4", "c5", "c6", "c7", "c8", "c9",
	"d0", "d1", "d2", "d3", "d4", "d5", "d6", "d7", "d8", "d9").

New File: tests/debugger/interpreter.exp
===================================================================
       1:      1  1 CALL DET   interpreter:main/2-0 
mtrace> valid commands are:
a, EOF:			abort the current execution.
c:			continue to end of program, not printing the trace.
C:			continue to end of program, printing the trace.
f:			finish this call, not printing the trace.
F:			finish this call, printing the trace.
<N> g:			go to event #N, not printing the trace.
<N> G:			go to event #N, printing the trace.
p:			print the variables live at this point.
[<N>] s, [N] CR:	skip N events, not printing the trace.
[<N>] S:		skip N events, printing the trace.
mtrace> Pure Prolog Interpreter.

Consulting file `interpreter.m'...
      11:      6  5 SWTC DET   interpreter:consult_until_eof_2/5-0 s3;
mtrace> mtrace>           HeadVar__1           		term(varset(0, empty, empty), functor(atom(":-"), [functor(atom("module"), [functor(atom("interpreter"), [], context("interpreter.m", 22))], context("interpreter.m", 22))], context("interpreter.m", 22)))
          HeadVar__2           		[]
          HeadVar__4           		state('<<c_pointer>>')
      30:     16 12 CALL DET   interpreter:database_assert_clause/4-0 
mtrace> mtrace>           HeadVar__1           		[clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("import_module"), [functor(atom("io"), [], context("interpreter.m", 24))], context("interpreter.m", 24))], context("interpreter.m", 24)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("interface"), [], context("interpreter.m", 23))], context("interpreter.m", 23)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("module"), [functor(atom("interpreter"), [], context("interpreter.m", 22))], context("interpreter.m", 22))], context("interpreter.m", 22)), functor(atom("true"), [], context("", 0)))]
          HeadVar__2           		varset(0, empty, empty)
          HeadVar__3           		functor(atom(":-"), [functor(atom("pred"), [functor(atom("main"), [functor(atom("io__state"), [], context("interpreter.m", 26)), functor(atom("io__state"), [], context("interpreter.m", 26))], context("interpreter.m", 26))], context("interpreter.m", 26))], context("interpreter.m", 26))
      30:     16 12 CALL DET   interpreter:database_assert_clause/4-0 
      31:     16 12 ELSE DET   interpreter:database_assert_clause/4-0 e;
      32:     16 12 EXIT DET   interpreter:database_assert_clause/4-0 
mtrace> mtrace>           HeadVar__4           		[clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("pred"), [functor(atom("main"), [functor(atom("io__state"), [], context("interpreter.m", 26)), functor(atom("io__state"), [], context("interpreter.m", 26))], context("interpreter.m", 26))], context("interpreter.m", 26))], context("interpreter.m", 26)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("import_module"), [functor(atom("io"), [], context("interpreter.m", 24))], context("interpreter.m", 24))], context("interpreter.m", 24)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("interface"), [], context("interpreter.m", 23))], context("interpreter.m", 23)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("module"), [functor(atom("interpreter"), [], context("interpreter.m", 22))], context("interpreter.m", 22))], context("interpreter.m", 22)), functor(atom("true"), [], context("", 0)))]
          HeadVar__1           		[clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("import_module"), [functor(atom("io"), [], context("interpreter.m", 24))], context("interpreter.m", 24))], context("interpreter.m", 24)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("interface"), [], context("interpreter.m", 23))], context("interpreter.m", 23)), functor(atom("true"), [], context("", 0))), clause(varset(0, empty, empty), functor(atom(":-"), [functor(atom("module"), [functor(atom("interpreter"), [], context("interpreter.m", 22))], context("interpreter.m", 22))], context("interpreter.m", 22)), functor(atom("true"), [], context("", 0)))]
          HeadVar__2           		varset(0, empty, empty)
          HeadVar__3           		functor(atom(":-"), [functor(atom("pred"), [functor(atom("main"), [functor(atom("io__state"), [], context("interpreter.m", 26)), functor(atom("io__state"), [], context("interpreter.m", 26))], context("interpreter.m", 26))], context("interpreter.m", 26))], context("interpreter.m", 26))
      33:     17 12 CALL DET   interpreter:consult_until_eof/4-0 
mtrace>      677:     17 12 EXIT DET   interpreter:consult_until_eof/4-0 
mtrace>      678:     15 11 EXIT DET   interpreter:consult_until_eof_2/5-0 
mtrace>      679:     14 10 EXIT DET   interpreter:consult_until_eof/4-0 
mtrace>      679:     14 10 EXIT DET   interpreter:consult_until_eof/4-0 
     680:     12  9 EXIT DET   interpreter:consult_until_eof_2/5-0 
     681:     11  8 EXIT DET   interpreter:consult_until_eof/4-0 
     682:      9  7 EXIT DET   interpreter:consult_until_eof_2/5-0 
     683:      8  6 EXIT DET   interpreter:consult_until_eof/4-0 
     684:      6  5 EXIT DET   interpreter:consult_until_eof_2/5-0 
     685:      5  4 EXIT DET   interpreter:consult_until_eof/4-0 
     686:      4  3 EXIT DET   interpreter:consult/5-0 
     687:    259  3 CALL DET   interpreter:consult_list/5-0 
     688:    259  3 SWTC DET   interpreter:consult_list/5-0 s2;
     689:    259  3 EXIT DET   interpreter:consult_list/5-0 
     690:      3  2 EXIT DET   interpreter:consult_list/5-0 
     691:    260  2 CALL DET   interpreter:main_loop/3-0 
?-      692:    261  3 CALL DET   interpreter:main_loop_2/4-0 
     693:    261  3 SWTC DET   interpreter:main_loop_2/4-0 s1;
     694:    261  3 EXIT DET   interpreter:main_loop_2/4-0 
     695:    260  2 EXIT DET   interpreter:main_loop/3-0 
     696:      1  1 EXIT DET   interpreter:main/2-0 

New File: tests/debugger/interpreter.inp
===================================================================
h
10s
p
30 g
p
F
p

f


C

New File: tests/debugger/interpreter.m
===================================================================
%-----------------------------------------------------------------------------%

% File: interpreter.m.
% Main author: fjh.

% This is an interpreter for definite logic programs
% (i.e. pure Prolog with no negation or if-then-else.)
%
% This is just intended as a demonstration of the use of the
% meta-programming library modules term, varset, and term_io.

% There are many extensions/improvements that could be made;
% they're left as an exercise for the reader.

% For a more efficient version (using backtrackable destructive update),
% see extras/trailed_update/samples/interpreter.m.

% This source file is hereby placed in the public domain.  -fjh (the author).

%-----------------------------------------------------------------------------%

:- module interpreter.
:- interface.
:- import_module io.

:- pred main(io__state, io__state).
:- mode main(di, uo) is det.

%-----------------------------------------------------------------------------%

:- implementation.
:- import_module list, string, term, varset, term_io, require, std_util.

main -->
	io__write_string("Pure Prolog Interpreter.\n\n"),
	io__command_line_arguments(Args),
	( { Args = [] } ->
		io__stderr_stream(StdErr),
		io__write_string(StdErr, "Usage: interpreter filename ...\n"),
		io__set_exit_status(1)
	;
		{ database_init(Database0) },
		consult_list(Args, Database0, Database),
		main_loop(Database)
	).

:- pred main_loop(database, io__state, io__state).
:- mode main_loop(in, di, uo) is det.

main_loop(Database) -->
	io__write_string("?- "),
	term_io__read_term(ReadTerm),
	main_loop_2(ReadTerm, Database).

:- pred main_loop_2(read_term, database, io__state, io__state).
:- mode main_loop_2(in, in, di, uo) is det.

main_loop_2(eof, _Database) --> [].
main_loop_2(error(ErrorMessage, LineNumber), Database) -->
	io__write_string("Error reading term at line "),
	io__write_int(LineNumber),
	io__write_string(" of standard input: "),
	io__write_string(ErrorMessage),
	io__write_string("\n"),
	main_loop(Database).
main_loop_2(term(VarSet0, Goal), Database) -->
	%%% It would be a good idea to add some special commands
	%%% with side-effects (such as `consult' and `listing');
	%%% these could be identified and processed here.
	{ solutions(solve(Database, Goal, VarSet0), Solutions) },
	write_solutions(Solutions, Goal),
	main_loop(Database).

:- pred write_solutions(list(varset), term, io__state, io__state).
:- mode write_solutions(in, in, di, uo) is det.

write_solutions(Solutions, Goal) -->
	( { Solutions = [] } ->
		io__write_string("No.\n")
	;
		write_solutions_2(Solutions, Goal),
		io__write_string("Yes.\n")
	).

:- pred write_solutions_2(list(varset), term, io__state, io__state).
:- mode write_solutions_2(in, in, di, uo) is det.

write_solutions_2([], _) --> [].
write_solutions_2([VarSet | VarSets], Goal) -->
	term_io__write_term_nl(VarSet, Goal),
	write_solutions_2(VarSets, Goal).

%-----------------------------------------------------------------------------%

:- pred consult_list(list(string), database, database, io__state, io__state).
:- mode consult_list(in, in, out, di, uo) is det.

consult_list([], Database, Database) --> [].
consult_list([File | Files], Database0, Database) -->
	consult(File, Database0, Database1),
	consult_list(Files, Database1, Database).

:- pred consult(string, database, database, io__state, io__state).
:- mode consult(in, in, out, di, uo) is det.

consult(File, Database0, Database) -->
	io__write_string("Consulting file `"),
	io__write_string(File),
	io__write_string("'...\n"),
	io__see(File, Result),
	( { Result = ok } ->
		consult_until_eof(Database0, Database),
		io__seen
	;
		io__write_string("Error opening file `"),
		io__write_string(File),
		io__write_string("' for input.\n"),
		{ Database = Database0 }
	).

:- pred consult_until_eof(database, database, io__state, io__state).
:- mode consult_until_eof(in, out, di, uo) is det.

consult_until_eof(Database0, Database) -->
	term_io__read_term(ReadTerm),
	consult_until_eof_2(ReadTerm, Database0, Database).

:- pred consult_until_eof_2(read_term, database, database,
				io__state, io__state).
:- mode consult_until_eof_2(in, in, out, di, uo) is det.

consult_until_eof_2(eof, Database, Database) --> [].

consult_until_eof_2(error(ErrorMessage, LineNumber), Database0, Database) -->
	io__write_string("Error reading term at line "),
	io__write_int(LineNumber),
	io__write_string(" of standard input: "),
	io__write_string(ErrorMessage),
	io__write_string("\n"),
	consult_until_eof(Database0, Database).

consult_until_eof_2(term(VarSet, Term), Database0, Database) -->
	{ database_assert_clause(Database0, VarSet, Term, Database1) },
	consult_until_eof(Database1, Database).

%-----------------------------------------------------------------------------%

% Solve takes a database of rules and facts, a goal to be solved,
% and a varset (which includes a supply of fresh vars, a substitution,
% and names for [some subset of] the variables).  It updates
% the varset, producing a new substitution and perhaps introducing
% some new vars, and returns the result.

% Goals are stored just as terms.
% (It might be more efficient to parse them 
% before storing them in the database.  Currently we do
% this parsing work every time we interpret a clause.)

:- pred solve(database, term, varset, varset).
:- mode solve(in, in, in, out) is nondet.

solve(_Database, term__functor(term__atom("true"), [], _)) --> [].

solve(Database, term__functor(term__atom(","), [A, B], _)) -->
	solve(Database, A),
	solve(Database, B).

solve(Database, term__functor(term__atom(";"), [A, B], _)) -->
	solve(Database, A)
	;
	solve(Database, B).

solve(_Database, term__functor(term__atom("="), [A, B], _)) -->
	unify(A, B).

solve(Database, Goal) -->
	{ database_lookup_clause(Database, Goal, ClauseVarSet, Head0, Body0) },
	rename_apart(ClauseVarSet, [Head0, Body0], [Head, Body]),
	unify(Goal, Head),
	solve(Database, Body).

%-----------------------------------------------------------------------------%

:- pred rename_apart(varset, list(term), list(term), varset, varset).
:- mode rename_apart(in, in, out, in, out) is det.

rename_apart(NewVarSet, Terms0, Terms, VarSet0, VarSet) :-
	varset__merge(VarSet0, NewVarSet, Terms0, VarSet, Terms).

%-----------------------------------------------------------------------------%

% The standard library module `term' contains routines for
% unifying terms based on separate substitutions, but we are
% using the substitutions that are contained in the `varset',
% so we can't use those versions.

:- pred unify(term, term, varset, varset).
:- mode unify(in, in, in, out) is semidet.

unify(term__variable(X), term__variable(Y), VarSet0, VarSet) :-
	(
		varset__search_var(VarSet0, X, BindingOfX)
	->
		(
			varset__search_var(VarSet0, Y, BindingOfY)
		->
			% both X and Y already have bindings - just
			% unify the terms they are bound to
			unify(BindingOfX, BindingOfY, VarSet0, VarSet)
		;
			% Y is a variable which hasn't been bound yet
			apply_rec_substitution(BindingOfX, VarSet0,
				SubstBindingOfX),
			( SubstBindingOfX = term__variable(Y) ->
			 	VarSet = VarSet0
			;
				\+ occurs(SubstBindingOfX, Y, VarSet0),
				varset__bind_var(VarSet0, Y, SubstBindingOfX,
					VarSet)
			)
		)
	;
		(
			varset__search_var(VarSet0, Y, BindingOfY2)
		->
			% X is a variable which hasn't been bound yet
			apply_rec_substitution(BindingOfY2, VarSet0,
				SubstBindingOfY2),
			( SubstBindingOfY2 = term__variable(X) ->
				VarSet = VarSet0
			;
				\+ occurs(SubstBindingOfY2, X, VarSet0),
				varset__bind_var(VarSet0, X, SubstBindingOfY2,
					VarSet)
			)
		;
			% both X and Y are unbound variables -
			% bind one to the other
			( X = Y ->
				VarSet = VarSet0
			;
				varset__bind_var(VarSet0, X, term__variable(Y),
					VarSet)
			)
		)
	).

unify(term__variable(X), term__functor(F, As, C), VarSet0, VarSet) :-
	(
		varset__search_var(VarSet0, X, BindingOfX)
	->
		unify(BindingOfX, term__functor(F, As, C), VarSet0,
			VarSet)
	;
		\+ occurs_list(As, X, VarSet0),
		varset__bind_var(VarSet0, X, term__functor(F, As, C), VarSet)
	).

unify(term__functor(F, As, C), term__variable(X), VarSet0, VarSet) :-
	(
		varset__search_var(VarSet0, X, BindingOfX)
	->
		unify(term__functor(F, As, C), BindingOfX, VarSet0,
			VarSet)
	;
		\+ occurs_list(As, X, VarSet0),
		varset__bind_var(VarSet0, X, term__functor(F, As, C), VarSet)
	).

unify(term__functor(F, AsX, _), term__functor(F, AsY, _)) -->
	unify_list(AsX, AsY).

:- pred unify_list(list(term), list(term), varset, varset).
:- mode unify_list(in, in, in, out) is semidet.

unify_list([], []) --> [].
unify_list([X | Xs], [Y | Ys]) -->
	unify(X, Y),
	unify_list(Xs, Ys).

%-----------------------------------------------------------------------------%

	% occurs(Term, Var, Subst) succeeds if Term contains Var,
	% perhaps indirectly via the substitution.  (The variable must
	% not be mapped by the substitution.)

:- pred occurs(term, var, varset).
:- mode occurs(in, in, in) is semidet.

occurs(term__variable(X), Y, VarSet) :-
	X = Y
	;
	varset__search_var(VarSet, X, BindingOfX),
	occurs(BindingOfX, Y, VarSet).
occurs(term__functor(_F, As, _), Y, VarSet) :-
	occurs_list(As, Y, VarSet).

:- pred occurs_list(list(term), var, varset).
:- mode occurs_list(in, in, in) is semidet.

occurs_list([Term | Terms], Y, VarSet) :-
	occurs(Term, Y, VarSet)
	;
	occurs_list(Terms, Y, VarSet).

%-----------------------------------------------------------------------------%

%	apply_rec_substitution(Term0, VarSet, Term) :
%		recursively apply substitution to Term0 until
%		no more substitions can be applied, and then
%		return the result in Term.

:- pred apply_rec_substitution(term, varset, term).
:- mode apply_rec_substitution(in, in, out) is det.

apply_rec_substitution(term__variable(Var), VarSet, Term) :-
	(
		varset__search_var(VarSet, Var, Replacement)
	->
		% recursively apply the substition to the replacement
		apply_rec_substitution(Replacement, VarSet, Term)
	;
		Term = term__variable(Var)
	).
apply_rec_substitution(term__functor(Name, Args0, Context), VarSet,
		 term__functor(Name, Args, Context)) :-
	apply_rec_substitution_to_list(Args0, VarSet, Args).

:- pred apply_rec_substitution_to_list(list(term), varset, list(term)).
:- mode apply_rec_substitution_to_list(in, in, out) is det.

apply_rec_substitution_to_list([], _VarSet, []).
apply_rec_substitution_to_list([Term0 | Terms0], VarSet,
		[Term | Terms]) :-
	apply_rec_substitution(Term0, VarSet, Term),
	apply_rec_substitution_to_list(Terms0, VarSet, Terms).

%-----------------------------------------------------------------------------%

% We store the database just as a list of clauses.
% (It would be more realistic to index this on the predicate name/arity
% and subindex on the name/arity of the first argument.)

:- type database == list(clause).
:- type clause ---> clause(varset, term, term).

:- pred database_init(database).
:- mode database_init(out) is det.

database_init([]).

:- pred database_assert_clause(database, varset, term, database).
:- mode database_assert_clause(in, in, in, out) is det.

database_assert_clause(Database, VarSet, Term, [Clause | Database]) :-
	( Term = term__functor(term__atom(":-"), [H, B], _) ->
		Head = H,
		Body = B
	;
		Head = Term,
		term__context_init(Context),
		Body = term__functor(term__atom("true"), [], Context)
	),
	Clause = clause(VarSet, Head, Body).

:- pred database_lookup_clause(database, term, varset, term, term).
:- mode database_lookup_clause(in, in, out, out, out) is nondet.

database_lookup_clause(Database, _Goal, VarSet, Head, Body) :-
	list__member(Clause, Database),
	Clause = clause(VarSet, Head, Body).

%-----------------------------------------------------------------------------%

New File: tests/debugger/queens.exp
===================================================================
       1:      1  1 CALL CCMUL queens:main/2-0 
mtrace> mtrace>           HeadVar__1           		state('<<c_pointer>>')
       2:      2  2 CALL DET   queens:data/1-0 
mtrace> mtrace> mtrace: no live variables
       3:      2  2 EXIT DET   queens:data/1-0 
mtrace> mtrace>           HeadVar__1           		[1, 2, 3, 4, 5]
       4:      3  2 CALL NON   queens:queen/2-0 
mtrace> mtrace>           HeadVar__1           		[1, 2, 3, 4, 5]
       5:      4  3 CALL NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__1           		[1, 2, 3, 4, 5]
       6:      4  3 SWTC NON   queens:qperm/2-0 s1;
mtrace> mtrace>           HeadVar__1           		[1, 2, 3, 4, 5]
       7:      5  4 CALL NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__2           		[1, 2, 3, 4, 5]
       8:      5  4 DISJ NON   queens:qdelete/3-0 c2;d1;
mtrace> mtrace>           HeadVar__2           		[1, 2, 3, 4, 5]
          V_11                 		1
          V_10                 		[2, 3, 4, 5]
       9:      5  4 EXIT NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__1           		1
          HeadVar__3           		[2, 3, 4, 5]
          HeadVar__2           		[1, 2, 3, 4, 5]
      10:      6  4 CALL NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__1           		[2, 3, 4, 5]
      11:      6  4 SWTC NON   queens:qperm/2-0 s1;
mtrace> mtrace>           HeadVar__1           		[2, 3, 4, 5]
      12:      7  5 CALL NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__2           		[2, 3, 4, 5]
      13:      7  5 DISJ NON   queens:qdelete/3-0 c2;d1;
mtrace> mtrace>           HeadVar__2           		[2, 3, 4, 5]
          V_11                 		2
          V_10                 		[3, 4, 5]
      14:      7  5 EXIT NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__1           		2
          HeadVar__3           		[3, 4, 5]
          HeadVar__2           		[2, 3, 4, 5]
      15:      8  5 CALL NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__1           		[3, 4, 5]
      16:      8  5 SWTC NON   queens:qperm/2-0 s1;
mtrace> mtrace>           HeadVar__1           		[3, 4, 5]
      17:      9  6 CALL NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__2           		[3, 4, 5]
      18:      9  6 DISJ NON   queens:qdelete/3-0 c2;d1;
mtrace> mtrace>           HeadVar__2           		[3, 4, 5]
          V_11                 		3
          V_10                 		[4, 5]
      19:      9  6 EXIT NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__1           		3
          HeadVar__3           		[4, 5]
          HeadVar__2           		[3, 4, 5]
      20:     10  6 CALL NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__1           		[4, 5]
      21:     10  6 SWTC NON   queens:qperm/2-0 s1;
mtrace> mtrace>           HeadVar__1           		[4, 5]
      22:     11  7 CALL NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__2           		[4, 5]
      23:     11  7 DISJ NON   queens:qdelete/3-0 c2;d1;
mtrace> mtrace>           HeadVar__2           		[4, 5]
          V_11                 		4
          V_10                 		[5]
      24:     11  7 EXIT NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__1           		4
          HeadVar__3           		[5]
          HeadVar__2           		[4, 5]
      25:     12  7 CALL NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__1           		[5]
      26:     12  7 SWTC NON   queens:qperm/2-0 s1;
mtrace> mtrace>           HeadVar__1           		[5]
      27:     13  8 CALL NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__2           		[5]
      28:     13  8 DISJ NON   queens:qdelete/3-0 c2;d1;
mtrace> mtrace>           HeadVar__2           		[5]
          V_11                 		5
          V_10                 		[]
      29:     13  8 EXIT NON   queens:qdelete/3-0 
mtrace> mtrace>           HeadVar__1           		5
          HeadVar__3           		[]
          HeadVar__2           		[5]
      30:     14  8 CALL NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__1           		[]
      31:     14  8 SWTC NON   queens:qperm/2-0 s2;
mtrace> mtrace>       32:     14  8 EXIT NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__2           		[]
          HeadVar__1           		[]
      33:     12  7 EXIT NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__2           		[5]
          HeadVar__1           		[5]
      34:     10  6 EXIT NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__2           		[4, 5]
          HeadVar__1           		[4, 5]
      35:      8  5 EXIT NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__2           		[3, 4, 5]
          HeadVar__1           		[3, 4, 5]
      36:      6  4 EXIT NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__2           		[2, 3, 4, 5]
          HeadVar__1           		[2, 3, 4, 5]
      37:      4  3 EXIT NON   queens:qperm/2-0 
mtrace> mtrace>           HeadVar__2           		[1, 2, 3, 4, 5]
          HeadVar__1           		[1, 2, 3, 4, 5]
      38:     15  3 CALL SEMI  queens:safe/1-0 
mtrace> mtrace>           HeadVar__1           		[1, 2, 3, 4, 5]
      39:     15  3 SWTC SEMI  queens:safe/1-0 s1;
mtrace> mtrace>           HeadVar__1           		[1, 2, 3, 4, 5]
      40:     16  4 CALL SEMI  queens:nodiag/3-0 
mtrace> mtrace>           HeadVar__1           		1
          HeadVar__2           		1
          HeadVar__3           		[2, 3, 4, 5]
      41:     16  4 SWTC SEMI  queens:nodiag/3-0 s1;
mtrace> mtrace>           HeadVar__1           		1
          HeadVar__2           		1
          HeadVar__3           		[2, 3, 4, 5]
[1, 3, 5, 2, 4]

New File: tests/debugger/queens.inp
===================================================================
p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p

p
c

New File: tests/debugger/queens.m
===================================================================
:- module queens.

:- interface.

:- import_module io.

:- pred main(io__state, io__state).
:- mode main(di, uo) is cc_multi.

:- implementation.

:- import_module list, int.

main -->
	( { data(Data), queen(Data, Out) } ->
		print_list(Out)
	;
		io__write_string("No solution\n")
	).

:- pred data(list(int)).
:- mode data(out) is det.

:- pred queen(list(int), list(int)).
:- mode queen(in, out) is nondet.

:- pred qperm(list(T), list(T)).
:- mode qperm(in, out) is nondet.

:- pred qdelete(T, list(T), list(T)).
:- mode qdelete(out, in, out) is nondet.

:- pred safe(list(int)).
:- mode safe(in) is semidet.

:- pred nodiag(int, int, list(int)).
:- mode nodiag(in, in, in) is semidet.

data([1,2,3,4,5]).

queen(Data, Out) :-
	qperm(Data, Out),
	safe(Out).

qperm([], []).
qperm([X|Y], K) :-
	qdelete(U, [X|Y], Z),
	K = [U|V],
	qperm(Z, V).

qdelete(A, [A|L], L).
qdelete(X, [A|Z], [A|R]) :-
	qdelete(X, Z, R).

safe([]).
safe([N|L]) :-
	nodiag(N, 1, L),
	safe(L).

nodiag(_, _, []).
nodiag(B, D, [N|L]) :-
	NmB is N - B,
	BmN is B - N,
	( D = NmB ->
		fail
	; D = BmN ->
		fail
	;
		true
	),
	D1 is D + 1,
	nodiag(B, D1, L).

:- pred print_list(list(int), io__state, io__state).
:- mode print_list(in, di, uo) is det.

print_list(Xs) -->
	(
		{ Xs = [] }
	->
		io__write_string("[]\n")
	;
		io__write_string("["),
		print_list_2(Xs),
		io__write_string("]\n")
	).

:- pred print_list_2(list(int), io__state, io__state).
:- mode print_list_2(in, di, uo) is det.

print_list_2([]) --> [].
print_list_2([X|Xs]) --> 
	io__write_int(X),
	(
		{ Xs = [] }
	->
		[]
	;
		io__write_string(", "),
		print_list_2(Xs)
	).

New File: tests/debugger/runtests
===================================================================
#!/bin/sh
# Test whether the code generated by the Mercury compiler
# is producing the expected output.
# Return a status of 0 (true) if everything is all right, and 1 otherwise.

. ../handle_options

mmake $jfactor clean > /dev/null 2>&1
mmake $jfactor depend || exit 1
eval mmake -k $jfactor $gradeopt $flagsopt $cflagsopt check
checkstatus=$?

cat *.res > .allres
if test ! -s .allres -a "$checkstatus" = 0
then
	echo "the tests in the debugger directory succeeded"
	rm -f .allres
	exit 0
else
	echo "the tests in the debugger directory failed"
	echo "the differences are:"
	cat .allres
	exit 1
fi




More information about the developers mailing list