for review: uplevel printing

Zoltan Somogyi zs at cs.mu.OZ.AU
Wed Jun 17 14:33:06 AEST 1998


Tyson, please review this.

Estimated hours taken: 20

Allow the debugger to print the values of variables in ancestors
of the current call. This requires knowledge about which named variables
are live at call return sites. Providing this information properly required
fixing the interaction of execution tracing and accurate garbage collection.

compiler/globals.m:
	Introduce a new trace level, so that there are now four:
	none, interface, interface_ports (corresponding to the existing
	three levels) and the new level interface_ports_returns,
	each of which requires all the information required by lower
	levels.

	Make the trace level abstract, since in the future we may want to
	introduce trace levels for new combinations, e.g. interfaces and
	returns but not internal ports. Introduce the necessary new
	predicates.

compiler/continuation_info.m:
	Redefine internal_label_info to allow us to record separate info about
	the sets of vars needed at (a) internal ports of execution tracing
	and at (b) call return points for accurate gc or (now) uplevel
	printing during execution tracing. Neither is a subset of the other,
	and they need to be treated differently.

compiler/mercury_compile.m:
	Gather information about vars at return labels if the trace level
	requires uplevel printing capability, even if agc is off.

compiler/stack_layout.m:
	Fix the handling of labels which are needed both by agc and by
	execution tracing. If information at a return label is needed only
	by uplevel printing in execution tracing and not by agc, then
	discard all info about lvals which do not hold named variables
	or their typeinfos (in fact we keep all typeinfos at the moment).
	If a label is both the label of a port and a return label, we
	include in the layout structure the union of the information
	recorded for the two roles.

	Sort the var_info vector before using it to generate layout
	structures in an attempt to make llds_common more effective
	and to make lists of variables printed by the debugger look better.

	Record a distinguished value when there is no info about the vars
	live at a label, rather than (incorrectly) recording that there
	are no live variables. Before up-level printing, the lie was harmless;
	now it isn't.

	Remove the label number from return label layouts, since the tracer
	isn't expecting it. It used to be included for debugging purposes 
	if the label was for agc, but it is possible for a label to be needed
	both for agc and for execution tracing. If Tyson finds he needs the
	label number, it can be easily turned back on for all label layouts.

compiler/code_info.m:
	Conform to the new definition of internal_label_info.

	Rename an internal pred for clarity.

	Rename some bool parameter to correctly reflect their new meaning.

