for review: stack dumps in the debugger and a bug fix

Zoltan Somogyi zs at cs.mu.OZ.AU
Sun Jun 7 13:29:30 AEST 1998


Tyson, please review this change. Peter, Fergus, please have a look at the
tratment of PROFILE_CALLS and PROFILE_TIME.

Fergus's recent change to the handling of some builtins broke the tracing
of those builtins. The following changes are a fix for this.

compiler/polymorphism.m:
	Export the predicate that checks whether a predicate is a builtin
	that lacks the usually necessary typeinfos.

	Comment out a misleading and in any case not very useful progress
	message.

compiler/liveness.m:
	Turn off type_info liveness for builtins without typeinfos.
	Since these builtins establish no gc points and shouldn't be
	execution traced, this is OK.

	Make type_info liveness part of live_info, since it can now be
	incorrect to look up the value of the option. (This may yield
	a speedup.)

compiler/live_vars.m:
compiler/store_alloc.m:
	Pass the pred_id to initial_liveness to liveness.m can do the test.

compiler/passes_aux.m:
	Add a new traversal type that passes along the pred_id.

compiler/mercury_compile.m:
	Turn off execution tracing for the modules builtin.m and
	private_builtin.m. The latter contains the interface predicates
	for the builtins without typeinfos. Since the interface predicates
	also lack the typeinfos, the compiler would get an internal abort
	if we left execution tracing on.

	In any case, these two modules contain stuff that users should
	consider language builtins, which means they should not be traced.

	Use the new traversal type for the modules that now need the pred_id.

compiler/globals.m:
	Allow the trace level to be set from outside, in this case
	mercury_compile.m.

The next batch of changes have to do with allowing execution tracing
to work in the usual (non-debug) grades, on programs in which only
some modules are compiled with tracing.

compiler/llds_out.m:
compiler/mercury_compile.m:
runtime/mercury_conf_param.h:
	Llds_out used to output "#include <mercury_imp.h>" as the first
	substantive thing in the generated C file. The set of #define
	parameters in effect when mercury_imp.h is processed determines
	whether the macros that optionally register stack layouts for label
	actually do so or not. The values of these parameters are derived
	from the grade, which means that with this setup it is not possible
	for a non-debug grade program to register its stack layouts in the
	label table.

	The new version of llds_out takes a parameter that says whether
	this module is compiled with execution tracing or not, and if it is,
	it generates a #define MR_LABELS_FOR_EXEC_TRACE *before* the #include
	of mercury_imp.h. This causes mercury_conf_param.h, included from
	mercury_imp.h, to define the macros MR_USE_STACK_LAYOUTS and
	and MR_INSERT_LABELS, which in turn cause stack layouts for this
	module to be handled as if the grade was debug.

	Use the same mechanism to #include mercury_trace.h when doing
	execution tracing, since it is simpler than the mechanism we
	used to use (mercury_compile.m including the #include in a list
	of C header file fragments).

compiler/mercury_compile.m:
runtime/mercury_conf_param.h:
	Split the MR_NEED_INITIALIZATION_CODE macro into two parts.
	The first, MR_MAY_NEED_INITIALIZATION, now controls whether
	initialization code makes it into the object file of a module.
	The second, MR_NEED_INITIALIZATION_AT_START, determines whether
	the initialization code is called before main/2.

	When a module is compiled with execution tracing, the macro
	MR_INSERT_LABELS turns on MR_MAY_NEED_INITIALIZATION but not
	MR_NEED_INITIALIZATION_AT_START. The debugger will make sure
	that the initialization code has been called before it tries
	to do a stack dump (which the initialization code to have
	been executed, because it needs labels to be put into the label
	table so that from a return address it can find the layout of the
	proc to which it belongs).

	Define MR_NEED_INITIALIZATION_AT_START if PROFILE_TIME is defined,
	since if PROFILE_TIME is defined mercury_wrapper.c calls init_modules.
	The fact that MR_NEED_INITIALIZATION_CODE didn't used to be defined
	when PROFILE_TIME was defined was, I believe, a bug, which was
	not detected because we do not turn on PROFILE_TIME without also
	turning on PROFILE_CALLS.

runtime/mercury_stack_trace.[ch]:
	Change the way stack dumps are done, to make it possible to
	print stack dumps from the debugger and to use trivial run-length
	encoding on the output (so that 100 consecutive calls to p
	yield the line "p * 100", rather than 100 lines of "p").

	The stack routine now returns an indication of whether the stack dump
	was fully successful, and if not, a description of the reason why not.
	This requires knowing when we have found the end of the stack dump,
	so we provide a global variable, MR_stack_trace_bottom, which
	mercury_wrapper.c will set to global_success, the address main/2
	goes to on success.

	s/multidet/multi/

runtime/mercury_wrapper.c:
	Set MR_stack_trace_bottom to the address of globals_success.
	Use MR_NEED_INITIALIZATION_AT_START to decide whether to call
	do_init_modules.

runtime/mercury_stacks.h:
	Provide variants of detstackvar(n) and framevar(n) that look up sp and
	curfr in an array of saved regs, for use by the debugger.

runtime/mercury_trace_util.c:
	Use the new variants of detstackvar(n) and framevar(n). This fixes
	an old bug on SPARCs.

runtime/mercury_trace_internal.c:
	Completely reorganize the way debugger commands are handled.
	Centralize reading in command lines, and the breaking up of command
	lines into words. The command names are the same as they were,
	but command syntax is now much easier to change.

	Add a new command "d" to dump as much of the stack as the available
	information will allow.

runtime/mercury_goto.h:
	Cosmetic changes to avoid the use of two different conditional
	compilation layout styles.

util/mkinit.c:
	Since we cannot know any modules are compiled with execution tracing,
	we must now include in the generated _init.c file the code to call
	the initialization functions in all the modules, even if
	MR_NEED_INITIALIZATION_AT_START is not set, since init_modules
	can be called later, from the debugger. (We should be able to
	use the same approach with the accurate collector.)

Zoltan.

cvs diff: Diffing .
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing bytecode
cvs diff: Diffing bytecode/test
cvs diff: Diffing compiler
Index: compiler/globals.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/globals.m,v
retrieving revision 1.29
diff -u -u -r1.29 globals.m
--- globals.m	1998/05/20 11:11:30	1.29
+++ globals.m	1998/06/03 11:03:04
@@ -79,6 +79,9 @@
 :- pred globals__set_options(globals::in, option_table::in, globals::out)
 	is det.
 
+:- pred globals__set_trace_level(globals::in, trace_level::in, globals::out)
+	is det.
+
 :- pred globals__lookup_option(globals::in, option::in, option_data::out)
 	is det.
 
@@ -136,6 +139,9 @@
 :- pred globals__io_set_option(option::in, option_data::in,
 	io__state::di, io__state::uo) is det.
 
+:- pred globals__io_set_trace_level(trace_level::in,
+	io__state::di, io__state::uo) is det.
+
 :- pred globals__io_lookup_option(option::in, option_data::out,
 	io__state::di, io__state::uo) is det.
 
@@ -230,6 +236,9 @@
 globals__set_options(globals(_, B, C, D, E, F, G), Options,
 	globals(Options, B, C, D, E, F, G)).
 
+globals__set_trace_level(globals(A, B, C, D, E, F, _), TraceLevel,
+	globals(A, B, C, D, E, F, TraceLevel)).
+
 globals__lookup_option(Globals, Option, OptionData) :-
 	globals__get_options(Globals, OptionTable),
 	map__lookup(OptionTable, Option, OptionData).
@@ -351,6 +360,14 @@
 		% XXX there is a bit of a design flaw with regard to
 		% uniqueness and io__set_globals
 	{ unsafe_promise_unique(Globals1, Globals) },
+	globals__io_set_globals(Globals).
+
+globals__io_set_trace_level(TraceLevel) -->
+	globals__io_get_globals(Globals0),
+	{ globals__set_trace_level(Globals0, TraceLevel, Globals1) },
+	{ unsafe_promise_unique(Globals1, Globals) },
+		% XXX there is a bit of a design flaw with regard to
+		% uniqueness and io__set_globals
 	globals__io_set_globals(Globals).
 
 %-----------------------------------------------------------------------------%
Index: compiler/live_vars.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/live_vars.m,v
retrieving revision 1.74
diff -u -u -r1.74 live_vars.m
--- live_vars.m	1998/05/16 07:30:08	1.74
+++ live_vars.m	1998/06/03 11:03:04
@@ -25,9 +25,9 @@
 
 :- import_module hlds_module, hlds_pred.
 
-:- pred allocate_stack_slots_in_proc(proc_info, module_info, proc_info).
-% :- mode allocate_stack_slots_in_proc(di, in, uo) is det.
-:- mode allocate_stack_slots_in_proc(in, in, out) is det.
+:- pred allocate_stack_slots_in_proc(proc_info, pred_id, module_info,
+	proc_info).
+:- mode allocate_stack_slots_in_proc(in, in, in, out) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -42,11 +42,11 @@
 
 %-----------------------------------------------------------------------------%
 
-allocate_stack_slots_in_proc(ProcInfo0, ModuleInfo, ProcInfo) :-
+allocate_stack_slots_in_proc(ProcInfo0, PredId, ModuleInfo, ProcInfo) :-
 	proc_info_goal(ProcInfo0, Goal0),
 	proc_info_interface_code_model(ProcInfo0, CodeModel),
 
-	initial_liveness(ProcInfo0, ModuleInfo, Liveness0),
+	initial_liveness(ProcInfo0, PredId, ModuleInfo, Liveness0),
 	set__init(LiveSets0),
 	module_info_globals(ModuleInfo, Globals),
 	globals__get_trace_level(Globals, TraceLevel),
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.93
diff -u -u -r1.93 liveness.m
--- liveness.m	1998/05/16 07:30:12	1.93
+++ liveness.m	1998/06/05 09:56:26
@@ -44,7 +44,7 @@
 % occurrence of a variable include that variable in their post-death
 % set. In branched structures, branches in which a variable is not
 % used at all include a pre-death set listing the variables that
-% have died in parallel branches. 
+% have died in parallel branches.
 %
 % The third pass, detect_resume_points_in_goal, finds goals that
 % establish resume points and attaches to them a resume_point
@@ -130,13 +130,13 @@
 	% This consists of the {pre,post}{birth,death} sets and
 	% resume point information.
 
-:- pred detect_liveness_proc(proc_info, module_info, proc_info).
-:- mode detect_liveness_proc(in, in, out) is det.
+:- pred detect_liveness_proc(proc_info, pred_id, module_info, proc_info).
+:- mode detect_liveness_proc(in, in, in, out) is det.
 
 	% Return the set of variables live at the start of the procedure.
 