compiler/*.m:
	Trivial changes, mostly due to making trace_level an abstract type.

runtime/mercury_stack_layout.h:
	Remove the label number from return label layouts, since the tracer
	isn't expecting it.

runtime/mercury_stack_trace.[ch]:
	Add a new function that returns the label layout structure at the
	Nth ancestor return continuation, together with the values of
	sp and curfr at that point. This required changing MR_stack_walk_step
	to step from an entry layout only to the return label layout.

runtime/mercury_stacks.h:
	Add macros that let us access detstackvars and framevars based on
	these synthesized values of sp and curfr.

runtime/mercury_trace_util.[ch]:
	Generalize several functions to allow them to use synthesized
	(as opposed to saved) values of sp and curfr in looking up values.

	Retain functions with the original names and signatures that call
	the new, general versions with the necessary additional parameters.

runtime/mercury_trace_internal.c:
	Add a new command that sets the "ancestor level". For example,
	"l 2" sets it to 2, which means that the command "v" and "p" will
	refer to the grandparent of the current call. The ancestor level
	persists while the debugger is at the current event; after that
	it is reset to 0.

	The implementation involves calling the new function in
	mercury_stack_trace.c and the generalized functions in
	mercury_trace_util.c.

	Also add a deliberately undocumented extra command, X, which
	prints the stack pointers.

NEWS:
	Add a reminder about removing the X command before release.

The updates of the debugger test files will come after I bootcheck
this.

Zoltan.

cvs diff: Diffing .
Index: NEWS
===================================================================
RCS file: /home/mercury1/repository/mercury/NEWS,v
retrieving revision 1.104
diff -u -u -r1.104 NEWS
--- NEWS	1998/05/30 15:22:19	1.104
+++ NEWS	1998/06/17 06:24:08
@@ -424,3 +424,4 @@
 
 * Numerous bug fixes.
 
+* XXX remove the X debugger command
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/code_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_gen.m,v
retrieving revision 1.51
diff -u -u -r1.51 code_gen.m
--- code_gen.m	1998/06/09 02:12:05	1.51
+++ code_gen.m	1998/06/16 06:09:55
@@ -212,9 +212,7 @@
 		% generate code for the procedure
 	globals__get_trace_level(Globals, TraceLevel),
 	code_util__make_proc_label(ModuleInfo, PredId, ProcId, ProcLabel),
-	(
-		( TraceLevel = interface ; TraceLevel = full )
-	->
+	( trace_level_trace_interface(TraceLevel, yes) ->
 		trace__setup(TraceLevel, CodeInfo0, CodeInfo1)
 	;
 		CodeInfo1 = CodeInfo0
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.222
diff -u -u -r1.222 code_info.m
--- code_info.m	1998/06/09 02:12:08	1.222
+++ code_info.m	1998/06/16 04:46:57
@@ -708,9 +708,9 @@
 :- 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,
+:- pred code_info__add_trace_layout_for_label(label, layout_label_info,
 	code_info, code_info).
-:- mode code_info__add_layout_for_label(in, in, in, out) is det.
+:- mode code_info__add_trace_layout_for_label(in, in, in, out) is det.
 
 %---------------------------------------------------------------------------%
 
@@ -996,14 +996,22 @@
 code_info__succip_is_used -->
 	code_info__set_succip_used(yes).
 
-code_info__add_layout_for_label(Label, LayoutInfo) -->
+code_info__add_trace_layout_for_label(Label, LayoutInfo) -->
 	code_info__get_layout_info(Internals0),
-	( { map__contains(Internals0, Label) } ->
-		{ error("adding layout for already known label") }
+	{ map__search(Internals0, Label, Internal0) ->
+		Internal0 = internal_layout_info(Exec0, Agc),
+		( Exec0 = no ->
+			true
+		;
+			error("adding trace layout for already known label")
+		),
+		Internal = internal_layout_info(yes(LayoutInfo), Agc),
+		map__set(Internals0, Label, Internal, Internals)
 	;
-		{ map__det_insert(Internals0, Label, LayoutInfo, Internals) },
-		code_info__set_layout_info(Internals)
-	).
+		Internal = internal_layout_info(yes(LayoutInfo), no),
+		map__det_insert(Internals0, Label, Internal, Internals)
+	},
+	code_info__set_layout_info(Internals).
 
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
@@ -2868,7 +2876,17 @@
 	{ set__to_sorted_list(LiveVals1, LiveVals2) },
 	code_info__get_globals(Globals),
 	{ globals__get_gc_method(Globals, GC_Method) },
-	code_info__livevals_to_livelvals(LiveVals2, GC_Method, 
+	{ globals__get_trace_level(Globals, TraceLevel) },
+	{
+		( GC_Method = accurate
+		; trace_level_trace_returns(TraceLevel, yes)
+		)
+	->
+		NeedVarInfo = yes
+	;
+		NeedVarInfo = no
+	},
+	code_info__livevals_to_livelvals(LiveVals2, NeedVarInfo, 
 		AfterCallInstMap, LiveVals3),
 	code_info__get_temps_in_use(TempsSet),
 	{ map__to_assoc_list(TempsSet, Temps) },
@@ -2925,17 +2943,17 @@
 				LiveInfo3]
 	).
 
-:- pred code_info__livevals_to_livelvals(assoc_list(lval, var), gc_method,
+:- pred code_info__livevals_to_livelvals(assoc_list(lval, var), bool,
 	instmap, list(liveinfo), code_info, code_info).
 :- mode code_info__livevals_to_livelvals(in, in, in, out, in, out) is det.
 
-code_info__livevals_to_livelvals([], _GC_Method, _, []) --> [].
-code_info__livevals_to_livelvals([Lval - Var | Ls], GC_Method, AfterCallInstMap,
-		[LiveLval | Lives]) -->
+code_info__livevals_to_livelvals([], _, _, []) --> [].
+code_info__livevals_to_livelvals([Lval - Var | Ls], NeedVarInfo,
+		AfterCallInstMap, [LiveLval | Lives]) -->
 	code_info__get_varset(VarSet),
 	{ varset__lookup_name(VarSet, Var, Name) },
 	(
-		{ GC_Method = accurate }
+		{ NeedVarInfo = yes }
 	->
 		{ instmap__lookup_var(AfterCallInstMap, Var, Inst) },
 
@@ -2947,7 +2965,7 @@
 	;
 		{ LiveLval = live_lvalue(Lval, unwanted, Name, []) }
 	),
-	code_info__livevals_to_livelvals(Ls, GC_Method, AfterCallInstMap, 
+	code_info__livevals_to_livelvals(Ls, NeedVarInfo, AfterCallInstMap, 
 		Lives).
 
 :- pred code_info__get_live_value_type(slot_contents, live_value_type).
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.12
diff -u -u -r1.12 continuation_info.m
--- continuation_info.m	1998/04/17 06:55:36	1.12
+++ continuation_info.m	1998/06/17 06:10:34
@@ -15,22 +15,22 @@
 %
 % Information is collected in several passes. 
 %
-% 	- Before we start generating code for a procedure,
+% 	1 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.
 %
-%	- During code generation for the procedure, provided the option
+%	2 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
+% 	3 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), together with 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
+% 	4 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.
@@ -83,23 +83,70 @@
 :- type proc_label_layout_info	==	map(label, internal_layout_info).
 
 	%
-	% Information for any internal label.
-	% 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.
+	% Information for an internal label.
 	%
-:- type internal_layout_info	==	maybe(layout_label_info).
+	% There are two ways for the compiler to generate labels for
+	% which layouts may be required:
+	%
+	% (a) as the label associated with a trace port, and
+	% (b) as the return label of some kind of call (plain, method or h-o).
+	%
+	% Label optimizations may redirect a call return away from the
+	% originally generated label to another label, possibly one
+	% that is associated with a trace port. This optimization may
+	% also direct returns from more than one call to the same label.
+	%
+	% We may be interested in the layout of things at a label for three
+	% different reasons: for stack tracing, for accurate gc, and for
+	% execution tracing.
+	%
+	% - For stack tracing, we are interested only in call return labels.
+	%   Even for these, we need only the pointer to the procedure layout
+	%   info; we do not need any information about variables.
+	%
+	% - For accurate gc, we are interested only in call return labels.
+	%   We need to know about all the variables that can be accessed
+	%   after the label; this is the intersection of all the variables
+	%   denoted as live in the call instructions. (Variables which
+	%   are not in the intersection are not guaranteed to have a
+	%   meaningful value on all execution paths that lead to the label.)
+	%
+	% - For execution tracing, our primary interest is in trace port
+	%   labels. At these labels we only want info about named variables,
+	%   but we may want this info even if the variable will never be
+	%   referred to again.
+	%
+	%   For supporting up-level printing, we are also interested in
+	%   the variables that are live at return labels. The variables
+	%   about which we want info at these labels is a subset of the
+	%   variables agc is interested in (the named subset).
+	%   We do not collect this set explicitly. Instead, if we are doing
+	%   execution tracing, we collect agc layout info as usual, and
+	%   (if we not really doing agc) remove the unnamed variables
+	%   in stack_layout.m.
+	%
+	% For labels which correspond to a trace port (part (a) above),
+	% we record information in the first field. Since trace.m generates
+	% a unique label for each trace port, this field is never updated
+	% once it is set in pass 2. For labels which correspond to a call
+	% return, we record information in the second field during pass 4.
+	% Since a label can serve as the return label for more than once call,
+	% this field can be updated (by taking the intersection of the live
+	% variables) after it is set. Since a call may return to the label
+	% of an internal port, it is possible for both fields to be set.
+	% In this case, stack_layout.m will take the union of the relevant
+	% info. If neither field is set, then the label's layout is required
+	% only for stack tracing.
+	%
+:- type internal_layout_info
+	--->	internal_layout_info(
+			maybe(layout_label_info),
+			maybe(layout_label_info)
+		).
 
 	%
 	% 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 layout_label_info
 	--->	layout_label_info(
 			set(var_info),
@@ -140,10 +187,12 @@
 
 	%
 	% Add the information for all the continuation labels within a proc.
+	% The bool says whether we want information about the variables
+	% live at continuation labels.
 	%
 :- pred continuation_info__process_instructions(pred_proc_id::in,
-	list(instruction)::in, bool::in, continuation_info::in,
-	continuation_info::out) is det.
+	list(instruction)::in, bool::in,
+	continuation_info::in, continuation_info::out) is det.
 
 	%
 	% Get the finished list of proc_layout_infos.
@@ -194,18 +243,18 @@
 	map__values(ContInfo, Entries).
 
 continuation_info__process_llds([], _) --> [].
-continuation_info__process_llds([Proc | Procs], WantAgcInfo) -->
+continuation_info__process_llds([Proc | Procs], WantReturnInfo) -->
 	{ Proc = c_procedure(_, _, PredProcId, Instrs) },
 	continuation_info__process_instructions(PredProcId, Instrs,
-		WantAgcInfo),
-	continuation_info__process_llds(Procs, WantAgcInfo).
+		WantReturnInfo),
+	continuation_info__process_llds(Procs, WantReturnInfo).
 
 	%
 	% Process the list of instructions for this proc, adding
 	% all internal label information to the continuation_info.
 	%
 continuation_info__process_instructions(PredProcId, Instructions,
-		WantAgcInfo, ContInfo0, ContInfo) :-
+		WantReturnInfo, ContInfo0, ContInfo) :-
 
 		% Get all the continuation info from the call instructions.
 	map__lookup(ContInfo0, PredProcId, ProcLayoutInfo0),
@@ -217,7 +266,7 @@
 	list__filter_map(GetCallLivevals, Instructions, Calls),
 
 		% Process the continuation label info.
-	list__foldl(continuation_info__process_continuation(WantAgcInfo),
+	list__foldl(continuation_info__process_continuation(WantReturnInfo),
 		Calls, Internals0, Internals),
 
 	ProcLayoutInfo = proc_layout_info(A, B, C, D, E, Internals),
@@ -226,96 +275,76 @@
 %-----------------------------------------------------------------------------%
 
 	%
-	% Collect the liveness information from a single label and add
-	% it to the internals.
+	% Collect the liveness information from a single return label
+	% and add it to the internals.
 	%
 :- pred continuation_info__process_continuation(bool::in,
 	pair(label, list(liveinfo))::in, 
 	proc_label_layout_info::in, proc_label_layout_info::out) is det.
 
-continuation_info__process_continuation(WantAgcInfo, Label - LiveInfoList,
+continuation_info__process_continuation(WantReturnInfo, Label - LiveInfoList,
 		Internals0, Internals) :-
-	( WantAgcInfo = yes ->
-		GetVarInfo = lambda([LiveLval::in, VarInfo::out] is det, (
-			LiveLval = live_lvalue(Lval, LiveValueType, Name, _),
-			VarInfo = var_info(Lval, LiveValueType, Name)
-		)),
-		list__map(GetVarInfo, LiveInfoList, VarInfoList),
-		GetTypeInfo = lambda([LiveLval::in, TypeInfos::out] is det, (
-			LiveLval = live_lvalue(_, _, _, TypeInfos)
-		)),
-		list__map(GetTypeInfo, LiveInfoList, TypeInfoListList),
-		list__condense(TypeInfoListList, TypeInfoList),
-		list__sort_and_remove_dups(TypeInfoList, SortedTypeInfoList),
-		set__sorted_list_to_set(SortedTypeInfoList, TypeInfoSet),
-		set__list_to_set(VarInfoList, VarInfoSet),
-		NewInternal = yes(layout_label_info(VarInfoSet, TypeInfoSet))
+	( map__search(Internals0, Label, Internal0) ->
+		Internal0 = internal_layout_info(Port0, Return0)
 	;
-		NewInternal = no
+		Port0 = no,
+		Return0 = no
 	),
-	continuation_info__add_internal_info(Label, NewInternal,
-		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
+	( WantReturnInfo = yes ->
+		continuation_info__convert_return_data(LiveInfoList,
+			VarInfoSet, TypeInfoSet),
+		(
+			Return0 = no,
+			Return = yes(layout_label_info(VarInfoSet,
+				TypeInfoSet))
+		;
+				% If a var is known to be dead
+				% on return from one call, it
+				% cannot be accessed on returning
+				% from the other calls that reach
+				% the same return address either.
+			Return0 = yes(layout_label_info(LV0, TV0)),
+			set__intersect(LV0, VarInfoSet, LV),
+			set__intersect(TV0, TypeInfoSet, TV),
+			Return = yes(layout_label_info(LV, TV))
+		)
 	;
-		map__det_insert(InternalMap0, Label, no, InternalMap)
-	).
-
-%-----------------------------------------------------------------------------%
+		Return = Return0
+	),
+	Internal = internal_layout_info(Port0, Return),
+	map__set(Internals0, Label, Internal, Internals).
 
-	%
-	% 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.
+:- pred continuation_info__convert_return_data(list(liveinfo)::in,
+	set(var_info)::out, set(pair(tvar, lval))::out) is det.
 
-continuation_info__add_internal_info(Label, Internal1,
-		Internals0, Internals) :-
+continuation_info__convert_return_data(LiveInfos, VarInfoSet, TypeInfoSet) :-
+	GetVarInfo = lambda([LiveLval::in, VarInfo::out] is det, (
+		LiveLval = live_lvalue(Lval, LiveValueType, Name, _),
+		VarInfo = var_info(Lval, LiveValueType, Name)
+	)),
+	list__map(GetVarInfo, LiveInfos, VarInfoList),
+	GetTypeInfo = lambda([LiveLval::in, TypeInfos::out] is det, (
+		LiveLval = live_lvalue(_, _, _, TypeInfos)
+	)),
+	list__map(GetTypeInfo, LiveInfos, TypeInfoListList),
+	list__condense(TypeInfoListList, TypeInfoList),
+	list__sort_and_remove_dups(TypeInfoList, SortedTypeInfoList),
+	set__sorted_list_to_set(SortedTypeInfoList, TypeInfoSet),
+	set__list_to_set(VarInfoList, VarInfoSet).
+
+:- pred continuation_info__filter_named_vars(list(liveinfo)::in,
+	list(liveinfo)::out) is det.
+
+continuation_info__filter_named_vars([], []).
+continuation_info__filter_named_vars([LiveInfo | LiveInfos], Filtered) :-
+	continuation_info__filter_named_vars(LiveInfos, Filtered1),
 	(
-		map__search(Internals0, Label, Internal0)
+		LiveInfo = live_lvalue(_, _, Name, _),
+		Name \= ""
 	->
-		continuation_info__merge_internal_labels(Internal0, Internal1,
-			Internal),
-		map__set(Internals0, Label, Internal, Internals)
+		Filtered = [LiveInfo | Filtered1]
 	;
-		map__det_insert(Internals0, Label, Internal1, Internals)
+		Filtered = Filtered1
 	).
 
-	%
-	% Merge the continuation label information of two labels.
-	%
-	% If there are two continuation infos to be merged, we take
-	% the intersection.
-	%
-	% The reason why taking the intersection is correct is that if
-	% something is not live on one path, the code following the
-	% label is guaranteed not to depend on it.
-	% XXX Is this true for non-det code?
-
-:- 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(layout_label_info(LV0, TV0)),
-		yes(layout_label_info(LV0, TV0))).
-continuation_info__merge_internal_labels(
-		yes(layout_label_info(LV0, TV0)),
-		no,
-		yes(layout_label_info(LV0, TV0))).
-continuation_info__merge_internal_labels(
-		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).
-
-%-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
Index: compiler/globals.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/globals.m,v
retrieving revision 1.30
diff -u -u -r1.30 globals.m
--- globals.m	1998/06/08 08:24:49	1.30
+++ globals.m	1998/06/16 07:13:46
@@ -46,10 +46,11 @@
 	;	num_data_elems
 	;	size_data_elems.
 
-:- type trace_level
-	--->	minimal
-	;	interface
-	;	full.
+:- type trace_level.
+
+:- pred trace_level_trace_interface(trace_level::in, bool::out) is det.
+:- pred trace_level_trace_ports(trace_level::in, bool::out) is det.
+:- pred trace_level_trace_returns(trace_level::in, bool::out) is det.
 
 :- pred convert_gc_method(string::in, gc_method::out) is semidet.
 :- pred convert_tags_method(string::in, tags_method::out) is semidet.
@@ -142,6 +143,8 @@
 :- pred globals__io_set_trace_level(trace_level::in,
 	io__state::di, io__state::uo) is det.
 
+:- pred globals__io_set_trace_level_none(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.
 
@@ -166,6 +169,27 @@
 :- import_module exprn_aux.
 :- import_module map, std_util, io, require.
 
+:- type trace_level
+	--->	none
+	;	interface
+	;	interface_ports
+	;	interface_ports_returns.
+
+trace_level_trace_interface(none, no).
+trace_level_trace_interface(interface, yes).
+trace_level_trace_interface(interface_ports, yes).
+trace_level_trace_interface(interface_ports_returns, yes).
+
+trace_level_trace_ports(none, no).
+trace_level_trace_ports(interface, no).
+trace_level_trace_ports(interface_ports, yes).
+trace_level_trace_ports(interface_ports_returns, yes).
+
+trace_level_trace_returns(none, no).
+trace_level_trace_returns(interface, no).
+trace_level_trace_returns(interface_ports, no).
+trace_level_trace_returns(interface_ports_returns, yes).
+
 %-----------------------------------------------------------------------------%
 
 convert_gc_method("none", none).
@@ -198,12 +222,13 @@
 convert_termination_norm("num-data-elems", num_data_elems).
 convert_termination_norm("size-data-elems", size_data_elems).
 
-convert_trace_level("minimum", no, minimal).
+convert_trace_level("minimum", no, none).
 convert_trace_level("minimum", yes, interface).
 convert_trace_level("interfaces", _, interface).
-convert_trace_level("all", _, full).
-convert_trace_level("default", no, minimal).
-convert_trace_level("default", yes, full).
+convert_trace_level("most", _, interface_ports).
+convert_trace_level("all", _, interface_ports_returns).
+convert_trace_level("default", no, none).
+convert_trace_level("default", yes, interface_ports).
 
 %-----------------------------------------------------------------------------%
 
@@ -369,6 +394,11 @@
 		% XXX there is a bit of a design flaw with regard to
 		% uniqueness and io__set_globals
 	globals__io_set_globals(Globals).
+
+	% This predicate is needed because mercury_compile.m doesn't know
+	% anything about type trace_level.
+globals__io_set_trace_level_none -->
+	globals__io_set_trace_level(none).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.55
diff -u -u -r1.55 handle_options.m
--- handle_options.m	1998/06/16 06:11:33	1.55
+++ handle_options.m	1998/06/17 05:21:51
@@ -273,7 +273,7 @@
 	%	  paths across optimization levels
 	% 	- enabling stack layouts
 	% 	- enabling typeinfo liveness
-	( { TraceLevel = interface ; TraceLevel = full } ->
+	( { trace_level_trace_interface(TraceLevel, yes) } ->
 			% The following options modify the structure
 			% of the program, which makes it difficult to
 			% relate the trace to the source code (although
Index: compiler/live_vars.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/live_vars.m,v
retrieving revision 1.76
diff -u -u -r1.76 live_vars.m
--- live_vars.m	1998/06/09 02:13:10	1.76
+++ live_vars.m	1998/06/16 04:49:12
@@ -50,7 +50,7 @@
 	set__init(LiveSets0),
 	module_info_globals(ModuleInfo, Globals),
 	globals__get_trace_level(Globals, TraceLevel),
-	( ( TraceLevel = interface ; TraceLevel = full ) ->
+	( trace_level_trace_interface(TraceLevel, yes) ->
 		trace__fail_vars(ModuleInfo, ProcInfo0, ResumeVars0),
 		set__insert(LiveSets0, ResumeVars0, LiveSets1)
 	;
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.96
diff -u -u -r1.96 liveness.m
--- liveness.m	1998/06/12 07:37:53	1.96
+++ liveness.m	1998/06/16 04:49:27
@@ -182,7 +182,7 @@
 	detect_deadness_in_goal(Goal1, Deadness0, LiveInfo, _, Goal2),
 
 	globals__get_trace_level(Globals, TraceLevel),
-	( ( TraceLevel = interface ; TraceLevel = full ) ->
+	( trace_level_trace_interface(TraceLevel, yes) ->
 		trace__fail_vars(ModuleInfo, ProcInfo0, ResumeVars0)
 	;
 		set__init(ResumeVars0)
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.83
diff -u -u -r1.83 llds_out.m
--- llds_out.m	1998/06/09 02:13:27	1.83
+++ llds_out.m	1998/06/16 07:39:31
@@ -216,7 +216,7 @@
 
 output_c_file_mercury_headers -->
 	globals__io_get_trace_level(TraceLevel),
-	( { TraceLevel = interface ; TraceLevel = full } ->
+	( { trace_level_trace_interface(TraceLevel, yes) } ->
 		io__write_string("#define MR_STACK_TRACE_THIS_MODULE\n"),
 		io__write_string("#include ""mercury_imp.h""\n"),
 		io__write_string("#include ""mercury_trace.h""\n")
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.99
diff -u -u -r1.99 mercury_compile.m
--- mercury_compile.m	1998/06/17 05:13:48	1.99
+++ mercury_compile.m	1998/06/17 05:22:07
@@ -240,7 +240,7 @@
 			globals__io_get_trace_level(TraceLevel),
 
 			globals__io_set_option(trace_stack_layout, bool(no)),
-			globals__io_set_trace_level(minimal),
+			globals__io_set_trace_level_none,
 
 			% XXX it would be better to do something like
 			%
@@ -1110,7 +1110,7 @@
 				PredId, ProcId, ModuleInfo3),
 	{ store_alloc_in_proc(ProcInfo5, PredId, ModuleInfo3, ProcInfo6) },
 	globals__io_get_trace_level(TraceLevel),
-	( { TraceLevel = interface ; TraceLevel = full } ->
+	( { trace_level_trace_interface(TraceLevel, yes) } ->
 		write_proc_progress_message(
 			"% Calculating goal paths in ",
 					PredId, ProcId, ModuleInfo3),
@@ -1139,13 +1139,21 @@
 	( { BasicStackLayout = yes } ->
 		{ Proc = c_procedure(_, _, PredProcId, Instructions) },
 		{ module_info_get_continuation_info(ModuleInfo5, ContInfo2) },
-		{ globals__lookup_bool_option(Globals, agc_stack_layout,
-			AgcStackLayout) },
 		write_proc_progress_message(
 			"% Generating call continuation information for ",
 				PredId, ProcId, ModuleInfo5),
+		{ globals__get_gc_method(Globals, GcMethod) },
+		{
+			( GcMethod = accurate
+			; trace_level_trace_returns(TraceLevel, yes)
+			)
+		->
+			WantReturnInfo = yes
+		;
+			WantReturnInfo = no
+		},
 		{ continuation_info__process_instructions(PredProcId,
-			Instructions, AgcStackLayout, ContInfo2, ContInfo3) },
+			Instructions, WantReturnInfo, ContInfo2, ContInfo3) },
 		{ module_info_set_continuation_info(ModuleInfo5, ContInfo3, 
 			ModuleInfo) }
 	;
@@ -1748,7 +1756,7 @@
 
 mercury_compile__maybe_goal_paths(HLDS0, Verbose, Stats, HLDS) -->
 	globals__io_get_trace_level(TraceLevel),
-	( { TraceLevel = interface ; TraceLevel = full } ->
+	( { trace_level_trace_interface(TraceLevel, yes) } ->
 		maybe_write_string(Verbose, "% Calculating goal paths..."),
 		maybe_flush_output(Verbose),
 		process_all_nonimported_procs(
@@ -1800,10 +1808,19 @@
 		maybe_write_string(Verbose,
 			"% Generating call continuation information..."),
 		maybe_flush_output(Verbose),
-		globals__io_lookup_bool_option(agc_stack_layout, 
-			AgcStackLayout),
+		globals__io_get_gc_method(GcMethod),
+		globals__io_get_trace_level(TraceLevel),
+		{
+			( GcMethod = accurate
+			; trace_level_trace_returns(TraceLevel, yes)
+			)
+		->
+			WantReturnInfo = yes
+		;
+			WantReturnInfo = no
+		},
 		{ module_info_get_continuation_info(ModuleInfo0, ContInfo0) },
-		{ continuation_info__process_llds(LLDS0, AgcStackLayout,
+		{ continuation_info__process_llds(LLDS0, WantReturnInfo,
 			ContInfo0, ContInfo) },
 		{ module_info_set_continuation_info(ModuleInfo0, ContInfo,
 			ModuleInfo) },
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.13
diff -u -u -r1.13 stack_layout.m
--- stack_layout.m	1998/05/19 05:14:30	1.13
+++ stack_layout.m	1998/06/17 06:13:18
@@ -83,7 +83,6 @@
 % This table has the following format:
 %
 %	procedure info		(Word *) - pointer to procedure stack layout
-%	internal label number	(Integer)
 % 	# of live vars		(Integer)
 % 	live data pairs 	(Word *) - pointer to vector of pairs
 %				containing MR_Live_Lval and MR_Live_Type
@@ -93,13 +92,6 @@
 %				giving the number of entries in the vector;
 %				a NULL pointer means no type parameters
 %
-% The internal label number field holds either the real label number
-% (which is always strictly positive), 0 indicating the entry label,
-% or a negative number indicating unknown (the last alternative is possible
-% only in non-compiler-generated structures). The only purpose of this field
-% is to make debugging the native garbage collector easier. Accordingly,
-% it will be present only if the option agc_stack_layout is set.
-%
 % 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.)
@@ -134,15 +126,21 @@
 %	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 or the trace level specifies
+%	a capability for uplevel printing, and the label represents
 % 	a point where execution can resume after a procedure call or
 %	after backtracking.
 %
-% 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).
+% For labels that do not fall into one of these two categories, the
+% "# of live vars" field will be negative to indicate the absence of
+% information about the variables live at this label, and the last
+% four fields will not be present.
+%
+% For labels that do fall into one of these two categories, the
+% "# of live vars" field will hold the number of live variables, which
+% will not be negative. If it is zero, the last four fields will not be
+% present. Even if it is not zero, however, the pointer to the live data
+% names vector will be NULL unless the label is used in execution tracing.
 %
 % XXX: Presently, inst information is ignored. We also do not yet enable
 % procid stack layouts for profiling, since profiling does not yet use
@@ -373,20 +371,17 @@
 	stack_layout__get_module_name(ModuleName),
 	{ EntryAddrRval = const(data_addr_const(data_addr(ModuleName,
 		stack_layout(local(ProcLabel))))) },
-	stack_layout__construct_internal_rvals(Internal, AgcRvals),
-	stack_layout__get_agc_stack_layout(AgcLayout),
-	( { AgcLayout = yes } ->
-		{ Label = local(_, LabelNum0) ->
-			LabelNum = LabelNum0
-		;
-			LabelNum = 0
-		},
-		{ LabelNumRval = const(int_const(LabelNum)) },
-		{ LayoutRvals = [yes(EntryAddrRval), yes(LabelNumRval)
-			| AgcRvals] }
-	;
-		{ LayoutRvals = [yes(EntryAddrRval) | AgcRvals] }
-	),
+	stack_layout__construct_internal_rvals(Internal, VarInfoRvals),
+	% Reenable this code if you want label numbers in label layouts.
+	% { Label = local(_, LabelNum0) ->
+	% 	LabelNum = LabelNum0
+	% ;
+	% 	LabelNum = 0
+	% },
+	% { LabelNumRval = const(int_const(LabelNum)) },
+	% { LayoutRvals = [yes(EntryAddrRval), yes(LabelNumRval
+	% 	| VarInfoRvals] }
+	{ LayoutRvals = [yes(EntryAddrRval) | VarInfoRvals] },
 	{ CModule = c_data(ModuleName, stack_layout(Label), no,
 		LayoutRvals, []) },
 	stack_layout__add_cmodule(CModule, Label).
@@ -398,37 +393,69 @@
 	stack_layout_info::in, stack_layout_info::out) is det.
 
 stack_layout__construct_internal_rvals(Internal, RvalList) -->
+	{ Internal = internal_layout_info(Port, Return) },
+	{
+		Port = no,
+		set__init(PortLiveVarSet),
+		set__init(PortTypeVarSet)
+	;
+		Port = yes(layout_label_info(PortLiveVarSet, PortTypeVarSet))
+	},
+	stack_layout__get_agc_stack_layout(AgcStackLayout),
+	{
+		Return = no,
+		set__init(ReturnLiveVarSet),
+		set__init(ReturnTypeVarSet)
+	;
+		Return = yes(layout_label_info(ReturnLiveVarSet0,
+			ReturnTypeVarSet0)),
+		( AgcStackLayout = yes ->
+			ReturnLiveVarSet = ReturnLiveVarSet0,
+			ReturnTypeVarSet0 = ReturnTypeVarSet
+		;
+			% This set of variables must be for uplevel printing
+			% in execution tracing, so we are interested only
+			% in (a) variables, not temporaries, (b) only named
+			% variables, and (c) only those on the stack, not
+			% the return valies.
+			set__to_sorted_list(ReturnLiveVarSet0,
+				ReturnLiveVarList0),
+			stack_layout__select_trace_return(
+				ReturnLiveVarList0, ReturnTypeVarSet0,
+				ReturnLiveVarList, ReturnTypeVarSet),
+			set__list_to_set(ReturnLiveVarList, ReturnLiveVarSet)
+		)
+	},
 	(
-		{ Internal = yes(layout_label_info(LiveLvalSet, TVars)) }
+		{ Port = no },
+		{ Return = no }
 	->
-		stack_layout__construct_livelval_rvals(LiveLvalSet, TVars,
-			RvalList)
+			% The -1 says that there is no info available
+			% about variables at this label. (Zero would say
+			% that there are no variables live at this label,
+			% which may not be true.)
+		{ RvalList = [yes(const(int_const(-1)))] }
 	;
-		% 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)))] }
+		{ set__union(PortLiveVarSet, ReturnLiveVarSet, LiveVarSet) },
+		{ set__union(PortTypeVarSet, ReturnTypeVarSet, TypeVarSet) },
+		stack_layout__construct_livelval_rvals(LiveVarSet, TypeVarSet,
+			RvalList)
 	).
 
 %---------------------------------------------------------------------------%
 
-:- pred stack_layout__construct_livelval_rvals(set(var_info),
-		set(pair(tvar, lval)), list(maybe(rval)),
-		stack_layout_info, stack_layout_info).
-:- mode stack_layout__construct_livelval_rvals(in, in, out, in, out) is det.
+:- pred stack_layout__construct_livelval_rvals(set(var_info)::in,
+	set(pair(tvar, lval))::in, list(maybe(rval))::out,
+	stack_layout_info::in, stack_layout_info::out) is det.
 
 stack_layout__construct_livelval_rvals(LiveLvalSet, TVarLocnSet, RvalList) -->
 	{ set__to_sorted_list(LiveLvalSet, LiveLvals) },
 	{ list__length(LiveLvals, Length) },
 	{ VarLengthRval = const(int_const(Length)) },
 	( { Length > 0 } ->
-		stack_layout__construct_liveval_pairs(LiveLvals, LiveValRval,
-			NamesRval),
+		{ stack_layout__sort_livevals(LiveLvals, SortedLiveLvals) },
+		stack_layout__construct_liveval_pairs(SortedLiveLvals,
+			LiveValRval, NamesRval),
 
 		{ set__to_sorted_list(TVarLocnSet, TVarLocns) },
 		( { TVarLocns = [] } ->
@@ -448,6 +475,62 @@
 	;
 		{ RvalList = [yes(VarLengthRval)] }
 	).
+
+%---------------------------------------------------------------------------%
+
+	% Given a list of var_infos and the type variables that occur in them,
+	% select only the var_infos that may be required by up-level printing
+	% in the trace-based debugger. At the moment the typeinfo list we
+	% return may be bigger than necessary, but this does not compromise
+	% correctness; we do this to avoid having to scan the types of all
+	% the selected var_infos.
+
+:- pred stack_layout__select_trace_return(
+	list(var_info)::in, set(pair(tvar, lval))::in,
+	list(var_info)::out, set(pair(tvar, lval))::out) is det.
+
+stack_layout__select_trace_return(Infos, TVars, TraceReturnInfos, TVars) :-
+	IsNamedReturnVar = lambda([LvalInfo::in] is semidet, (
+		LvalInfo = var_info(Lval, LvalType, Name),
+		LvalType = var(_, _),
+		Name \= "",
+		( Lval = stackvar(_) ; Lval = framevar(_) )
+	)),
+	list__filter(IsNamedReturnVar, Infos, TraceReturnInfos).
+
+	% Given a list of var_infos, put the ones that tracing can be
+	% interested in (whether at an internal port or for uplevel printing)
+	% in a block at the start, and both this block and the remaining
+	% block. The division into two blocks can make the job of the
+	% debugger somewhat easier, the sorting of the named var block makes
+	% the output of the debugger look nicer, and the sorting of the both
+	% blocks makes it more likely that different labels' layout structures
+	% will have common parts (e.g. name vectors) that can be optimized
+	% by llds_common.m.
+
+:- pred stack_layout__sort_livevals(list(var_info)::in, list(var_info)::out)
+	is det.
+
+stack_layout__sort_livevals(OrigInfos, FinalInfos) :-
+	IsNamedVar = lambda([LvalInfo::in] is semidet, (
+		LvalInfo = var_info(_Lval, LvalType, Name),
+		LvalType = var(_, _),
+		Name \= ""
+	)),
+	list__filter(IsNamedVar, OrigInfos, NamedVarInfos0, OtherInfos0),
+	CompareVarInfos = lambda([Var1::in, Var2::in, Result::out] is det, (
+		Var1 = var_info(Lval1, _, Name1),
+		Var2 = var_info(Lval2, _, Name2),
+		compare(NameResult, Name1, Name2),
+		( NameResult = (=) ->
+			compare(Result, Lval1, Lval2)
+		;
+			Result = NameResult
+		)
+	)),
+	list__sort(CompareVarInfos, NamedVartInfos0, NamedVartInfos),
+	list__sort(CompareVarInfos, OtherInfos0, OtherInfos),
+	list__append(NamedVarInfos, OtherInfos, FinalInfos).
 
 %---------------------------------------------------------------------------%
 
Index: compiler/store_alloc.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/store_alloc.m,v
retrieving revision 1.65
diff -u -u -r1.65 store_alloc.m
--- store_alloc.m	1998/06/09 02:14:43	1.65
+++ store_alloc.m	1998/06/16 04:53:08
@@ -69,7 +69,7 @@
 	),
 	initial_liveness(ProcInfo0, PredId, ModuleInfo, Liveness0),
 	globals__get_trace_level(Globals, TraceLevel),
-	( ( TraceLevel = interface ; TraceLevel = full ) ->
+	( trace_level_trace_interface(TraceLevel, yes) ->
 		trace__fail_vars(ModuleInfo, ProcInfo0, ResumeVars0)
 	;
 		set__init(ResumeVars0)
Index: compiler/trace.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/trace.m,v
retrieving revision 1.9
diff -u -u -r1.9 trace.m
--- trace.m	1998/05/16 07:30:56	1.9
+++ trace.m	1998/06/16 04:54:29
@@ -162,7 +162,7 @@
 trace__setup(TraceLevel) -->
 	code_info__get_trace_slot(CallNumSlot),
 	code_info__get_trace_slot(CallDepthSlot),
-	( { TraceLevel = full } ->
+	( { trace_level_trace_ports(TraceLevel, yes) } ->
 		{ TraceType = full_trace }
 	;
 		code_info__get_trace_slot(CallFromFullSlot),
@@ -353,7 +353,7 @@
 		]),
 	Code = tree(ProduceCode, TraceCode)
 	},
-	code_info__add_layout_for_label(Label, yes(LayoutLabelInfo)).
+	code_info__add_trace_layout_for_label(Label, 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,
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_stack_layout.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_layout.h,v
retrieving revision 1.6
diff -u -u -r1.6 mercury_stack_layout.h
--- mercury_stack_layout.h	1998/05/19 05:15:09	1.6
+++ mercury_stack_layout.h	1998/06/17 06:18:24
@@ -300,7 +300,7 @@
 
 typedef	struct MR_Stack_Layout_Label_Struct {
 	MR_Stack_Layout_Entry	*MR_sll_entry;
-#ifdef	NATIVE_GC
+#if 0
 	Integer			MR_sll_label_num;
 #endif
 	Integer			MR_sll_var_count;
Index: runtime/mercury_stack_trace.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_trace.c,v
retrieving revision 1.8
diff -u -u -r1.8 mercury_stack_trace.c
--- mercury_stack_trace.c	1998/06/11 05:22:33	1.8
+++ mercury_stack_trace.c	1998/06/14 09:09:51
@@ -40,7 +40,7 @@
 };
 
 static	MR_Stack_Walk_Step_Result MR_stack_walk_step(MR_Stack_Layout_Entry *,
-			MR_Stack_Layout_Entry **, Word **, Word **,
+			MR_Stack_Layout_Label **, Word **, Word **,
 			const char **);
 
 static	void	MR_dump_stack_record_init(void);
@@ -81,10 +81,10 @@
 
 const char *
 MR_dump_stack_from_layout(FILE *fp, MR_Stack_Layout_Entry *entry_layout,
-		Word *det_stack_pointer, Word *current_frame)
+	Word *det_stack_pointer, Word *current_frame)
 {
 	MR_Stack_Walk_Step_Result	result;
-	MR_Stack_Layout_Entry		*next_entry_layout;
+	MR_Stack_Layout_Label		*return_label_layout;
 	const char			*problem;
 	Word				*stack_trace_sp;
 	Word				*stack_trace_curfr;
@@ -95,7 +95,7 @@
 	stack_trace_curfr = current_frame;
 
 	do {
-		result = MR_stack_walk_step(entry_layout, &next_entry_layout,
+		result = MR_stack_walk_step(entry_layout, &return_label_layout,
 				&stack_trace_sp, &stack_trace_curfr, &problem);
 		if (result == STEP_ERROR_BEFORE) {
 			MR_dump_stack_record_flush(fp);
@@ -108,32 +108,58 @@
 			MR_dump_stack_record_frame(fp, entry_layout);
 		}
 
-		if (next_entry_layout == NULL) {
+		if (return_label_layout == NULL) {
 			break;
 		}
 
-		entry_layout = next_entry_layout;
+		entry_layout = return_label_layout->MR_sll_entry;
 	} while (TRUE); 
 
 	MR_dump_stack_record_flush(fp);
 	return NULL;
 }
 
+const MR_Stack_Layout_Label *
+MR_find_nth_ancestor(const MR_Stack_Layout_Label *label_layout,
+	int ancestor_level, Word **stack_trace_sp, Word **stack_trace_curfr,
+	const char **problem)
+{
+	MR_Stack_Walk_Step_Result	result;
+	MR_Stack_Layout_Label		*return_label_layout;
+	int				i;
+
+	*problem = NULL;
+	for (i = 0; i < ancestor_level && label_layout != NULL; i++) {
+		(void) MR_stack_walk_step(label_layout->MR_sll_entry,
+				&return_label_layout,
+				stack_trace_sp, stack_trace_curfr, problem);
+		label_layout = return_label_layout;
+	}
+
+	if (label_layout == NULL && *problem == NULL) {
+		*problem = "not that many ancestors";
+	}
+
+	return label_layout;
+}
+
+
 static	MR_Stack_Walk_Step_Result
 MR_stack_walk_step(MR_Stack_Layout_Entry *entry_layout,
-	MR_Stack_Layout_Entry **next_entry_layout,
+	MR_Stack_Layout_Label **return_label_layout,
 	Word **stack_trace_sp_ptr, Word **stack_trace_curfr_ptr,
 	const char **problem_ptr)
 {
 	Label			*label;
 	MR_Live_Lval		location;
-	MR_Stack_Layout_Label	*layout;
+	MR_Stack_Layout_Label	*label_layout;
 	MR_Lval_Type		type;
 	int			number, determinism;
 	Code			*success;
 
-	determinism = entry_layout->MR_sle_detism;
+	*return_label_layout = NULL;
 
+	determinism = entry_layout->MR_sle_detism;
 	if (determinism < 0) {
 		/*
 		** This means we have reached some handwritten code that has
@@ -163,7 +189,6 @@
 	}
 
 	if (success == MR_stack_trace_bottom) {
-		*next_entry_layout = NULL;
 		return STEP_OK;
 	}
 
@@ -173,13 +198,13 @@
 		return STEP_ERROR_AFTER;
 	}
 
-	layout = (MR_Stack_Layout_Label *) label->e_layout;
-	if (layout == NULL) {
+	label_layout = (MR_Stack_Layout_Label *) label->e_layout;
+	if (label_layout == NULL) {
 		*problem_ptr = "reached label with no stack layout info";
 		return STEP_ERROR_AFTER;
 	}
 
-	*next_entry_layout = layout->MR_sll_entry;
+	*return_label_layout = label_layout;
 	return STEP_OK;
 }
 
Index: runtime/mercury_stack_trace.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stack_trace.h,v
retrieving revision 1.5
diff -u -u -r1.5 mercury_stack_trace.h
--- mercury_stack_trace.h	1998/06/08 08:27:07	1.5
+++ mercury_stack_trace.h	1998/06/14 08:57:46
@@ -55,6 +55,11 @@
 				MR_Stack_Layout_Entry *entry_layout,
 				Word *det_stack_pointer, Word *current_frame);
 
+extern	const MR_Stack_Layout_Label *MR_find_nth_ancestor(
+				const MR_Stack_Layout_Label *label_layout,
+				int ancestor_level, Word **stack_trace_sp,
+				Word **stack_trace_curfr, const char **problem);
+
 /*
 ** 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
Index: runtime/mercury_stacks.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_stacks.h,v
retrieving revision 1.5
diff -u -u -r1.5 mercury_stacks.h
--- mercury_stacks.h	1998/06/08 08:27:08	1.5
+++ mercury_stacks.h	1998/06/14 07:19:37
@@ -18,6 +18,7 @@
 /* DEFINITIONS FOR MANIPULATING THE DET STACK */
 
 #define	detstackvar(n)	(MR_sp[-n])
+#define	based_detstackvar(base_sp, n)	((base_sp)[-n])
 #define	saved_detstackvar(save_area, n)	(MR_saved_sp(save_area)[-n])
 
 #define	incr_sp_push_msg(n, msg)				\
@@ -101,6 +102,7 @@
 #define	cursuccfr	bt_succfr(MR_curfr)
 #define	framevar(n)	bt_var(MR_curfr,n)
 
+#define	based_framevar(base_curfr, n)	bt_var(base_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.6
diff -u -u -r1.6 mercury_trace_internal.c
--- mercury_trace_internal.c	1998/06/14 07:00:14	1.6
+++ mercury_trace_internal.c	1998/06/16 11:27:16
@@ -43,15 +43,17 @@
 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_list_vars(int var_count,
-			const MR_Stack_Layout_Vars *var_info);
-static	void	MR_trace_browse_one(int which_var,
-			const MR_Stack_Layout_Vars *var_info);
-static	void	MR_trace_browse_all(int var_count,
-			const MR_Stack_Layout_Vars *var_info);
+			const char *path, int *ancestor_level);
+static	void	MR_trace_list_vars(const MR_Stack_Layout_Label *top_layout,
+			int ancestor_level);
+static	void	MR_trace_browse_one(const MR_Stack_Layout_Label *top_layout,
+			int ancestor_level, int which_var);
+static	void	MR_trace_browse_all(const MR_Stack_Layout_Label *top_layout,
+			int ancestor_level);
 static	void	MR_trace_browse_var(const char *name,
-			const MR_Stack_Layout_Var *var, Word *type_params);
+			const MR_Stack_Layout_Var *var,
+			bool saved_regs_valid, Word *base_sp, Word *base_curfr,
+			Word *type_params);
 static	void	MR_trace_help(void);
 
 static	bool	MR_trace_is_number(char *word, int *value);