-:- pred initial_liveness(proc_info, module_info, set(var)).
-:- mode initial_liveness(in, in, out) is det.
+:- pred initial_liveness(proc_info, pred_id, module_info, set(var)).
+:- mode initial_liveness(in, in, in, out) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -145,26 +145,42 @@
 
 :- import_module hlds_goal, hlds_data, llds, quantification, (inst), instmap.
 :- import_module hlds_out, mode_util, code_util, quantification, options.
-:- import_module prog_data, trace, globals, passes_aux.
+:- import_module prog_data, trace, globals, polymorphism, passes_aux.
 
 :- import_module bool, map, std_util, list, assoc_list, require.
 :- import_module varset, string.
 
-detect_liveness_proc(ProcInfo0, ModuleInfo, ProcInfo) :-
+detect_liveness_proc(ProcInfo0, PredId, ModuleInfo, ProcInfo) :-
 	requantify_proc(ProcInfo0, ProcInfo1),
 	proc_info_goal(ProcInfo1, Goal0),
 	proc_info_varset(ProcInfo1, Varset),
 	proc_info_vartypes(ProcInfo1, VarTypes),
-	live_info_init(ModuleInfo, ProcInfo1, VarTypes, Varset, LiveInfo),
+	module_info_globals(ModuleInfo, Globals),
+	globals__lookup_bool_option(Globals, typeinfo_liveness,
+		TypeInfoLiveness0),
+
+	module_info_pred_info(ModuleInfo, PredId, PredInfo),
+	pred_info_module(PredInfo, PredModule),
+	pred_info_name(PredInfo, PredName),
+	pred_info_arity(PredInfo, PredArity),
+	(
+		polymorphism__no_type_info_builtin(PredModule,
+			PredName, PredArity)
+	->
+		TypeInfoLiveness = no
+	;
+		TypeInfoLiveness = TypeInfoLiveness0
+	),
+	live_info_init(ModuleInfo, ProcInfo1, TypeInfoLiveness,
+		VarTypes, Varset, LiveInfo),
 
-	initial_liveness(ProcInfo1, ModuleInfo, Liveness0),
+	initial_liveness(ProcInfo1, PredId, ModuleInfo, Liveness0),
 	detect_liveness_in_goal(Goal0, Liveness0, LiveInfo,
 		_, Goal1),
 
-	initial_deadness(ProcInfo1, ModuleInfo, Deadness0),
+	initial_deadness(ProcInfo1, LiveInfo, ModuleInfo, Deadness0),
 	detect_deadness_in_goal(Goal1, Deadness0, LiveInfo, _, Goal2),
 
-	module_info_globals(ModuleInfo, Globals),
 	globals__get_trace_level(Globals, TraceLevel),
 	( ( TraceLevel = interface ; TraceLevel = full ) ->
 		trace__fail_vars(ModuleInfo, ProcInfo0, ResumeVars0)
@@ -261,10 +277,9 @@
 	detect_liveness_in_goal(Cond0, Liveness0, LiveInfo, LivenessCond, Cond),
 
 	%
-	% If the condition cannot succeed, any variables which become
-	% live in the else part should put in the post-birth set of the
-	% then part by add_liveness_after_goal, and the other sets
-	% should be empty.
+	% If the condition cannot succeed, any variables which become live
+	% in the else part should be put in the post-birth set of the then part
+	% by add_liveness_after_goal, and the other sets should be empty.
 	%
 	Cond = _ - CondInfo,
 	goal_info_get_instmap_delta(CondInfo, CondDelta),
@@ -867,7 +882,7 @@
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-initial_liveness(ProcInfo, ModuleInfo, Liveness) :-
+initial_liveness(ProcInfo, PredId, ModuleInfo, Liveness) :-
 	proc_info_headvars(ProcInfo, Vars),
 	proc_info_argmodes(ProcInfo, Modes),
 	proc_info_vartypes(ProcInfo, VarTypes),
@@ -881,21 +896,27 @@
 	;
 		error("initial_liveness: list length mismatch")
 	),
-	module_info_globals(ModuleInfo, Globals),
 
 		% If a variable is unused in the goal, it shouldn't be
 		% in the initial liveness. (If we allowed it to start
 		% live, it wouldn't ever become dead, because it would
 		% have to be used to be killed).
 		% So we intersect the headvars with the non-locals and
-		% (if doing alternate liveness calculation) their
+		% (if doing typeinfo liveness calculation) their
 		% typeinfo vars.
+	module_info_globals(ModuleInfo, Globals),
 	proc_info_goal(ProcInfo, _Goal - GoalInfo),
 	goal_info_get_nonlocals(GoalInfo, NonLocals0),
 	globals__lookup_bool_option(Globals, typeinfo_liveness, 
 		TypeinfoLiveness),
+	module_info_pred_info(ModuleInfo, PredId, PredInfo),
+	pred_info_module(PredInfo, PredModule),
+	pred_info_name(PredInfo, PredName),
+	pred_info_arity(PredInfo, PredArity),
 	( 	
-		TypeinfoLiveness = yes
+		TypeinfoLiveness = yes,
+		\+ polymorphism__no_type_info_builtin(PredModule,
+			PredName, PredArity)
 	->
 		proc_info_get_typeinfo_vars_setwise(ProcInfo, NonLocals0,
 			TypeInfoNonLocals),
@@ -905,7 +926,6 @@
 	),
 	set__intersect(Liveness2, NonLocals, Liveness).
 
-
 :- pred initial_liveness_2(list(var), list(mode), list(type), module_info,
 	set(var), set(var)).
 :- mode initial_liveness_2(in, in, in, in, in, out) is semidet.
@@ -924,15 +944,16 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred initial_deadness(proc_info, module_info, set(var)).
-:- mode initial_deadness(in, in, out) is det.
+:- pred initial_deadness(proc_info, live_info, module_info, set(var)).
+:- mode initial_deadness(in, in, in, out) is det.
 
-initial_deadness(ProcInfo, ModuleInfo, Deadness) :-
+initial_deadness(ProcInfo, LiveInfo, ModuleInfo, Deadness) :-
 	proc_info_headvars(ProcInfo, Vars),
 	proc_info_argmodes(ProcInfo, Modes),
 	proc_info_vartypes(ProcInfo, VarTypes),
 	map__apply_to_list(Vars, VarTypes, Types),
 	set__init(Deadness0),
+		% All output arguments are in the initial deadness.
 	(
 		initial_deadness_2(Vars, Modes, Types, ModuleInfo,
 			Deadness0, Deadness1)
@@ -941,11 +962,10 @@
 	;
 		error("initial_deadness: list length mis-match")
 	),
+
 		% If doing alternate liveness, the corresponding
 		% typeinfos need to be added to these.