@@ -75,6 +77,7 @@
 	Word	saved_seqno;
 	Word	saved_depth;
 	Word	saved_event;
+	int	ancestor_level;
 
 	MR_trace_event_internal_report(layout, port, seqno, depth, path);
 
@@ -83,8 +86,11 @@
 	saved_depth = MR_trace_call_depth;
 	saved_event = MR_trace_event_number;
 
-	while (MR_trace_debug_cmd(cmd, layout, port, seqno, depth, path)
-			== KEEP_INTERACTING) {
+	/* by default, print variables from the current procedure */
+	ancestor_level = 0;
+
+	while (MR_trace_debug_cmd(cmd, layout, port, seqno, depth, path,
+			&ancestor_level) == KEEP_INTERACTING) {
 		; /* all the work is done in MR_trace_debug_cmd */
 	}
 
@@ -95,7 +101,8 @@
 
 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)
+	MR_trace_port port, int seqno, int depth, const char *path,
+	int *ancestor_level)
 {
 	char	line[MR_MAX_LINE_LEN];
 	char	count_buf[MR_MAX_LINE_LEN];
@@ -262,27 +269,26 @@
 		} else {
 			printf("This command expects no argument.\n");
 		}
+	} else if (streq(words[0], "l")) {
+		if (word_count == 2 && MR_trace_is_number(words[1], &n)) {
+			*ancestor_level = n;
+			printf("Ancestor level set to %d\n", n);
+		} else {
+			printf("This command expects one argument,\n");
+			printf("a number denoting an ancestor level.\n");
+		}
 	} else if (streq(words[0], "v")) {
 		if (word_count == 1) {
-			MR_trace_list_vars((int) layout->MR_sll_var_count,
-				&layout->MR_sll_var_info);
+			MR_trace_list_vars(layout, *ancestor_level);
 		} else {
 			printf("This command expects no argument.\n");
 		}
 	} else if (streq(words[0], "p")) {
 		if (word_count == 2) {
 			if (MR_trace_is_number(words[1], &n)) {
-				if (n < layout->MR_sll_var_count) {
-					MR_trace_browse_one(n,
-						&layout->MR_sll_var_info);
-				} else {
-					printf("There is no variable #%d.\n",
-						n);
-				}
+				MR_trace_browse_one(layout, *ancestor_level, n);
 			} else if streq(words[1], "*") {
-				MR_trace_browse_all((int)
-					layout->MR_sll_var_count,
-					&layout->MR_sll_var_info);
+				MR_trace_browse_all(layout, *ancestor_level);
 			} else {
 				printf("The argument of this command should be,\n");
 				printf("a variable number or a '*' indicating all variables.\n");
@@ -297,13 +303,20 @@
 
 			do_init_modules();
 			result = MR_dump_stack_from_layout(stdout,
-					layout->MR_sll_entry, sp, maxfr);
+					layout->MR_sll_entry,
+					MR_saved_sp(MR_saved_regs),
+					MR_saved_maxfr(MR_saved_regs));
 			if (result != NULL) {
 				printf("%s\n", result);
 			}
 		} else {
 			printf("This command expects no argument.\n");
 		}
+	} else if (streq(words[0], "X")) {
+		printf("sp = %p, curfr = %p, maxfr = %p\n",
+			MR_saved_sp(MR_saved_regs),
+			MR_saved_curfr(MR_saved_regs),
+			MR_saved_maxfr(MR_saved_regs));
 	} else if (streq(words[0], "b")) {
 		if (word_count != 3) {
 			printf("This command expects two arguments,\n");
@@ -423,53 +436,128 @@
 }
 
 static void
-MR_trace_list_vars(int var_count, const MR_Stack_Layout_Vars *vars)
+MR_trace_list_vars(const MR_Stack_Layout_Label *top_layout, int ancestor_level)
 {
-	Word	*type_params;
-	bool	succeeded;
-	int	count;
-	int	i;
+	const MR_Stack_Layout_Label	*level_layout;
+	Word				*base_sp;
+	Word				*base_curfr;
+	Word				*type_params;
+	int				var_count;
+	const MR_Stack_Layout_Vars	*vars;
+	int				i;
+	const char 			*problem;
+
+	base_sp = MR_saved_sp(MR_saved_regs);
+	base_curfr = MR_saved_curfr(MR_saved_regs);
+	level_layout = MR_find_nth_ancestor(top_layout, ancestor_level,
+				&base_sp, &base_curfr, &problem);
+
+	if (level_layout == NULL) {
+		printf("%s\n", problem);
+		return;
+	}
 
-	if (var_count == 0) {
-		printf("mtrace: no live variables\n");
+	var_count = (int) level_layout->MR_sll_var_count;
+	if (var_count < 0) {
+		printf("mtrace: there is no information about live variables\n");
 		return;
+	} else if (var_count == 0) {
+		printf("mtrace: there are no live variables\n");
+		return;
 	}
 
+	vars = &level_layout->MR_sll_var_info;
 	for (i = 0; i < var_count; i++) {
-		printf("%3d %s\n", i, MR_name_if_present(vars, i));
+		printf("%9d %s\n", i, MR_name_if_present(vars, i));
 	}
 }
 
 static void
-MR_trace_browse_one(int which_var, const MR_Stack_Layout_Vars *vars)
+MR_trace_browse_one(const MR_Stack_Layout_Label *top_layout,
+	int ancestor_level, int which_var)
 {
-	Word	*type_params;
-	int	i;
+	const MR_Stack_Layout_Label	*level_layout;
+	Word				*base_sp;
+	Word				*base_curfr;
+	Word				*type_params;
+	bool				saved_regs_valid;
+	int				var_count;
+	const MR_Stack_Layout_Vars	*vars;
+	const char 			*problem;
+
+	base_sp = MR_saved_sp(MR_saved_regs);
+	base_curfr = MR_saved_curfr(MR_saved_regs);
+	level_layout = MR_find_nth_ancestor(top_layout, ancestor_level,
+				&base_sp, &base_curfr, &problem);
 
-	type_params = MR_trace_materialize_typeinfos(vars);
+	if (level_layout == NULL) {
+		printf("%s\n", problem);
+		return;
+	}
+
+	var_count = (int) level_layout->MR_sll_var_count;
+	if (var_count < 0) {
+		printf("mtrace: there is no information about live variables\n");
+		return;
+	} else if (which_var >= var_count) {
+		printf("mtrace: there is no such variable\n");
+		return;
+	}
+
+	vars = &level_layout->MR_sll_var_info;
+	saved_regs_valid = (ancestor_level == 0);
+
+	type_params = MR_trace_materialize_typeinfos_base(vars,
+				saved_regs_valid, base_sp, base_curfr);
 	MR_trace_browse_var(MR_name_if_present(vars, which_var),
-		&vars->MR_slvs_pairs[which_var], type_params);
+		&vars->MR_slvs_pairs[which_var], saved_regs_valid,
+		base_sp, base_curfr, type_params);
 	free(type_params);
 }
 
 static void 
-MR_trace_browse_all(int var_count, const MR_Stack_Layout_Vars *vars)
+MR_trace_browse_all(const MR_Stack_Layout_Label *top_layout,
+	int ancestor_level)
 {
-	Word	*type_params;
-	bool	succeeded;
-	int	count;
-	int	i;
+	const MR_Stack_Layout_Label	*level_layout;
+	Word				*base_sp;
+	Word				*base_curfr;
+	Word				*type_params;
+	bool				saved_regs_valid;
+	int				var_count;
+	const MR_Stack_Layout_Vars	*vars;
+	const char 			*problem;
+	int				i;
+
+	base_sp = MR_saved_sp(MR_saved_regs);
+	base_curfr = MR_saved_curfr(MR_saved_regs);
+	level_layout = MR_find_nth_ancestor(top_layout, ancestor_level,
+				&base_sp, &base_curfr, &problem);
+
+	if (level_layout == NULL) {
+		printf("%s\n", problem);
+		return;
+	}
 
-	if (var_count == 0) {
-		printf("mtrace: no live variables\n");
+	var_count = (int) level_layout->MR_sll_var_count;
+	if (var_count < 0) {
+		printf("mtrace: there is no information about live variables\n");
 		return;
+	} else if (var_count == 0) {
+		printf("mtrace: there are no live variables\n");
+		return;
 	}
+
+	vars = &level_layout->MR_sll_var_info;
+	saved_regs_valid = (ancestor_level == 0);
 
-	type_params = MR_trace_materialize_typeinfos(vars);
+	type_params = MR_trace_materialize_typeinfos_base(vars,
+				saved_regs_valid, base_sp, base_curfr);
 
 	for (i = 0; i < var_count; i++) {
 		MR_trace_browse_var(MR_name_if_present(vars, i),
-			&vars->MR_slvs_pairs[i], type_params);
+			&vars->MR_slvs_pairs[i], saved_regs_valid,
+			base_sp, base_curfr, type_params);
 	}
 
 	free(type_params);
@@ -477,9 +565,11 @@
 
 static void
 MR_trace_browse_var(const char *name, const MR_Stack_Layout_Var *var,
+	bool saved_regs_valid, Word *base_sp, Word *base_curfr,
 	Word *type_params)
 {
-	Word	value, type_info;
+	Word	value;
+	Word	type_info;
 	bool	print_value;
 	int	i;
 
@@ -513,7 +603,8 @@
 	** are not of interest to the user.
 	*/
 
-	if (MR_trace_get_type_and_value(var, type_params, &type_info, &value))
+	if (MR_trace_get_type_and_value_base(var, saved_regs_valid,
+			base_sp, base_curfr, type_params, &type_info, &value))
 	{
 		printf("\t");
 
@@ -803,8 +894,10 @@
 		"\tgo to event #N, printing the trace.\n"
 		"v:\t\t"
 		"\tlist the names of the variables live at this point.\n"
+		"l <n>:\t\t"
+		"\tset ancestor level to <n>\n"
 		"p <n>:\t\t"
-		"\tprint variable #n (or all live vars if <n> is '*')\n"
+		"\tprint variable #n (or all vars if <n> is '*')\n"
 		"r:\t\t"
 		"\tcontinue until forward execution is resumed.\n"
 		"[<N>] [s]:\t"
Index: runtime/mercury_trace_util.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace_util.c,v
retrieving revision 1.5
diff -u -u -r1.5 mercury_trace_util.c
--- mercury_trace_util.c	1998/06/14 07:00:18	1.5
+++ mercury_trace_util.c	1998/06/14 07:32:15
@@ -73,6 +73,14 @@
 Word *
 MR_trace_materialize_typeinfos(const MR_Stack_Layout_Vars *vars)
 {
+	return MR_trace_materialize_typeinfos_base(vars, TRUE,
+		MR_saved_sp(MR_saved_regs), MR_saved_curfr(MR_saved_regs));
+}
+
+Word *
+MR_trace_materialize_typeinfos_base(const MR_Stack_Layout_Vars *vars,
+	bool saved_regs_valid, Word *base_sp, Word *base_curfr)
+{
 	Word	*type_params;
 	bool	succeeded;
 	int	count;
@@ -88,10 +96,12 @@
 		*/
 		for (i = 1; i <= count; i++) {
 			if (vars->MR_slvs_tvars[i] != 0) {
-				type_params[i] = MR_trace_lookup_live_lval(
-					vars->MR_slvs_tvars[i], &succeeded);
+				type_params[i] = MR_trace_lookup_live_lval_base(
+					vars->MR_slvs_tvars[i],
+					saved_regs_valid, base_sp, base_curfr,
+					&succeeded);
 				if (!succeeded) {
-					fatal_error("missing type param in MR_trace_browse");
+					fatal_error("missing type param in MR_trace_materialize_typeinfos_base");
 				}
 			}
 		}
@@ -180,6 +190,15 @@
 Word
 MR_trace_lookup_live_lval(MR_Live_Lval locn, bool *succeeded)
 {
+	return MR_trace_lookup_live_lval_base(locn, TRUE,
+		MR_saved_sp(MR_saved_regs), MR_saved_curfr(MR_saved_regs),
+		succeeded);
+}
+
+Word
+MR_trace_lookup_live_lval_base(MR_Live_Lval locn, bool saved_regs_valid,
+	Word *base_sp, Word *base_curfr, bool *succeeded)
+{
 	int	locn_num;
 	Word	value;
 
@@ -189,64 +208,77 @@
 	locn_num = (int) MR_LIVE_LVAL_NUMBER(locn);
 	switch (MR_LIVE_LVAL_TYPE(locn)) {
 		case MR_LVAL_TYPE_R:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("r%d", locn_num);
-			value = saved_reg(MR_saved_regs, locn_num);
-			*succeeded = TRUE;
+			}
+			if (saved_regs_valid) {
+				value = saved_reg(MR_saved_regs, locn_num);
+				*succeeded = TRUE;
+			}
 			break;
 
 		case MR_LVAL_TYPE_F:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("f%d", locn_num);
+			}
 			break;
 
 		case MR_LVAL_TYPE_STACKVAR:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("stackvar%d", locn_num);
-			value = saved_detstackvar(MR_saved_regs, locn_num);
+			}
+			value = based_detstackvar(base_sp, locn_num);
 			*succeeded = TRUE;
 			break;
 
 		case MR_LVAL_TYPE_FRAMEVAR:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("framevar%d", locn_num);
-			value = saved_framevar(MR_saved_regs, locn_num);
+			}
+			value = based_framevar(base_curfr, locn_num);
 			*succeeded = TRUE;
 			break;
 
 		case MR_LVAL_TYPE_SUCCIP:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("succip");
+			}
 			break;
 
 		case MR_LVAL_TYPE_MAXFR:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("maxfr");
+			}
 			break;
 
 		case MR_LVAL_TYPE_CURFR:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("curfr");
+			}
 			break;
 
 		case MR_LVAL_TYPE_HP:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("hp");
+			}
 			break;
 
 		case MR_LVAL_TYPE_SP:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("sp");
+			}
 			break;
 
 		case MR_LVAL_TYPE_UNKNOWN:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("unknown");
+			}
 			break;
 
 		default:
-			if (MR_trace_print_locn)
+			if (MR_trace_print_locn) {
 				printf("DEFAULT");
+			}
 			break;
 	}
 
@@ -257,6 +289,16 @@
 MR_trace_get_type_and_value(const MR_Stack_Layout_Var *var,
 	Word *type_params, Word *type_info, Word *value)
 {
+	return MR_trace_get_type_and_value_base(var, TRUE,
+		MR_saved_sp(MR_saved_regs), MR_saved_curfr(MR_saved_regs),
+		type_params, type_info, value);
+}
+
+bool
+MR_trace_get_type_and_value_base(const MR_Stack_Layout_Var *var,
+	bool saved_regs_valid, Word *base_sp, Word *base_curfr,
+	Word *type_params, Word *type_info, Word *value)
+{
 	bool	succeeded;
 	Word	*pseudo_type_info;
 	int	i;
@@ -267,6 +309,7 @@
 
 	pseudo_type_info = MR_LIVE_TYPE_GET_VAR_TYPE(var->MR_slv_live_type);
 	*type_info = (Word) MR_create_type_info(type_params, pseudo_type_info);
-	*value = MR_trace_lookup_live_lval(var->MR_slv_locn, &succeeded);
+	*value = MR_trace_lookup_live_lval_base(var->MR_slv_locn,
+		saved_regs_valid, base_sp, base_curfr, &succeeded);
 	return succeeded;
 }