-	module_info_globals(ModuleInfo, Globals),
-	globals__lookup_bool_option(Globals, typeinfo_liveness, 
-		TypeinfoLiveness),
+	live_info_get_typeinfo_liveness(LiveInfo, TypeinfoLiveness),
 	( 
 		TypeinfoLiveness = yes
 	->
@@ -1029,36 +1049,43 @@
 :- type live_info	--->	live_info(
 					module_info,
 					proc_info,
+					bool,
 					map(var, type),
 					varset
 				).
 
-:- pred live_info_init(module_info, proc_info, map(var, type),
+:- pred live_info_init(module_info, proc_info, bool, map(var, type),
 	varset, live_info).
-:- mode live_info_init(in, in, in, in, out) is det.
+:- mode live_info_init(in, in, in, in, in, out) is det.
 
-live_info_init(ModuleInfo, ProcInfo, VarTypes, Varset,
-	live_info(ModuleInfo, ProcInfo, VarTypes, Varset)).
+live_info_init(ModuleInfo, ProcInfo, TypeInfoLiveness, VarTypes, Varset,
+	live_info(ModuleInfo, ProcInfo, TypeInfoLiveness, VarTypes, Varset)).
 
 :- pred live_info_get_module_info(live_info, module_info).
 :- mode live_info_get_module_info(in, out) is det.
 
-live_info_get_module_info(live_info(ModuleInfo, _, _, _), ModuleInfo).
+live_info_get_module_info(live_info(ModuleInfo, _, _, _, _), ModuleInfo).
 
 :- pred live_info_get_proc_info(live_info, proc_info).
 :- mode live_info_get_proc_info(in, out) is det.
+
+live_info_get_proc_info(live_info(_, ProcInfo, _, _, _), ProcInfo).
+
+:- pred live_info_get_typeinfo_liveness(live_info, bool).
+:- mode live_info_get_typeinfo_liveness(in, out) is det.
 
-live_info_get_proc_info(live_info(_, ProcInfo, _, _), ProcInfo).
+live_info_get_typeinfo_liveness(live_info(_, _, TypeInfoLiveness, _, _),
+	TypeInfoLiveness).
 
 :- pred live_info_get_var_types(live_info, map(var, type)).
 :- mode live_info_get_var_types(in, out) is det.
 
-live_info_get_var_types(live_info(_, _, VarTypes, _), VarTypes).
+live_info_get_var_types(live_info(_, _, _, VarTypes, _), VarTypes).
 
 :- pred live_info_get_varset(live_info, varset).
 :- mode live_info_get_varset(in, out) is det.
 
-live_info_get_varset(live_info(_, _, _, Varset), Varset).
+live_info_get_varset(live_info(_, _, _, _, Varset), Varset).
 
 %-----------------------------------------------------------------------------%
 
@@ -1068,13 +1095,11 @@
 :- pred liveness__get_nonlocals_and_typeinfos(live_info, hlds_goal_info,
 		set(var)).
 :- mode liveness__get_nonlocals_and_typeinfos(in, in, out) is det.
+
 liveness__get_nonlocals_and_typeinfos(LiveInfo, GoalInfo, 
 		NonLocals) :-
-	live_info_get_module_info(LiveInfo, ModuleInfo),
-	module_info_globals(ModuleInfo, Globals),
 	goal_info_get_nonlocals(GoalInfo, NonLocals0),
-	globals__lookup_bool_option(Globals, typeinfo_liveness, 
-		TypeinfoLiveness),
+	live_info_get_typeinfo_liveness(LiveInfo, TypeinfoLiveness),
 	( 
 		TypeinfoLiveness = yes
 	->
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.81
diff -u -u -r1.81 llds_out.m
--- llds_out.m	1998/05/25 21:48:49	1.81
+++ llds_out.m	1998/06/03 11:03:04
@@ -21,10 +21,13 @@
 :- import_module set_bbbtree, bool, io.
 
 	% Given a 'c_file' structure, open the appropriate .c file
-	% and output the code into that file.
+	% and output the code into that file. The bool says whether
+	% this Mercury module was compiled with any flavor of execution
+	% tracing; the third argument gives the set of labels that have
+	% layout structures.
 
-:- pred output_c_file(c_file, set_bbbtree(label), io__state, io__state).
-:- mode output_c_file(in, in, di, uo) is det.
+:- pred output_c_file(c_file, bool, set_bbbtree(label), io__state, io__state).
+:- mode output_c_file(in, in, in, di, uo) is det.
 
 	% Convert an lval to a string description of that lval.
 
@@ -135,17 +138,17 @@
 		;	data_addr(data_addr)
 		;	pragma_c_struct(string).
 
-output_c_file(C_File, StackLayoutLabels) -->
+output_c_file(C_File, ExecTrace, StackLayoutLabels) -->
 	globals__io_lookup_bool_option(split_c_files, SplitFiles),
 	( { SplitFiles = yes } ->
 		{ C_File = c_file(ModuleName, C_HeaderInfo, C_Modules) },
 		module_name_to_file_name(ModuleName, ".dir", yes, ObjDirName),
 		make_directory(ObjDirName),
-		output_c_file_init(ModuleName, C_Modules),
-		output_c_file_list(C_Modules, 1, ModuleName, C_HeaderInfo,
-			StackLayoutLabels)
+		output_c_file_init(ModuleName, ExecTrace, C_Modules),
+		output_c_file_list(C_Modules, ExecTrace, 1, ModuleName,
+			C_HeaderInfo, StackLayoutLabels)
 	;
-		output_single_c_file(C_File, no, StackLayoutLabels)
+		output_single_c_file(C_File, ExecTrace, no, StackLayoutLabels)
 	).
 
 :- pred make_directory(string, io__state, io__state).
@@ -156,23 +159,24 @@
 		Command) },
 	io__call_system(Command, _Result).
 
-:- pred output_c_file_list(list(c_module), int, module_name,
+:- pred output_c_file_list(list(c_module), bool, int, module_name,
 	list(c_header_code), set_bbbtree(label), io__state, io__state).
-:- mode output_c_file_list(in, in, in, in, in, di, uo) is det.
+:- mode output_c_file_list(in, in, in, in, in, in, di, uo) is det.
 
-output_c_file_list([], _, _, _, _) --> [].
-output_c_file_list([Module|Modules], Num, ModuleName, C_HeaderLines,
+output_c_file_list([], _, _, _, _, _) --> [].
+output_c_file_list([Module|Modules], ExecTrace, Num, ModuleName, C_HeaderLines,
 		StackLayoutLabels) -->
 	output_single_c_file(c_file(ModuleName, C_HeaderLines, [Module]),
-		yes(Num), StackLayoutLabels),
+		ExecTrace, yes(Num), StackLayoutLabels),
 	{ Num1 is Num + 1 },
-	output_c_file_list(Modules, Num1, ModuleName, C_HeaderLines,
+	output_c_file_list(Modules, ExecTrace, Num1, ModuleName, C_HeaderLines,
 		StackLayoutLabels).
 
-:- pred output_c_file_init(module_name, list(c_module), io__state, io__state).
-:- mode output_c_file_init(in, in, di, uo) is det.
+:- pred output_c_file_init(module_name, bool, list(c_module),
+	io__state, io__state).
+:- mode output_c_file_init(in, in, in, di, uo) is det.
 
-output_c_file_init(ModuleName, C_Modules) -->
+output_c_file_init(ModuleName, ExecTrace, C_Modules) -->
 	module_name_to_file_name(ModuleName, ".m", no, SourceFileName),
 	module_name_to_split_c_file_name(ModuleName, 0, ".c", FileName),
 
@@ -194,7 +198,13 @@
 		io__write_string("\n"),
 		io__write_string("ENDINIT\n"),
 		io__write_string("*/\n\n"),
-		io__write_string("#include ""mercury_imp.h""\n"),
+		( { ExecTrace = yes } ->
+			io__write_string("#define MR_LABELS_FOR_EXEC_TRACE\n"),
+			io__write_string("#include ""mercury_imp.h""\n"),
+			io__write_string("#include ""mercury_trace.h""\n")
+		;
+			io__write_string("#include ""mercury_imp.h""\n")
+		),
 		io__write_string("\n"),
 		output_c_module_init_list(ModuleName, C_Modules),
 		io__told
@@ -208,12 +218,12 @@
 		io__set_exit_status(1)
 	).
 
-:- pred output_single_c_file(c_file, maybe(int), set_bbbtree(label),
+:- pred output_single_c_file(c_file, bool, maybe(int), set_bbbtree(label),
 	io__state, io__state).
-:- mode output_single_c_file(in, in, in, di, uo) is det.
+:- mode output_single_c_file(in, in, in, in, di, uo) is det.
 
-output_single_c_file(c_file(ModuleName, C_HeaderLines, Modules), SplitFiles,
-		StackLayoutLabels) -->
+output_single_c_file(c_file(ModuleName, C_HeaderLines, Modules), ExecTrace,
+		SplitFiles, StackLayoutLabels) -->
 	( { SplitFiles = yes(Num) } ->
 		module_name_to_split_c_file_name(ModuleName, Num, ".c",
 			FileName)
@@ -242,8 +252,14 @@
 			io__write_string("\n"),
 			io__write_string("ENDINIT\n"),
 			io__write_string("*/\n\n")
+		),
+		( { ExecTrace = yes } ->
+			io__write_string("#define MR_LABELS_FOR_EXEC_TRACE\n"),
+			io__write_string("#include ""mercury_imp.h""\n"),
+			io__write_string("#include ""mercury_trace.h""\n")
+		;
+			io__write_string("#include ""mercury_imp.h""\n")
 		),
-		io__write_string("#include ""mercury_imp.h""\n"),
 		output_c_header_include_lines(C_HeaderLines),
 		io__write_string("\n"),
 		{ gather_c_file_labels(Modules, Labels) },
@@ -275,7 +291,7 @@
 
 		% Output initialization functions, bunched into groups
 		% of 40.
-	io__write_string("#if defined(MR_NEED_INITIALIZATION_CODE)\n\n"),
+	io__write_string("#if defined(MR_MAY_NEED_INITIALIZATION)\n\n"),
 	io__write_string("static void "),
 	output_bunch_name(ModuleName, 0),
 	io__write_string("(void)\n"),
@@ -293,7 +309,7 @@
 	output_init_name(ModuleName),
 	io__write_string("(void)\n"),
 	io__write_string("{\n"),
-	io__write_string("#if defined(MR_NEED_INITIALIZATION_CODE)\n\n"),
+	io__write_string("#if defined(MR_MAY_NEED_INITIALIZATION)\n\n"),
 	io__write_string("\tstatic bool done = FALSE;\n"),
 	io__write_string("\tif (!done) {\n"),
 	io__write_string("\t\tdone = TRUE;\n"),
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.96
diff -u -u -r1.96 mercury_compile.m
--- mercury_compile.m	1998/06/05 09:12:07	1.96
+++ mercury_compile.m	1998/06/07 04:52:09
@@ -28,7 +28,7 @@
 :- import_module int, list, map, set, std_util, dir, require, string, bool.
 :- import_module library, getopt, term, set_bbbtree, varset.
 
-	% the main compiler passes (in order of execution)
+	% the main compiler passes (mostly in order of execution)
 :- import_module handle_options, prog_io, prog_out, modules, module_qual.
 :- import_module equiv_type, make_hlds, typecheck, purity, modes.
 :- import_module switch_detection, cse_detection, det_analysis, unique_modes.
@@ -45,7 +45,7 @@
 	% miscellaneous compiler modules
 :- import_module prog_data, hlds_module, hlds_pred, hlds_out, llds.
 :- import_module mercury_to_c, mercury_to_mercury, mercury_to_goedel.
-:- import_module dependency_graph.
+:- import_module dependency_graph, prog_util.
 :- import_module options, globals, passes_aux.
 
 %-----------------------------------------------------------------------------%
@@ -225,17 +225,41 @@
 		{ ModulesToLink = [] }
 	;
 		{ split_into_submodules(ModuleName, Items, SubModuleList) },
-		list__foldl(compile(FileName), SubModuleList),
-		list__map_foldl(module_to_link, SubModuleList, ModulesToLink)
+		(
+			{ mercury_private_builtin_module(ModuleName)
+			; mercury_public_builtin_module(ModuleName)
+			}
+		->
+			% Some predicates in the builtin modules are missing
+			% typeinfo arguments, which means that tracing will
+			% not work on them. Predicates defined there should
+			% never be traced anyway; they are effectively
+			% language primitives.
+			globals__io_lookup_bool_option(trace_stack_layout, TSL),
+			globals__io_get_trace_level(TraceLevel),
+
+			globals__io_set_option(trace_stack_layout, bool(no)),
+			globals__io_set_trace_level(minimal),
+
+			% XXX it would be better to do something like
+			%
+			%	list__map_foldl(compile_to_llds, SubModuleList,
+			%		LLDS_FragmentList),
+			%	merge_llds_fragments(LLDS_FragmentList, LLDS),
+			%	output_pass(LLDS_FragmentList)
+			%
+			% i.e. compile nested modules to a single C file.
+			list__foldl(compile(FileName), SubModuleList),
+			list__map_foldl(module_to_link, SubModuleList,
+				ModulesToLink),
 
-		% XXX it would be better to do something like
-		%
-		%	list__map_foldl(compile_to_llds, SubModuleList,
-		%		LLDS_FragmentList),
-		%	merge_llds_fragments(LLDS_FragmentList, LLDS),
-		%	output_pass(LLDS_FragmentList)
-		%
-		% i.e. compile nested modules to a single C file.
+			globals__io_set_option(trace_stack_layout, bool(TSL)),
+			globals__io_set_trace_level(TraceLevel)
+		;
+			list__foldl(compile(FileName), SubModuleList),
+			list__map_foldl(module_to_link, SubModuleList,
+				ModulesToLink)
+		)
 	).
 
 :- pred make_interface(file_name, pair(module_name, item_list),
@@ -1073,14 +1097,15 @@
 	),
 	write_proc_progress_message("% Computing liveness in ", PredId, ProcId,
 		ModuleInfo3),
-	{ detect_liveness_proc(ProcInfo3, ModuleInfo3, ProcInfo4) },
+	{ detect_liveness_proc(ProcInfo3, PredId, ModuleInfo3, ProcInfo4) },
 	write_proc_progress_message("% Allocating stack slots in ", PredId,
 		                ProcId, ModuleInfo3),
-	{ allocate_stack_slots_in_proc(ProcInfo4, ModuleInfo3, ProcInfo5) },
+	{ allocate_stack_slots_in_proc(ProcInfo4, PredId, ModuleInfo3,
+		ProcInfo5) },
 	write_proc_progress_message(
 		"% Allocating storage locations for live vars in ",
 				PredId, ProcId, ModuleInfo3),
-	{ store_alloc_in_proc(ProcInfo5, ModuleInfo3, ProcInfo6) },
+	{ store_alloc_in_proc(ProcInfo5, PredId, ModuleInfo3, ProcInfo6) },
 	globals__io_get_trace_level(TraceLevel),
 	( { TraceLevel = interface ; TraceLevel = full } ->
 		write_proc_progress_message(
@@ -1684,7 +1709,7 @@
 mercury_compile__compute_liveness(HLDS0, Verbose, Stats, HLDS) -->
 	maybe_write_string(Verbose, "% Computing liveness...\n"),
 	maybe_flush_output(Verbose),
-	process_all_nonimported_procs(update_proc(detect_liveness_proc),
+	process_all_nonimported_procs(update_proc_predid(detect_liveness_proc),
 		HLDS0, HLDS),
 	maybe_write_string(Verbose, "% done.\n"),
 	maybe_report_stats(Stats).
@@ -1696,7 +1721,8 @@
 mercury_compile__compute_stack_vars(HLDS0, Verbose, Stats, HLDS) -->
 	maybe_write_string(Verbose, "% Computing stack vars..."),
 	maybe_flush_output(Verbose),
-	process_all_nonimported_procs(update_proc(allocate_stack_slots_in_proc),
+	process_all_nonimported_procs(
+		update_proc_predid(allocate_stack_slots_in_proc),
 		HLDS0, HLDS),
 	maybe_write_string(Verbose, " done.\n"),
 	maybe_report_stats(Stats).
@@ -1708,7 +1734,7 @@
 mercury_compile__allocate_store_map(HLDS0, Verbose, Stats, HLDS) -->
 	maybe_write_string(Verbose, "% Allocating store map..."),
 	maybe_flush_output(Verbose),
-	process_all_nonimported_procs(update_proc(store_alloc_in_proc),
+	process_all_nonimported_procs(update_proc_predid(store_alloc_in_proc),
 		HLDS0, HLDS),
 	maybe_write_string(Verbose, " done.\n"),
 	maybe_report_stats(Stats).
@@ -1882,15 +1908,7 @@
 			ProcModules) }
 	),
 	maybe_add_header_file_include(C_ExportDecls, ModuleName, C_HeaderCode0,
-		C_HeaderCode1),
-	globals__io_get_trace_level(TraceLevel),
-	( { TraceLevel = interface ; TraceLevel = full } ->
-		{ term__context_init(Context) },
-		{ TraceInclude = "#include ""mercury_trace.h""\n" - Context },
-		{ list__append(C_HeaderCode1, [TraceInclude], C_HeaderCode) }
-	;
-		{ C_HeaderCode = C_HeaderCode1 }
-	),
+		C_HeaderCode),
 	{ list__condense([C_BodyCode, BaseTypeData, CommonDataModules,
 		ProcModules, [c_export(C_ExportDefns)]], ModuleList) },
 	{ list__length(ModuleList, NumChunks) }.
@@ -1969,7 +1987,13 @@
 	maybe_write_string(Verbose, FileName),
 	maybe_write_string(Verbose, "'..."),
 	maybe_flush_output(Verbose),
-	output_c_file(LLDS, StackLayoutLabels),
+	globals__io_get_trace_level(TraceLevel),
+	( { TraceLevel = interface ; TraceLevel = full } ->
+		{ ExecTrace = yes }
+	;
+		{ ExecTrace = no }
+	),
+	output_c_file(LLDS, ExecTrace, StackLayoutLabels),
 	maybe_write_string(Verbose, " done.\n"),
 	maybe_flush_output(Verbose),
 	maybe_report_stats(Stats).
Index: compiler/passes_aux.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/passes_aux.m,v
retrieving revision 1.25
diff -u -u -r1.25 passes_aux.m
--- passes_aux.m	1998/03/03 17:35:34	1.25
+++ passes_aux.m	1998/06/05 02:22:55
@@ -20,6 +20,8 @@
 
 :- type task	--->	update_proc(pred(
 				proc_info, module_info, proc_info))
+		;	update_proc_predid(pred(
+				proc_info, pred_id, module_info, proc_info))
 		;	update_proc_io(pred(
 				pred_id, proc_id, module_info,
 				proc_info, proc_info, io__state, io__state))
@@ -73,6 +75,7 @@
 ****************/
 
 :- inst task =	bound(( update_proc(pred(in, in, out) is det)
+		;	update_proc_predid(pred(in, in, in, out) is det)
 		;	update_proc_io(pred(in, in, in, in, out, di, uo) is det)
 		;	update_proc_error(pred(in, in, in, out, in, out,
 				out, out, di, uo) is det)
@@ -121,7 +124,6 @@
 				io__state, io__state).
 :- mode report_pred_name_mode(in, in, in, di, uo) is det.
 	
-
 %-----------------------------------------------------------------------------%
 
 :- implementation.
@@ -186,6 +188,12 @@
 	;
 		Task0 = update_proc(Closure),
 		call(Closure, Proc0, ModuleInfo0, Proc),
+		ModuleInfo8 = ModuleInfo0,
+		Task1 = Task0,
+		State9 = State0
+	;
+		Task0 = update_proc_predid(Closure),
+		call(Closure, Proc0, PredId, ModuleInfo0, Proc),
 		ModuleInfo8 = ModuleInfo0,
 		Task1 = Task0,
 		State9 = State0
Index: compiler/polymorphism.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/polymorphism.m,v
retrieving revision 1.134
diff -u -u -r1.134 polymorphism.m
--- polymorphism.m	1998/05/25 21:48:53	1.134
+++ polymorphism.m	1998/06/03 11:03:04
@@ -280,20 +280,30 @@
 
 :- module polymorphism.
 :- interface.
-:- import_module hlds_module.
+
+:- import_module hlds_module, prog_data.
 :- import_module io.
 
 :- pred polymorphism__process_module(module_info, module_info,
 			io__state, io__state).
 :- mode polymorphism__process_module(in, out, di, uo) is det.
 
+	% unsafe_type_cast and unsafe_promise_unique are polymorphic
+	% builtins which do not need their type_infos. unsafe_type_cast
+	% can be introduced by common.m after polymorphism is run, so it
+	% is much simpler to avoid introducing type_info arguments for it.
+	% Since both of these are really just assignment unifications, it
+	% is desirable to generate them inline.
+:- pred polymorphism__no_type_info_builtin(module_name, string, int).
+:- mode polymorphism__no_type_info_builtin(in, in, out) is semidet.
+
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
 :- implementation.
 
 :- import_module hlds_pred, hlds_goal, hlds_data, llds, (lambda).
-:- import_module prog_data, type_util, mode_util, quantification, instmap.
+:- import_module 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, goal_util, passes_aux.
 
@@ -363,8 +373,11 @@
 	pred_info_procedures(PredInfo0, ProcTable0),
 	map__lookup(ProcTable0, ProcId, ProcInfo0),
 
-	write_proc_progress_message("% Transforming polymorphism for ",
-				PredId, ProcId, ModuleInfo0, IO0, IO1),
+%	It is misleading to output this message for predicates which are
+%	not defined in this module, and we get far too many of them anyway.
+%	write_proc_progress_message("% Transforming polymorphism for ",
+%				PredId, ProcId, ModuleInfo0, IO0, IO1),
+	IO1 = IO0,
 
 	polymorphism__process_proc(ProcInfo0, PredInfo0, ModuleInfo0,
 					ProcInfo, PredInfo1, ModuleInfo1),
@@ -378,15 +391,6 @@
 
 	polymorphism__process_procs(PredId, ProcIds, ModuleInfo2, ModuleInfo,
 			IO1, IO).
-
-	% unsafe_type_cast and unsafe_promise_unique are polymorphic
-	% builtins which do not need their type_infos. unsafe_type_cast
-	% can be introduced by common.m after polymorphism is run, so it
-	% is much simpler to avoid introducing type_info arguments for it.
-	% Since both of these are really just assignment unifications, it
-	% is desirable to generate them inline.
-:- pred polymorphism__no_type_info_builtin(module_name, string, int).
-:- mode polymorphism__no_type_info_builtin(in, in, out) is semidet.
 
 polymorphism__no_type_info_builtin(MercuryBuiltin, "unsafe_type_cast", 2) :-
 	mercury_private_builtin_module(MercuryBuiltin).
Index: compiler/store_alloc.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/store_alloc.m,v
retrieving revision 1.63
diff -u -u -r1.63 store_alloc.m
--- store_alloc.m	1998/05/16 07:30:51	1.63
+++ store_alloc.m	1998/06/03 11:03:04
@@ -28,8 +28,8 @@
 
 :- import_module hlds_module, hlds_pred.
 
-:- pred store_alloc_in_proc(proc_info, module_info, proc_info).
-:- mode store_alloc_in_proc(in, in, out) is det.
+:- pred store_alloc_in_proc(proc_info, pred_id, module_info, proc_info).
+:- mode store_alloc_in_proc(in, in, in, out) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -51,7 +51,7 @@
 
 %-----------------------------------------------------------------------------%
 
-store_alloc_in_proc(ProcInfo0, ModuleInfo, ProcInfo) :-
+store_alloc_in_proc(ProcInfo0, PredId, ModuleInfo, ProcInfo) :-
 	module_info_globals(ModuleInfo, Globals),
 	globals__lookup_bool_option(Globals, follow_vars, ApplyFollowVars),
 	( ApplyFollowVars = yes ->
@@ -67,7 +67,7 @@
 	;
 		proc_info_goal(ProcInfo0, Goal2)
 	),
-	initial_liveness(ProcInfo0, ModuleInfo, Liveness0),
+	initial_liveness(ProcInfo0, PredId, ModuleInfo, Liveness0),
 	globals__get_trace_level(Globals, TraceLevel),
 	( ( TraceLevel = interface ; TraceLevel = full ) ->
 		trace__fail_vars(ModuleInfo, ProcInfo0, ResumeVars0)
cvs diff: Diffing compiler/notes
cvs diff: Diffing doc
cvs diff: Diffing extras
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/Togl-1.2
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing library
cvs diff: Diffing lp_solve
cvs diff: Diffing lp_solve/lp_examples
cvs diff: Diffing profiler
cvs diff: Diffing runtime
Index: runtime/mercury_conf_param.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_conf_param.h,v
retrieving revision 1.4
diff -u -u -r1.4 mercury_conf_param.h
--- mercury_conf_param.h	1998/05/20 11:11:51	1.4
+++ mercury_conf_param.h	1998/06/05 10:21:34
@@ -123,7 +123,7 @@
 ** MR_DEBUG_NONDET_STACK
 **	Include a "name" field in the nondet stack frames.
 **	(Since this affects binary compatibility,
-**	This is a "compilation model" option which affects the grade.)
+**	this is a "compilation model" option which affects the grade.)
 */
 
 /*
@@ -181,7 +181,7 @@
 #ifdef MR_USE_STACK_LAYOUTS
   #error "MR_USE_STACK_LAYOUTS should not be defined on the command line"
 #endif
-#if defined(MR_STACK_TRACE) || defined(NATIVE_GC)
+#if defined(MR_STACK_TRACE) || defined(NATIVE_GC) || defined(MR_LABELS_FOR_EXEC_TRACE)
   #define MR_USE_STACK_LAYOUTS
 #endif
 
@@ -193,7 +193,7 @@
 #ifdef MR_INSERT_LABELS
   #error "MR_INSERT_LABELS should not be defined on the command line"
 #endif
-#if defined(MR_STACK_TRACE) || defined(NATIVE_GC) || defined(MR_DEBUG_GOTOS)
+#if defined(MR_STACK_TRACE) || defined(NATIVE_GC) || defined(MR_DEBUG_GOTOS) || defined(MR_LABELS_FOR_EXEC_TRACE)
   #define MR_INSERT_LABELS
 #endif
 
@@ -209,20 +209,34 @@
 #endif
 
 /*
-** MR_NEED_INITIALIZATION_CODE -- the module specific initialization code
-**				  is needed (doesn't actually run the code,
-**				  however).
+** MR_NEED_INITIALIZATION_AT_START -- the module specific initialization code
+**				      must be run any Mercury code is run.
 **
 ** You need to run initialization code for grades without static
 ** code addresses, for profiling, and any time you need to insert
 ** labels into the label table.
 */
-#ifdef MR_NEED_INITIALIZATION_CODE
-  #error "NEED_INITIALIZATION_CODE should not be defined on the command line"
+#ifdef MR_NEED_INITIALIZATION_AT_START
+  #error "MR_NEED_INITIALIZATION_AT_START should not be defined on the command line"
 #endif
 #if !defined(MR_STATIC_CODE_ADDRESSES) || defined(PROFILE_CALLS) \
-	|| defined(DEBUG_LABELS) || defined(MR_INSERT_LABELS)
-  #define MR_NEED_INITIALIZATION_CODE
+	|| defined(PROFILE_TIME) || defined(DEBUG_LABELS)
+  #define MR_NEED_INITIALIZATION_AT_START
+#endif
+
+/*
+** MR_MAY_NEED_INITIALIZATION -- the module specific initialization code
+**				 may be needed, either at start or later.
+**
+** You need to run initialization code for grades without static
+** code addresses, for profiling, and any time you need to insert
+** labels into the label table.
+*/
+#ifdef MR_MAY_NEED_INITIALIZATION
+  #error "MR_MAY_NEED_INITIALIZATION should not be defined on the command line"
+#endif
+#if defined(MR_NEED_INITIALIZATION_AT_START) || defined(MR_INSERT_LABELS)
+  #define MR_MAY_NEED_INITIALIZATION
 #endif
 
 /*---------------------------------------------------------------------------*/
Index: runtime/mercury_goto.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_goto.h,v
retrieving revision 1.9
diff -u -u -r1.9 mercury_goto.h
--- mercury_goto.h	1998/05/16 07:28:15	1.9
+++ mercury_goto.h	1998/06/03 11:05:59
@@ -18,12 +18,12 @@
 #define entry(label) paste(_entry_,label)
 #define skip(label) paste(skip_,label)
 
-#ifdef MR_USE_STACK_LAYOUTS
+#if defined(MR_USE_STACK_LAYOUTS)
   #define MR_STACK_LAYOUT(label)        (Word *) (Word) \
 	&(paste(mercury_data__layout__,label))
 #else
-  #define MR_STACK_LAYOUT(label) (Word *) NULL
-#endif /* MR_USE_STACK_LAYOUTS */
+  #define MR_STACK_LAYOUT(label)	(Word *) NULL
+#endif
 
 
 /*
@@ -63,7 +63,6 @@
   #define make_entry(n, a, l)		/* nothing */
   #define make_entry_sl(n, a, l)	/* nothing */
 #endif
-
 
 #ifdef SPLIT_C_FILES
 #define MODULE_STATIC_OR_EXTERN extern
Index: runtime/mercury_stack_trace.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_trace.c,v
retrieving revision 1.6
diff -u -u -r1.6 mercury_stack_trace.c
--- mercury_stack_trace.c	1998/04/24 06:15:27	1.6
+++ mercury_stack_trace.c	1998/06/03 11:05:59
@@ -22,57 +22,73 @@
 	"erroneous",	/* 4 */
 	"",		/* 5 */
 	"det",		/* 6 */
-	"multidet",	/* 7 */
+	"multi",	/* 7 */
 	"",		/* 8 */
 	"",		/* 9 */
 	"cc_nondet",	/* 10 */
 	"",		/* 11 */
 	"",		/* 12 */
 	"",		/* 13 */
-	"cc_multidet"	/* 14 */
+	"cc_multi"	/* 14 */
 };
 
-	
+static	void	MR_dump_stack_record_init(void);
+static	void	MR_dump_stack_record_frame(FILE *fp, MR_Stack_Layout_Entry *);
+static	void	MR_dump_stack_record_flush(FILE *fp);
+static	void	MR_dump_stack_record_print(FILE *fp, MR_Stack_Layout_Entry *,
+			int);
 
-
 void
 MR_dump_stack(Code *success_pointer, Word *det_stack_pointer,
 		Word *current_frame)
 {
+#ifndef MR_STACK_TRACE
+	fprintf(stderr, "Stack dump not available in this grade.\n");
+#else
 	Label			*label;
-	MR_Live_Lval		location;
 	MR_Stack_Layout_Label	*layout;
 	MR_Stack_Layout_Entry	*entry_layout;
-	MR_Lval_Type		type;
-	int			number, determinism;
+	char			*result;
 
-#ifndef MR_STACK_TRACE
-	fprintf(stderr, "Stack dump not available in this grade.\n");
-#else
 	fprintf(stderr, "Stack dump follows:\n");
-
-	do {
-		label = lookup_label_addr(success_pointer);
-		if (label == NULL) {
-			fatal_error("internal label not found");
-		}
 
+	label = lookup_label_addr(success_pointer);
+	if (label == NULL) {
+		fprintf(stderr, "internal label not found\n");
+	} else {
 		layout = (MR_Stack_Layout_Label *) label->e_layout;
 		entry_layout = layout->MR_sll_entry;
-		
-		label = lookup_label_addr(
-			entry_layout->MR_sle_code_addr);
-		if (label == NULL) {
-			fatal_error("entry label not found");
+		result = MR_dump_stack_from_layout(stderr, entry_layout,
+			det_stack_pointer, current_frame);
+
+		if (result != NULL) {
+			fprintf(stderr, "%s\n", result);
 		}
+	}
+#endif
+}
+
+const char *
+MR_dump_stack_from_layout(FILE *fp, MR_Stack_Layout_Entry *entry_layout,
+		Word *det_stack_pointer, Word *current_frame)
+{
+	Label			*label;
+	MR_Live_Lval		location;
+	MR_Stack_Layout_Label	*layout;
+	MR_Lval_Type		type;
+	Code			*success_pointer;
+	int			number, determinism;
+
+	MR_dump_stack_record_init();
 
+	do {
 		location = entry_layout->MR_sle_succip_locn;
 		type = MR_LIVE_LVAL_TYPE(location);
 		number = MR_LIVE_LVAL_NUMBER(location);
 
 		determinism = entry_layout->MR_sle_detism;
 
-		/* 
+		/*
 		** A negative determinism means handwritten code has
 		** been reached.  Usually this means we have reached
 		** "global_success", so we should stop dumping the stack.
@@ -83,34 +99,95 @@
 		*/
 
 		if (determinism < 0) {
-			break;
+			MR_dump_stack_record_flush(fp);
+			return "reached procedure with no stack trace info";
 		}
+
+		MR_dump_stack_record_frame(fp, entry_layout);
 		if (MR_DETISM_DET_STACK(determinism)) {
-		        fprintf(stderr, "\t%s:%s/%ld (mode %ld, %s)\n",
-				entry_layout->MR_sle_def_module,
-				entry_layout->MR_sle_name,
-				(long) entry_layout->MR_sle_arity,
-		                (long) entry_layout->MR_sle_mode,
-				detism_names[entry_layout->MR_sle_detism]);
 			if (type == MR_LVAL_TYPE_STACKVAR) {
-				success_pointer = (Code *) field(0, 
+				success_pointer = (Code *) field(0,
 					det_stack_pointer, -number);
 			} else {
-				fatal_error("can only handle stackvars");
+				MR_dump_stack_record_flush(fp);
+				return "can only handle stackvars";
 			}
-			det_stack_pointer = det_stack_pointer - 
+			det_stack_pointer = det_stack_pointer -
 				entry_layout->MR_sle_stack_slots;
 		} else {
-		        fprintf(stderr, "\t%s:%s/%ld (mode %ld, %s)\n",
-		                entry_layout->MR_sle_def_module,
-		                entry_layout->MR_sle_name,
-		                (long) entry_layout->MR_sle_arity,
-		                (long) entry_layout->MR_sle_mode,
-				detism_names[entry_layout->MR_sle_detism]);
 			success_pointer = bt_succip(current_frame);
 			current_frame = bt_succfr(current_frame);
 		}
+
+		if (success_pointer == MR_stack_trace_bottom) {
+			MR_dump_stack_record_flush(fp);
+			return NULL;
+		}
+
+		label = lookup_label_addr(success_pointer);
+		if (label == NULL) {
+			MR_dump_stack_record_flush(fp);
+			return "reached label with no stack trace info";
+		}
+
+		layout = (MR_Stack_Layout_Label *) label->e_layout;
+		if (layout == NULL) {
+			MR_dump_stack_record_flush(fp);
+			return "reached label with no stack layout info";
+		}
+
+		entry_layout = layout->MR_sll_entry;
 	} while (TRUE);
-#endif /* MR_STACK_TRACE */
+
+	/*NOTREACHED*/
+	return "internal error in MR_dump_stack_from_layout";
 }
 
+static MR_Stack_Layout_Entry	*prev_entry_layout;
+static int			prev_entry_layout_count;
+
+static void
+MR_dump_stack_record_init(void)
+{
+	prev_entry_layout = NULL;
+	prev_entry_layout_count = 0;
+}
+
+static void
+MR_dump_stack_record_frame(FILE *fp, MR_Stack_Layout_Entry *entry_layout)
+{
+	if (entry_layout == prev_entry_layout) {
+		prev_entry_layout_count++;
+	} else {
+		MR_dump_stack_record_flush(fp);
+		prev_entry_layout = entry_layout;
+		prev_entry_layout_count = 1;
+	}
+}
+
+static void
+MR_dump_stack_record_flush(FILE *fp)
+{
+	if (prev_entry_layout != NULL) {
+		MR_dump_stack_record_print(fp, prev_entry_layout,
+			prev_entry_layout_count);
+	}
+}
+
+static void
+MR_dump_stack_record_print(FILE *fp, MR_Stack_Layout_Entry *entry_layout,
+	int count)
+{
+	fprintf(fp, "\t%s:%s/%ld (mode %ld, %s)",
+		entry_layout->MR_sle_def_module,
+		entry_layout->MR_sle_name,
+		(long) entry_layout->MR_sle_arity,
+		(long) entry_layout->MR_sle_mode,
+		detism_names[entry_layout->MR_sle_detism]);
+
+	if (count > 1) {
+		fprintf(fp, " * %d\n", count);
+	} else {
+		putc('\n', fp);
+	}
+}
Index: runtime/mercury_stack_trace.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_trace.h,v
retrieving revision 1.4
diff -u -u -r1.4 mercury_stack_trace.h
--- mercury_stack_trace.h	1998/05/19 15:16:56	1.4
+++ mercury_stack_trace.h	1998/06/03 11:05:59
@@ -7,6 +7,8 @@
 #ifndef MERCURY_STACK_TRACE_H
 #define MERCURY_STACK_TRACE_H
 
+#include "mercury_stack_layout.h"
+
 /*
 ** mercury_stack_trace.h -
 **	Definitions for use by the stack tracing.
@@ -21,7 +23,7 @@
 ** 	stack.
 ** 	NOTE: MR_dump_stack will assume that the succip is for the
 ** 	topmost stack frame.  If you call MR_dump_stack from some
-** 	pragma c_code that may not be the case.
+** 	pragma c_code, that may not be the case.
 ** 	Due to some optimizations (or lack thereof) the MR_dump_stack call 
 ** 	may end up inside code that has a stack frame allocated, but
 ** 	that has a succip for the previous stack frame.
@@ -34,8 +36,31 @@
 ** 	it would probably be best to make an impure predicate defined
 ** 	using `:- external'.
 */
+
+extern	void		MR_dump_stack(Code *success_pointer,
+				Word *det_stack_pointer,
+				Word *current_frame);
+
+/*
+** MR_dump_stack_from_layout:
+**	This function does the same job and makes the same assumptions
+**	as MR_dump_stack, but instead of the succip, it takes the entry
+**	layout of the current procedure as input. It also takes a paramater
+**	that tells it where to put the stack dump. If the entire stack
+**	was printed successfully, the return value is NULL; otherwise,
+**	it is a string indicating why the dump was cut short.
+*/
+
+extern	const char	*MR_dump_stack_from_layout(FILE *fp,
+				MR_Stack_Layout_Entry *entry_layout,
+				Word *det_stack_pointer, Word *current_frame);
+
+/*
+** MR_stack_trace_bottom should be set to the address of global_success,
+** the label main/2 goes to on success. Stack dumps terminate when they
+** reach a stack frame whose saved succip slot contains this address.
+*/
 
-extern void MR_dump_stack(Code *success_pointer, Word *det_stack_pointer,
-		Word *current_frame);
+Code	*MR_stack_trace_bottom;
 
 #endif /* MERCURY_STACK_TRACE_H */
Index: runtime/mercury_stacks.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stacks.h,v
retrieving revision 1.4
diff -u -u -r1.4 mercury_stacks.h
--- mercury_stacks.h	1998/03/16 12:23:38	1.4
+++ mercury_stacks.h	1998/06/03 11:05:59
@@ -18,6 +18,7 @@
 /* DEFINITIONS FOR MANIPULATING THE DET STACK */
 
 #define	detstackvar(n)	(MR_sp[-n])
+#define	saved_detstackvar(save_area, n)	(MR_saved_sp(save_area)[-n])
 
 #define	incr_sp_push_msg(n, msg)				\
 			(					\
@@ -99,6 +100,8 @@
 #define	cursuccip	bt_succip(MR_curfr)
 #define	cursuccfr	bt_succfr(MR_curfr)
 #define	framevar(n)	bt_var(MR_curfr,n)
+
+#define	saved_framevar(save_area, n)	bt_var(MR_saved_curfr(save_area), n)
 
 /* DEFINITIONS FOR MANIPULATING THE NONDET STACK */
 
Index: runtime/mercury_trace_internal.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace_internal.c,v
retrieving revision 1.3
diff -u -u -r1.3 mercury_trace_internal.c
--- mercury_trace_internal.c	1998/05/25 21:46:40	1.3
+++ mercury_trace_internal.c	1998/06/03 11:06:00
@@ -21,29 +21,38 @@
 #define	MR_MAX_SPY_POINTS	100
 #define	MR_LOG10_MAX_SPY_POINTS	20
 
+#define	MR_MAX_LINE_LEN		256
+
 typedef struct {
 	bool	enabled;
 	char	module_name[MR_NAME_LEN];
 	char	pred_name[MR_NAME_LEN];
 } MR_spy_point;
 
+typedef enum {
+	KEEP_INTERACTING,
+	STOP_INTERACTING
+} MR_next;
+
 static	MR_spy_point	MR_spy_points[MR_MAX_SPY_POINTS];
 static	int		MR_next_spy_point = 0;
 
+static	MR_next	MR_trace_debug_cmd(MR_trace_cmd_info *cmd,
+			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(const char *name,
 			const MR_Stack_Layout_Var *var, Word *type_params);
-
-static	void	MR_add_spy_point(void);
-static	void	MR_list_spy_points(void);
-static	void	MR_change_spy_point_status(bool status);
-
-static	int	MR_trace_skip_spaces(int c);
-static	void	MR_trace_discard_to_eol(int c);
-static	int	MR_trace_get_word(int *c, char word[], int len);
 static	void	MR_trace_help(void);
 
+static	bool	MR_trace_is_number(char *word, int *value);
+static	bool	MR_trace_is_number_prefix(char *word, char **suffix,
+			int *value);
+static	int	MR_trace_break_into_words(char line[], char *words[]);
+static	int	MR_trace_getline(FILE *file, char line[], int line_max);
+
 static	void	MR_trace_print_port(MR_trace_port port);
 static	void	MR_trace_print_detism(Word detism);
 
@@ -67,168 +76,322 @@
 	saved_depth = MR_trace_call_depth;
 	saved_event = MR_trace_event_number;
 
-	for (;;) {
-		printf("mtrace> ");
+	while (MR_trace_debug_cmd(cmd, layout, port, seqno, depth, path)
+			== KEEP_INTERACTING) {
+		; /* all the work is done in MR_trace_debug_cmd */
+	}
 
-		count = 1;
-		count_given = FALSE;
-		cmd->MR_trace_print_intermediate = FALSE;
+	MR_trace_call_seqno = saved_seqno;
+	MR_trace_call_depth = saved_depth;
+	MR_trace_event_number = saved_event;
+}
+
+static MR_next
+MR_trace_debug_cmd(MR_trace_cmd_info *cmd, const MR_Stack_Layout_Label *layout,
+	MR_trace_port port, int seqno, int depth, const char *path)
+{
+	char	line[MR_MAX_LINE_LEN];
+	char	count_buf[MR_MAX_LINE_LEN];
+	char	*raw_words[MR_MAX_LINE_LEN/2+1];
+	char	**words;
+	char	raw_word_count;
+	char	word_count;
+	char	*s;
+	int	i, n;
+
+	printf("mtrace> ");
+
+	if (MR_trace_getline(stdin, line, MR_MAX_LINE_LEN) == 0) {
+		/*
+		** We got a line without even a newline character,
+		** which must mean that the user typed EOF.
+		** We arrange things so we don't have to treat this case
+		** specially in the command interpreter below.
+		*/
+
+		(void) strcpy(line, "a\n");
+	}
 
-		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();
+	/*
+	** Handle a possible number prefix on the first word on the line,
+	** separating it out into a word on its own.
+	*/
+
+	raw_word_count = MR_trace_break_into_words(line, raw_words+1);
+
+	if (raw_word_count > 0 && isdigit(*raw_words[1])) {
+		i = 0;
+		s = raw_words[1];
+		while (isdigit(*s)) {
+			count_buf[i] = *s;
+			i++;
+			s++;
+		}
+
+		count_buf[i] = '\0';
+
+		if (*s == '\0') {
+			/* all of the first word constitutes a number */
+			/* exchange it with the command, if it exists */
+
+			if (raw_word_count > 1) {
+				s = raw_words[1];
+				raw_words[1] = raw_words[2];
+				raw_words[2] = s;
 			}
 
-			c = MR_trace_skip_spaces(c);
+			words = raw_words+1;
+			word_count = raw_word_count;
+		} else {
+			/* only part of the first word constitutes a number */
+			/* put it in an extra word at the start */
+
+			raw_words[0] = count_buf;
+			raw_words[1] = s;
+			words = raw_words;
+			word_count = raw_word_count + 1;
 		}
+	} else {
+		words = raw_words + 1;
+		word_count = raw_word_count;
+	}
 
-		switch (c) {
-			case 'S':
-				cmd->MR_trace_print_intermediate = TRUE;
-				/* fall through */
+	/*
+	** If the first word is a number, try to exchange it
+	** with the command word, to put the command word first.
+	*/
 
-			case 's':
-			case '\n':
-				cmd->MR_trace_cmd = MR_CMD_GOTO;
-				cmd->MR_trace_stop_event =
-					MR_trace_event_number + count;
-				MR_trace_discard_to_eol(c);
-				break;
-
-			case 'G':
-				cmd->MR_trace_print_intermediate = TRUE;
-				/* fall through */
-
-			case 'g':
-				if (! count_given) {
-					MR_trace_discard_to_eol(c);
-					printf("mtrace: no count given\n");
-					continue;
-				}
+	if (word_count > 1 && MR_trace_is_number(words[0], &n)
+			&& ! MR_trace_is_number(words[1], &n)) {
+		s = words[0];
+		words[0] = words[1];
+		words[1] = s;
+	}
+
+	/*
+	** At this point, the first word_count members of the words
+	** array contain the command.
+	*/
 
+	cmd->MR_trace_print_intermediate = FALSE;
+
+	if (word_count == 0) {
+		cmd->MR_trace_cmd = MR_CMD_GOTO;
+		cmd->MR_trace_print_intermediate = FALSE;
+		cmd->MR_trace_stop_event = MR_trace_event_number + 1;
+		return STOP_INTERACTING;
+	} else if (MR_trace_is_number(words[0], &n)) {
+		if (word_count == 1) {
+			cmd->MR_trace_cmd = MR_CMD_GOTO;
+			cmd->MR_trace_print_intermediate = FALSE;
+			cmd->MR_trace_stop_event = MR_trace_event_number + n;
+			return STOP_INTERACTING;
+		} else {
+			printf("One of the first two words "
+				"must be a command.\n");
+		}
+	} else if (streq(words[0], "S") || streq(words[0], "s")) {
+		if (word_count == 1) {
+			cmd->MR_trace_cmd = MR_CMD_GOTO;
+			cmd->MR_trace_print_intermediate = streq(words[0], "S");
+			cmd->MR_trace_stop_event = MR_trace_event_number + 1;
+			return STOP_INTERACTING;
+		} else if (word_count == 2
+				&& MR_trace_is_number(words[1], &n)) {
+			cmd->MR_trace_cmd = MR_CMD_GOTO;
+			cmd->MR_trace_print_intermediate = streq(words[0], "S");
+			cmd->MR_trace_stop_event = MR_trace_event_number + n;
+			return STOP_INTERACTING;
+		} else {
+			printf("This command expects at most one argument,\n"
+				"which must be a number.\n");
+		}
+	} else if (streq(words[0], "g") || streq(words[0], "G")) {
+		if (word_count == 2 && MR_trace_is_number(words[1], &n)) {
+			if (MR_trace_event_number < n) {
 				cmd->MR_trace_cmd = MR_CMD_GOTO;
-				cmd->MR_trace_stop_event = count;
-				MR_trace_discard_to_eol(c);
-				break;
-
-			case 'F':
-				cmd->MR_trace_print_intermediate = TRUE;
-				/* fall through */
-
-			case 'f':
-				if (MR_port_is_final(port)) {
-					MR_trace_discard_to_eol(c);
-					printf("mtrace: this port is "
-						"already final\n");
-					continue;
+				cmd->MR_trace_print_intermediate =
+					streq(words[0], "G");
+				cmd->MR_trace_stop_event = n;
+				return STOP_INTERACTING;
+			} else {
+				printf("The debugger cannot go "
+					"to a past event.\n");
+			}
+		} else {
+			printf("This command expects exactly one argument,\n");
+			printf("which must be a number.\n");
+		}
+	} else if (streq(words[0], "f") || streq(words[0], "F")) {
+		if (word_count == 1) {
+			if (MR_port_is_final(port)) {
+				printf("This command is a no-op "
+					"from this port.\n");
+			} else {
+				cmd->MR_trace_cmd = MR_CMD_FINISH;
+				cmd->MR_trace_print_intermediate =
+					streq(words[0], "F");
+				cmd->MR_trace_stop_seqno = seqno;
+				return STOP_INTERACTING;
+			}
+		} else {
+			printf("This command expects no argument.\n");
+		}
+	} else if (streq(words[0], "c") || streq(words[0], "C")) {
+		if (word_count == 1) {
+			cmd->MR_trace_cmd = MR_CMD_TO_END;
+			cmd->MR_trace_print_intermediate =
+				streq(words[0], "C");
+			return STOP_INTERACTING;
+		} else {
+			printf("This command expects no argument.\n");
+		}
+	} else if (streq(words[0], "r") || streq(words[0], "R")) {
+		if (word_count == 1) {
+			cmd->MR_trace_cmd = MR_CMD_RESUME_FORWARD;
+			cmd->MR_trace_print_intermediate =
+				streq(words[0], "R");
+			return STOP_INTERACTING;
+		} else {
+			printf("This command expects no argument.\n");
+		}
+	} else if (streq(words[0], "p")) {
+		if (word_count == 1) {
+			MR_trace_browse((int)
+				layout->MR_sll_var_count,
+				&layout->MR_sll_var_info);
+		} else {
+			printf("This command expects no argument.\n");
+		}
+	} else if (streq(words[0], "d")) {
+		if (word_count == 1) {
+			const char	*result;
+
+			do_init_modules();
+			result = MR_dump_stack_from_layout(stdout,
+					layout->MR_sll_entry, sp, maxfr);
+			if (result != NULL) {
+				printf("%s\n", result);
+			}
+		} else {
+			printf("This command expects no argument.\n");
+		}
+	} else if (streq(words[0], "b")) {
+		if (word_count != 3) {
+			printf("This command expects two arguments,\n");
+			printf("a module name and a predicate name.\n");
+		} else {
+			if (MR_next_spy_point >= MR_MAX_SPY_POINTS) {
+				printf("There is no room "
+					"for any more spy points.\n");
+			} else {
+				printf("%2d: %s %s:%s\n", MR_next_spy_point,
+					"+", words[1], words[2]);
+				strcpy(MR_spy_points[MR_next_spy_point]
+					.module_name, words[1]);
+				strcpy(MR_spy_points[MR_next_spy_point]
+					.pred_name, words[2]);
+				MR_spy_points[MR_next_spy_point].enabled
+					= TRUE;
+				MR_next_spy_point++;
+			}
+		}
+	} else if (streq(words[0], "?")) {
+		for (i = 0; i < MR_next_spy_point; i++) {
+			printf("%2d: %s %s:%s\n", i,
+				MR_spy_points[i].enabled ? "+" : "-",
+				MR_spy_points[i].module_name,
+				MR_spy_points[i].pred_name);
+		}
+	} else if (streq(words[0], "+")) {
+		if (word_count == 2) {
+			if (MR_trace_is_number(words[1], &n)) {
+				if (0 <= n && n < MR_next_spy_point) {
+					MR_spy_points[n].enabled = TRUE;
+					printf("%2d: %s %s:%s\n", n,
+						"+",
+						MR_spy_points[n].module_name,
+						MR_spy_points[n].pred_name);
 				} else {
-					cmd->MR_trace_cmd = MR_CMD_FINISH;
-					cmd->MR_trace_stop_seqno = seqno;
+					printf("Break point #%d "
+						"does not exist.\n", n);
 				}
-
-				MR_trace_discard_to_eol(c);
-				break;
-
-			case 'C':
-				cmd->MR_trace_print_intermediate = TRUE;
-				/* fall through */
-
-			case 'c':
-				if (count_given)
-					printf("mtrace: count ignored\n");
-
-				cmd->MR_trace_cmd = MR_CMD_TO_END;
-				MR_trace_discard_to_eol(c);
-				break;
-
-			case 'p':
-				if (count_given)
-					printf("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 'r':
-				if (count_given)
-					printf("mtrace: count ignored\n");
-
-				cmd->MR_trace_cmd = MR_CMD_RESUME_FORWARD;
-				MR_trace_discard_to_eol(c);
-				break;
-
-			case 'b':
-				if (count_given)
-					printf("mtrace: count ignored\n");
-
-				MR_add_spy_point();
-				continue;
-
-			case '?':
-				if (count_given)
-					printf("mtrace: count ignored\n");
-
-				MR_list_spy_points();
-				continue;
-
-			case '+':
-				if (count_given)
-					printf("mtrace: count ignored\n");
-
-				MR_change_spy_point_status(TRUE);
-				continue;
-
-			case '-':
-				if (count_given)
-					printf("mtrace: count ignored\n");
-
-				MR_change_spy_point_status(FALSE);
-				continue;
-
-			case 'a':
-			case EOF:
-				MR_trace_discard_to_eol(c);
-				printf("mtrace: are you sure"
-						" you want to abort? ");
-
-				c = MR_trace_skip_spaces(' ');
-				if (c == 'y' || c == EOF) {
-					/*
-					** We reset MR_trace_event_number
-					** that fatal_error will not
-					** print the last trace event number
-					** (since in this case it is not
-					** meaningful).
-					*/
-
-					MR_trace_event_number = 0;
-					fatal_error("aborting the execution "
-						"on user request");
+			} else if (streq(words[1], "*")) {
+				for (i = 0; i < MR_next_spy_point; i++) {
+					MR_spy_points[i].enabled = TRUE;
+					printf("%2d: %s %s:%s\n", i,
+						"+",
+						MR_spy_points[i].module_name,
+						MR_spy_points[i].pred_name);
 				}
-
-				MR_trace_discard_to_eol(c);
-				continue;
-
-			default:
-				MR_trace_discard_to_eol(c);
-				MR_trace_help();
-				continue;
+			} else {
+				printf("The argument of this command must be "
+					"a break point number or a `*'.\n");
+			}
+		} else {
+			printf("This command expects one argument,\n");
+			printf("which must be a break point number "
+				"or a `*'.\n");
+		}
+	} else if (streq(words[0], "-")) {
+		if (word_count == 2) {
+			if (MR_trace_is_number(words[1], &n)) {
+				if (0 <= n && n < MR_next_spy_point) {
+					MR_spy_points[n].enabled = FALSE;
+					printf("%2d: %s %s:%s\n", n,
+						"-",
+						MR_spy_points[n].module_name,
+						MR_spy_points[n].pred_name);
+				} else {
+					printf("Break point #%d "
+						"does not exist.\n", n);
+				}
+			} else if (streq(words[1], "*")) {
+				for (i = 0; i < MR_next_spy_point; i++) {
+					MR_spy_points[i].enabled = FALSE;
+					printf("%2d: %s %s:%s\n", i,
+						"-",
+						MR_spy_points[i].module_name,
+						MR_spy_points[i].pred_name);
+				}
+			} else {
+				printf("The argument of this command must be "
+					"a break point number or a `*'.\n");
+			}
+		} else {
+			printf("This command expects one argument,\n");
+			printf("which must be a break point number "
+				"or a `*'.\n");
 		}
+	} else if (streq(words[0], "h")) {
+		if (word_count != 1) {
+			printf("This command expects no argument.\n");
+		}
+		MR_trace_help();
+	} else if (streq(words[0], "a")) {
+		if (word_count == 1) {
+			printf("mtrace: are you sure you want to abort? ");
+			if (MR_trace_getline(stdin, line, MR_MAX_LINE_LEN)
+					== 0) {
+				/* This means the user input EOF. */
+				exit(0);
+			} else {
+				for (i = 0; isspace(line[i]); i++)
+					;
 
-		break;
+				if (line[i] == 'y' || line[i] == 'Y') {
+					exit(0);
+				}
+			}
+		} else {
+			printf("This command expects no argument.\n");
+		}
+	} else {
+		printf("Command not recognized. "
+			"Give the command `h' for help.\n");
 	}
 
-	MR_trace_call_seqno = saved_seqno;
-	MR_trace_call_depth = saved_depth;
-	MR_trace_event_number = saved_event;
+	return KEEP_INTERACTING;
 }
 
 static void
@@ -344,77 +507,6 @@
 	printf("\n");
 }
 
-static void
-MR_add_spy_point(void)
-{
-	int	c;
-
-	c = getchar();
-
-	if (MR_next_spy_point >= MR_MAX_SPY_POINTS) {
-		MR_trace_discard_to_eol(c);
-		printf("mtrace: no room for more spy points\n");
-		return;
-	}
-
-	if (MR_trace_get_word(&c, MR_spy_points[MR_next_spy_point].module_name,
-			MR_NAME_LEN)
-	&& MR_trace_get_word(&c, MR_spy_points[MR_next_spy_point].pred_name,
-			MR_NAME_LEN)) {
-		MR_trace_discard_to_eol(c);
-		MR_spy_points[MR_next_spy_point].enabled = TRUE;
-		MR_next_spy_point++;
-	}
-	else {
-		printf("usage: \"b module_name pred_name\"\n");
-	}
-}
-
-static void
-MR_list_spy_points(void)
-{
-	int	i;
-
-	for (i = 0; i < MR_next_spy_point; i++) {
-		printf("%2d: %s %s:%s\n", i,
-			MR_spy_points[i].enabled? "+": "-",
-			MR_spy_points[i].module_name,
-			MR_spy_points[i].pred_name);
-	}
-
-	MR_trace_discard_to_eol(getchar());
-}
-
-static void
-MR_change_spy_point_status(bool status)
-{
-	char	buf[MR_LOG10_MAX_SPY_POINTS];
-	int	c;
-	int	i;
-
-	c = getchar();
-
-	if (MR_trace_get_word(&c, buf, MR_LOG10_MAX_SPY_POINTS)) {
-		if (sscanf(buf, "%d", &i) == 1) {
-			if (0 <= i && i < MR_next_spy_point) {
-				MR_spy_points[i].enabled = status;
-			} else {
-				printf("spy point #%d does not exist\n", i);
-			}
-		} else if (strcmp(buf, "*") == 0) {
-			for (i = 0; i < MR_next_spy_point; i++) {
-				MR_spy_points[i].enabled = status;
-			}
-		} else {
-			printf("garbled spy point number\n");
-		}
-	} else {
-		printf("missing spy point number\n");
-	}
-
-	MR_trace_discard_to_eol(c);
-}
-
 bool
 MR_event_matches_spy_point(const MR_Stack_Layout_Label *layout)
 {
@@ -436,47 +528,105 @@
 	return FALSE;
 }
 
-static int
-MR_trace_skip_spaces(int c)
+/*
+** Is the string pointed to by word an integer?
+** If yes, return its value in *value.
+*/
+
+static bool
+MR_trace_is_number(char *word, int *value)
 {
-	while (c != EOF && c != '\n' && isspace(c))
-		c = getchar();
+	if (isdigit(*word)) {
+		*value = *word - '0';
+		word++;
+		while (isdigit(*word)) {
+			*value = (*value * 10) + *word - '0';
+			word++;
+		}
 
-	return c;
-}
+		if (*word == '\0') {
+			return TRUE;
+		}
+	}
 
-static void
-MR_trace_discard_to_eol(int c)
-{
-	while (c != EOF && c != '\n')
-		c = getchar();
+	return FALSE;
 }
 
+/*
+** Given a text line, break it up into words composed of non-space characters
+** separated by space characters. Make each word a NULL-terminated string
+** (overwriting some spaces in the line array in the process), return pointers
+** to them in the words array, and return the number of words in the return
+** value of the function.
+**
+** This function assumes that the words array is as long as necessary.
+** This can be (and is) ensured by making the words array have one element
+** for every two characters in the line array (since you need at least one
+** non-space and one space or newline character per word).
+**
+** This function also assumes that line[] is guaranteed to have a white space
+** character (which will usually be a newline) just before the null character.
+*/
+
 static int
-MR_trace_get_word(int *cptr, char word[], int len)
+MR_trace_break_into_words(char line[], char *words[])
 {
-	int	c;
-	int	i;
+	int	token_number;
+	int	char_pos;
+	int	int_val;
 
-	c = MR_trace_skip_spaces(*cptr);
+	token_number = 0;
+	char_pos = 0;
 
-	i = 0;
-	while (c != EOF && (isalnum(c) || c == '_')) {
-		if (i < len) {
-			word[i++] = c;
+	/* each iteration of this loop processes one token, or end of line */
+	for (;;) {
+		while (line[char_pos] != '\0' && isspace(line[char_pos])) {
+			char_pos++;
+		}
+
+		if (line[char_pos] == '\0') {
+			return token_number;
+		}
+
+		words[token_number] = line + char_pos;
+		while (line[char_pos] != '\0' && !isspace(line[char_pos])) {
+			char_pos++;
 		}
 
-		c = getchar();
+		line[char_pos] = '\0';
+		char_pos++;
+		token_number++;
 	}
+}
 
-	*cptr = c;
+/*
+**	Read a line from a file. If the line does not fit in the array,
+**	read the whole line anyway but store only the first part.
+**	If the last line ends without a newline, insert it.
+**	Return the length of the (possibly truncated) line.
+**	This will be zero only if getline is called at EOF;
+**	it will be one only if line contains a single newline;
+**	otherwise it will contain a newline terminated string.
+*/
 
-	if (i > 0) {
-		word[i] = '\0';
-		return TRUE;
+static int
+MR_trace_getline(FILE *file, char line[], int line_max)
+{
+	int	c, i;
+
+	i = 0;
+	while ((c = getc(file)) != EOF && c != '\n') {
+		if (i < line_max-1) {
+			line[i++] = c;
+		}
 	}
 
-	return FALSE;
+	if (c == '\n' || i > 0) {
+		line[i++] = '\n';
+	}
+
+	line[i] = '\0';
+	return i;
 }
 
 void
Index: runtime/mercury_trace_util.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace_util.c,v
retrieving revision 1.2
diff -u -u -r1.2 mercury_trace_util.c
--- mercury_trace_util.c	1998/05/25 21:46:41	1.2
+++ mercury_trace_util.c	1998/06/03 11:06:00
@@ -171,18 +171,14 @@
 		case MR_LVAL_TYPE_STACKVAR:
 			if (MR_trace_print_locn)
 				printf("stackvar%d", locn_num);
-			/* XXX BUG! detstackvar() will give wrong results
-			   because MR_sp is not valid */
-			value = detstackvar(locn_num);
+			value = saved_detstackvar(MR_saved_regs, locn_num);
 			*succeeded = TRUE;
 			break;
 
 		case MR_LVAL_TYPE_FRAMEVAR:
 			if (MR_trace_print_locn)
 				printf("framevar%d", locn_num);
-			/* XXX BUG! detstackvar() will give wrong results
-			   because MR_currfr is not valid */
-			value = framevar(locn_num);
+			value = saved_framevar(MR_saved_regs, locn_num);
 			*succeeded = TRUE;
 			break;
 
Index: runtime/mercury_wrapper.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_wrapper.c,v
retrieving revision 1.11
diff -u -u -r1.11 mercury_wrapper.c
--- mercury_wrapper.c	1998/05/16 07:28:38	1.11
+++ mercury_wrapper.c	1998/06/03 11:06:00
@@ -9,7 +9,7 @@
 */
 
 /*
-** file: wrapper.mod
+** file: mercury_wrapper.c
 ** main authors: zs, fjh
 **
 **	This file contains the startup and termination entry points
@@ -236,8 +236,7 @@
 	saved_trace_enabled = MR_trace_enabled;
 	MR_trace_enabled = FALSE;
 
-#if (defined(USE_GCC_NONLOCAL_GOTOS) && !defined(USE_ASM_LABELS)) || \
-		defined(PROFILE_CALLS) || defined(PROFILE_TIME)
+#ifdef MR_NEED_INITIALIZATION_AT_START
 	do_init_modules();
 #endif
 
@@ -917,6 +916,8 @@
 	if (program_entry_point == NULL) {
 		fatal_error("no program entry point supplied");
 	}
+
+	MR_stack_trace_bottom = LABEL(global_success);
 
 #ifdef  PROFILE_TIME
 	if (MR_profiling) MR_prof_turn_on_time_profiling();
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/diff
cvs diff: Diffing scripts
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
cvs diff: Diffing tests/general
cvs diff: Diffing tests/hard_coded
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/term
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
cvs diff: Diffing trial
cvs diff: Diffing util
Index: util/mkinit.c
===================================================================
RCS file: /home/mercury1/repository/mercury/util/mkinit.c,v
retrieving revision 1.32
diff -u -u -r1.32 mkinit.c
--- mkinit.c	1998/06/04 11:50:11	1.32
+++ mkinit.c	1998/06/05 09:54:00
@@ -178,12 +178,6 @@
 	"}\n"
 	;
 
-
-static const char if_need_to_init[] = 
-	"#if defined(MR_NEED_INITIALIZATION_CODE)\n\n"
-	;
-
-
 /* --- function prototypes --- */
 static	void parse_options(int argc, char *argv[]);
 static	void usage(void);
@@ -315,8 +309,6 @@
 {
 	int filenum;
 
-	fputs(if_need_to_init, stdout);
-
 	fputs("static void init_modules_0(void)\n", stdout);
 	fputs("{\n", stdout);
 
@@ -324,8 +316,7 @@
 		process_file(files[filenum]);
 	}
 
-	fputs("}\n", stdout);
-	fputs("\n#endif\n\n", stdout);
+	fputs("}\n\n", stdout);
 }
 
 static void 
@@ -336,12 +327,9 @@
 	fputs("static void init_modules(void)\n", stdout);
 	fputs("{\n", stdout);
 
-	fputs(if_need_to_init, stdout);
-
 	for (i = 0; i <= num_modules; i++) {
 		printf("\tinit_modules_%d();\n", i);
 	}
-	fputs("#endif\n", stdout);
 
 	fputs("}\n", stdout);
 }



More information about the developers mailing list