Index: runtime/mercury_trace_util.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace_util.h,v
retrieving revision 1.2
diff -u -u -r1.2 mercury_trace_util.h
--- mercury_trace_util.h	1998/06/14 07:00:20	1.2
+++ mercury_trace_util.h	1998/06/14 07:30:55
@@ -13,10 +13,19 @@
 
 extern	Word	*MR_trace_materialize_typeinfos(const MR_Stack_Layout_Vars
 			*vars);
+extern	Word	*MR_trace_materialize_typeinfos_base(const MR_Stack_Layout_Vars
+			*vars, bool saved_regs_valid,
+			Word *base_sp, Word *base_curfr);
 
 extern	Word	MR_trace_make_var_list(const MR_Stack_Layout_Label *layout);
 extern	Word	MR_trace_lookup_live_lval(MR_Live_Lval locn, bool *succeeded);
+extern	Word	MR_trace_lookup_live_lval_base(MR_Live_Lval locn,
+			bool saved_regs_valid, Word *base_sp, Word *base_curfr,
+			bool *succeeded);
 extern	bool	MR_trace_get_type_and_value(const MR_Stack_Layout_Var *var,
+			Word *type_params, Word *type_info, Word *value);
+extern	bool	MR_trace_get_type_and_value_base(const MR_Stack_Layout_Var *var,
+			bool saved_regs_valid, Word *base_sp, Word *base_curfr,
 			Word *type_params, Word *type_info, Word *value);
 
 #endif	/* MERCURY_TRACE_UTIL_H */
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



More information about the developers mailing list